Skip to content
Snippets Groups Projects
  1. Jun 04, 2018
    • Tao He's avatar
      Fix broken test T14547. · d8efb098
      Tao He authored
      Phab:D4571 lags behind HEAD for too many commits. The commit of
      Phab:4571 1f88f541 brought some
      unintentional changes (not belong to [Phab:4571's Diff
      16314](https://phabricator.haskell.org/differential/diff/16314/)) into
      ghc-head, breaking T14557.
      
      Let's fix that.
      
      Test Plan: make test TEST="T14547"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15222
      
      Differential Revision: https://phabricator.haskell.org/D4778
      d8efb098
    • Ben Gamari's avatar
      Bump stm and haskeline submodules · c560f382
      Ben Gamari authored
      c560f382
    • Simon Peyton Jones's avatar
      Refactor SetLevels.abstractVars · a1a507a1
      Simon Peyton Jones authored
      This patch is pure refactoring: using utility functions
      rather than special-purpose code, especially for closeOverKinds
      a1a507a1
    • Simon Peyton Jones's avatar
      Expand type synonyms when Linting a forall · 9d600ea6
      Simon Peyton Jones authored
      Trac #14939 showed a type like
         type Alg cls ob = ob
         f :: forall (cls :: * -> Constraint) (b :: Alg cls *). b
      
      where the kind of the forall looks like (Alg cls *), with a
      free cls. This tripped up Core Lint.
      
      I fixed this by making Core Lint a bit more forgiving, expanding
      type synonyms if necessary.
      
      I'm worried that this might not be the whole story; notably
      typeKind looks suspect.  But it certainly fixes this problem.
      9d600ea6
    • Simon Peyton Jones's avatar
      Do a late CSE pass · 0e5d2b74
      Simon Peyton Jones authored
      When investigating something else I found that a condition
      was being re-evaluated in wheel-seive1.  Why, when CSE should
      find it?  Because the opportunity only showed up after
      LiberateCase
      
      This patch adds a late CSE pass. Rather than give it an extra
      flag I do it when (cse && (spec_constr || liberate_case)), so
      roughly speaking it happense with -O2.
      
      In any case, CSE is very cheap.
      
      Nofib results are minor but in the right direction:
      
              Program           Size    Allocs   Runtime   Elapsed  TotalMem
      --------------------------------------------------------------------------------
                 anna          -0.1%     -0.0%     0.163     0.163      0.0%
                eliza          -0.1%     -0.4%     0.001     0.001      0.0%
                 fft2          -0.1%      0.0%     0.087     0.087      0.0%
                 mate          -0.0%     -1.3%     -0.8%     -0.8%      0.0%
            paraffins          -0.0%     -0.1%     +0.9%     +0.9%      0.0%
                  pic          -0.0%     -0.1%     0.009     0.009      0.0%
         wheel-sieve1          -0.2%     -0.0%     -0.1%     -0.1%      0.0%
      --------------------------------------------------------------------------------
                  Min          -0.6%     -1.3%     -2.4%     -2.4%      0.0%
                  Max          +0.0%     +0.0%     +3.8%     +3.8%    +23.8%
       Geometric Mean          -0.0%     -0.0%     +0.2%     +0.2%     +0.2%
      0e5d2b74
    • Matthew Pickering's avatar
      Provide `getWithUserData` and `putWithUserData` · 554bc7fc
      Matthew Pickering authored
      Summary:
      This makes it possible to serialise Names and FastStrings in user
      programs, for example, when writing a source plugin.
      
      When writing my first source plugin, I wanted to serialise names but it
      wasn't possible easily without exporting additional constructors. This
      interface is sufficient and abstracts nicely over the symbol table and
      dictionary.
      
      Reviewers: alpmestan, bgamari
      
      Reviewed By: alpmestan
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15223
      
      Differential Revision: https://phabricator.haskell.org/D4782
      554bc7fc
  2. Jun 03, 2018
    • Ben Gamari's avatar
      testsuite: Really mark T14547 as broken · 4dd1895b
      Ben Gamari authored
      4dd1895b
    • Ben Gamari's avatar
      testsuite: Mark T14547 as broken · b564eb7e
      Ben Gamari authored
      b564eb7e
    • Ryan Scott's avatar
      Add tests for #8128 and #8740 · 90e99c4c
      Ryan Scott authored
      Commit 08073e16 (#11066) ended up
      fixing these, fortunately enough.
      90e99c4c
    • Joachim Breitner's avatar
      Fix typo in OverloadedLabels docs · 61280373
      Joachim Breitner authored
      as helpfully reported by elpinal (#15217).
      61280373
    • Tao He's avatar
      Improve exhaustiveness checking for literal values and patterns, fix #14546 · 1f88f541
      Tao He authored
      Currently, we parse both the **integral literal** value and the patterns
      as `OverLit HsIntegral`.  For example:
      
      ```
        case 0::Int of
            0 -> putStrLn "A"
            1 -> putStrLn "B"
            _ -> putStrLn "C"
      ```
      
      When checking the exhaustiveness of pattern matching, we translate the
      `0` in value position as `PmOLit`, but translate the `0` and `1` in
      pattern position as `PmSLit`. The inconsistency leads to the failure of
      `eqPmLit` to detect the equality and report warning of "Pattern match is
      redundant" on pattern `0`, as reported in #14546. In this patch we
      remove the specialization of `OverLit` patterns, and keep the overloaded
      number literal in pattern as it is to maintain the consistency.  Now we
      can capture the exhaustiveness of pattern `0` and the redundancy of
      pattern `1` and `_`.
      
      For **string literals**, we parse the string literals as `HsString`.
      When  `OverloadedStrings` is enabled, it further be turned as `HsOverLit
      HsIsString`, whether it's type is `String` or not. For example:
      
      ```
        case "foo" of
            "foo" -> putStrLn "A"
            "bar" -> putStrLn "B"
            "baz" -> putStrLn "C"
      ```
      
      Previously, the overloaded string values are translated to `PmOLit` and
      the non-overloaded string values are translated to `PmSLit`. However the
      string patterns, both overloaded and non-overloaded, are translated to
      list of characters. The inconsistency leads to wrong warnings about
      redundant and non-exhaustive pattern matching warnings, as reported
      in #14546.
      
      In order to catch the redundant pattern in following case:
      
      ```
        case "foo" of
            ('f':_) -> putStrLn "A"
            "bar" -> putStrLn "B"
      ```
      
      In this patch, we translate non-overloaded string literals, both in
      value position and pattern position, as list of characters. For
      overloaded string literals, we only translate it to list of characters
      only when it's type is `stringTy`, since we know nothing about the
      `toString` methods.  But we know that if two overloaded strings are
      syntax equal, then they are equal. Then if it's type is not `stringTy`,
      we just translate it to `PmOLit`. We can still capture the
      exhaustiveness of pattern `"foo"` and the redundancy of pattern `"bar"`
      and `"baz"` in the following code:
      
      ```
      {-# LANGUAGE OverloadedStrings #-}
      main = do
        case "foo" of
            "foo" -> putStrLn "A"
            "bar" -> putStrLn "B"
            "baz" -> putStrLn "C"
      ```
      
      Test Plan: make test TEST="T14546"
      
      Reviewers: bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: simonpj, thomie, carter
      
      GHC Trac Issues: #14546
      
      Differential Revision: https://phabricator.haskell.org/D4571
      1f88f541
    • Andreas Klebinger's avatar
      Allow aligning of cmm procs at specific boundry · f68c2cb6
      Andreas Klebinger authored
      Allows to align CmmProcs at the given boundries.
      
      It makes performance usually worse but can be helpful
      to limit the effect of a unrelated function B becoming
      faster/slower after changing function A.
      
      Test Plan: ci, using it.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15148
      
      Differential Revision: https://phabricator.haskell.org/D4706
      f68c2cb6
    • Alanas Plascinskas's avatar
      tcExtendTyVarEnv2 changed to tcExtendNameTyVarEnv · 9b7eec86
      Alanas Plascinskas authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: mpickering, goldfire, bgamari
      
      Reviewed By: mpickering
      
      Subscribers: goldfire, rwbarton, thomie, carter
      
      GHC Trac Issues: #15017
      
      Differential Revision: https://phabricator.haskell.org/D4732
      9b7eec86
    • Tobias Dammers's avatar
      Turn "inaccessible code" error into a warning · 08073e16
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      With GADTs, it is possible to write programs such that the type
      constraints make some code branches inaccessible.
      
      Take, for example, the following program ::
      
          {-# LANGUAGE GADTs #-}
      
          data Foo a where
           Foo1 :: Foo Char
           Foo2 :: Foo Int
      
          data TyEquality a b where
                  Refl :: TyEquality a a
      
          checkTEQ :: Foo t -> Foo u -> Maybe (TyEquality t u)
          checkTEQ x y = error "unimportant"
      
          step2 :: Bool
          step2 = case checkTEQ Foo1 Foo2 of
                   Just Refl -> True -- Inaccessible code
                   Nothing -> False
      
      Clearly, the `Just Refl` case cannot ever be reached, because the `Foo1`
      and `Foo2` constructors say `t ~ Char` and `u ~ Int`, while the `Refl`
      constructor essentially mandates `t ~ u`, and thus `Char ~ Int`.
      
      Previously, GHC would reject such programs entirely; however, in
      practice this is too harsh. Accepting such code does little harm, since
      attempting to use the "impossible" code will still produce errors down
      the chain, while rejecting it means we cannot legally write or generate
      such code at all.
      
      Hence, we turn the error into a warning, and provide
      `-Winaccessible-code` to control GHC's behavior upon encountering this
      situation.
      
      Test Plan: ./validate
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #11066
      
      Differential Revision: https://phabricator.haskell.org/D4744
      08073e16
    • Ryan Scott's avatar
      Fix a bad interaction between GADTs and COMPLETE sets · 4d800448
      Ryan Scott authored
      As observed in #14059 (starting at comment 5), the error
      messages surrounding a program involving GADTs and a `COMPLETE` set
      became worse between 8.2 and 8.4. The culprit was a new validity
      check in 8.4 which filters out `COMPLETE` set candidates if a return
      type of any conlike in the set doesn't match the type of the
      scrutinee. However, this check was too conservative, since it removed
      perfectly valid `COMPLETE` sets that contained GADT constructors,
      which quite often have return types that don't match the type of a
      scrutinee.
      
      To fix this, I adopted the most straightforward possible solution of
      only performing this validity check on //pattern synonym//
      constructors, not //data// constructors.
      
      Note that this does not fix #14059 entirely, but instead simply fixes
      a particular buglet that was discovered in that ticket.
      
      Test Plan: make test TEST=T14059
      
      Reviewers: bgamari, mpickering
      
      Reviewed By: mpickering
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14059
      
      Differential Revision: https://phabricator.haskell.org/D4752
      4d800448
    • David Feuer's avatar
      Remove ~# from surface syntax · 5b82ee69
      David Feuer authored
      For some reason, it seems that the `ConstraintKinds` commit
      introduced `~#` into Haskell syntax, in a pretty broken manner.
      Unless and until we have an actual story for unboxed equality,
      it doesn't make sense to expose it. Moreover, the way it was
      donet was wrong enough and small enough that it will probably be
      easier to start over if we do that. Yank it out.
      
      Reviewers: bgamari, RyanGlScott
      
      Reviewed By: RyanGlScott
      
      Subscribers: RyanGlScott, rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #15209
      
      Differential Revision: https://phabricator.haskell.org/D4763
      5b82ee69
    • Tobias Dammers's avatar
      Handle abi-depends correctly in ghc-pkg · 1626fe60
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      When inferring the correct abi-depends, we now look at all the package
      databases in the stack, up to and including the current one, because
      these are the ones that the current package can legally depend on. While
      doing so, we will issue warnings:
      
      - In verbose mode, we warn about every package that declares
        abi-depends:, whether we actually end up overriding them with the
        inferred ones or not ("possibly broken abi-depends").
      
      - Otherwise, we only warn about packages whose declared abi-depends
        does not match what we inferred ("definitely broken abi-depends").
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14381
      
      Differential Revision: https://phabricator.haskell.org/D4729
      1626fe60
    • Ben Gamari's avatar
      rts: Query system rlimit for maximum address-space size · 26273774
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      When we attempt to reserve the heap, we query the system's rlimit to
      establish the starting point for our search over sizes.
      
      Test Plan: Validate
      
      Reviewers: erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14492
      
      Differential Revision: https://phabricator.haskell.org/D4754
      26273774
    • Ryan Scott's avatar
      Fix #15214 by listing (~) in isBuiltInOcc_maybe · 21e9d4f5
      Ryan Scott authored
      This changes an obscure error (which mistakenly mentions
      Template Haskell) to one that makes more sense.
      
      Test Plan: make test TEST=T15214
      
      Reviewers: bgamari, mpickering
      
      Reviewed By: bgamari, mpickering
      
      Subscribers: mpickering, rwbarton, thomie, carter
      
      GHC Trac Issues: #15214
      
      Differential Revision: https://phabricator.haskell.org/D4768
      21e9d4f5
    • Andreas Klebinger's avatar
      Check for singletons when creating Bag/OrdList from a list. · 18cb4f5e
      Andreas Klebinger authored
      This gives us `One x` instead of `Many (x : [])` reducing overhead.
      For compiling spectral/simple with -O0 difference was ~ -0.05%
      allocations.
      
      The only drawback is that something like toOL (x:panic "") will now
      panic.  But that seems like a reasonable tradeoff.
      
      Test Plan: ci, looking at +RTS -s
      
      Reviewers: bgamari, jmct
      
      Reviewed By: bgamari
      
      Subscribers: jmct, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4770
      18cb4f5e
    • Ryan Scott's avatar
      Fix #13777 by improving the underdetermined CUSK error message · ac91d073
      Ryan Scott authored
      The error message that GHC emits from underdetermined CUSKs
      is rather poor, since:
      
      1. It may print an empty list of user-written variables if there
          are none in the declaration.
      2. It may not mention any `forall`-bound, underdetermined
          variables in the result kind.
      
      To resolve these issues, this patch:
      
      1. Doesn't bother printing a herald about user-written
          variables if there are none.
      2. Prints the result kind to advertise any
          underdetermination it may exhibit.
      
      Test Plan: make test TEST=T13777
      
      Reviewers: goldfire, bgamari
      
      Reviewed By: goldfire
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13777
      
      Differential Revision: https://phabricator.haskell.org/D4771
      ac91d073
    • lazac's avatar
      Extended the plugin system to run plugins on more representations · c2783ccf
      lazac authored and Ben Gamari's avatar Ben Gamari committed
      Extend GHC plugins to access parsed, type checked representation,
      interfaces that are loaded. And splices that are evaluated. The goal is
      to enable development tools to access the GHC representation in the
      pre-existing build environment.
      
      See the full proposal here:
      https://ghc.haskell.org/trac/ghc/wiki/ExtendedPluginsProposal
      
      Reviewers: goldfire, bgamari, ezyang, angerman, mpickering
      
      Reviewed By: mpickering
      
      Subscribers: ezyang, angerman, mpickering, ulysses4ever, rwbarton, thomie, carter
      
      GHC Trac Issues: #14709
      
      Differential Revision: https://phabricator.haskell.org/D4342
      c2783ccf
    • Ben Gamari's avatar
      Bump version of stm submodule back to 2.4 · 72725668
      Ben Gamari authored
      Haskeline doesn't have its upper bound lifted yet.
      72725668
  3. Jun 02, 2018
    • Ben Gamari's avatar
      testsuite: Don't assume location of bash · e0f33a6e
      Ben Gamari authored
      e0f33a6e
    • Ben Gamari's avatar
      rts: Rip out support for STM invariants · a122d4fd
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This feature has some very serious correctness issues (#14310),
      introduces a great deal of complexity, and hasn't seen wide usage.
      Consequently we are removing it, as proposed in Proposal #77 [1]. This
      is heavily based on a patch from fryguybob.
      
      Updates stm submodule.
      
      [1] https://github.com/ghc-proposals/ghc-proposals/pull/77
      
      Test Plan: Validate
      
      Reviewers: erikd, simonmar, hvr
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14310
      
      Differential Revision: https://phabricator.haskell.org/D4760
      a122d4fd
    • Sergei Trofimovich's avatar
    • Ben Gamari's avatar
      vectorise: Put it out of its misery · faee23bb
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Poor DPH and its vectoriser have long been languishing; sadly it seems there is
      little chance that the effort will be rekindled. Every few years we discuss
      what to do with this mass of code and at least once we have agreed that it
      should be archived on a branch and removed from `master`. Here we do just that,
      eliminating heaps of dead code in the process.
      
      Here we drop the ParallelArrays extension, the vectoriser, and the `vector` and
      `primitive` submodules.
      
      Test Plan: Validate
      
      Reviewers: simonpj, simonmar, hvr, goldfire, alanz
      
      Reviewed By: simonmar
      
      Subscribers: goldfire, rwbarton, thomie, mpickering, carter
      
      Differential Revision: https://phabricator.haskell.org/D4761
      faee23bb
    • admock's avatar
      Add llvm-target for powerpc64le-unknown-linux · 13a86606
      admock authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15212
      
      Differential Revision: https://phabricator.haskell.org/D4765
      13a86606
    • Ben Gamari's avatar
      Conservatively estimate levity in worker/wrapper · f0c1eb8b
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      The worker/wrapper transform needs to determine the levity of the result to
      determine whether it needs to introduce a lambda to preserve laziness of the
      result. For this is previously used isUnliftedType. However, this may fail in
      the presence of levity polymorphism.
      
      We now instead use isLiftedType_maybe, assuming that a lambda is needed if the
      levity of the result cannot be determined.
      
      Fixes #15186.
      
      Test Plan: make test=T15186
      
      Reviewers: simonpj, goldfire, tdammers
      
      Reviewed By: simonpj
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15186
      
      Differential Revision: https://phabricator.haskell.org/D4755
      f0c1eb8b
    • Ben Gamari's avatar
      testsuite: Add test for #15186 · c983a1db
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Summary: Currently broken.
      
      Test Plan: Validate
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15186
      
      Differential Revision: https://phabricator.haskell.org/D4757
      c983a1db
    • Andreas Klebinger's avatar
      Optimizations for CmmBlockElim. · bd43378d
      Andreas Klebinger authored
      * Use toBlockList instead of revPostorder.
      
          Block elimination works on a given Cmm graph by:
           * Getting a list of blocks.
           * Looking for duplicates in these blocks.
           * Removing all but one instance of duplicates.
      
          There are two (reasonable) ways to get the list of blocks.
           * The fast way: `toBlockList`
             This just flattens the underlying map into a list.
           * The convenient way: `revPostorder`
             Start at the entry label, scan for reachable blocks and return
             only these. This has the advantage of removing all dead code.
      
          If there is dead code the later is better. Work done on unreachable
          blocks is clearly wasted work. However by the point we run the
          common block elimination pass the input graph already had all dead code
          removed. This is done during control flow optimization in
          CmmContFlowOpt which is our first Cmm pass.
      
          This means common block elimination is free to use toBlockList
          because revPostorder would return the same blocks. (Although in
          a different order).
      
      * Change the triemap used for grouping by a label list
        from `(TM.ListMap UniqDFM)` to `ListMap (GenMap LabelMap)`.
      
          * Using GenMap offers leaf compression. Which is a trie
            optimization described by the Note [Compressed TrieMap] in
            CoreSyn/TrieMap.hs
      
          * Using LabelMap removes the overhead associated with UniqDFM.
      
        This is deterministic since if we have the same input keys the same
        LabelMap will be constructed.
      
      Test Plan: ci, profiling output
      
      Reviewers: bgamari, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: dfeuer, thomie, carter
      
      GHC Trac Issues: #15103
      
      Differential Revision: https://phabricator.haskell.org/D4597
      bd43378d
  4. Jun 01, 2018
    • Sergei Trofimovich's avatar
      UNREG: mark SRT as writable in generated C code · 9fd4ed90
      Sergei Trofimovich authored
      
      Noticed section mismatch on UNREG build failure:
      
      ```
        HC [stage 1] libraries/integer-gmp/dist-install/build/GHC/Integer/Type.o
      
           error: conflicting types for 'ufu0_srt'
           static StgWord ufu0_srt[]__attribute__((aligned(8)))= {
                          ^~~~~~~~
      
           note: previous declaration of 'ufu0_srt' was here
           IRO_(ufu0_srt);
                ^~~~~~~~
      ```
      
      `IRO_` is a 'const' qualifier.
      
      The error is a leftover from commit 838b6903
      "Merge FUN_STATIC closure with its SRT" where part of SRT was moved
      into closure itself and made SRTs writable.
      
      This change puts all SRTs into writable section.
      
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      
      Reviewers: simonmar, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4731
      9fd4ed90
    • Gabor Greif's avatar
      Cleanups [ci skip] · 9921f5b0
      Gabor Greif authored
      9921f5b0
  5. May 31, 2018
    • Andreas Klebinger's avatar
      Change jump targets in JMP_TBL from blocks to X86.JumpDest. · 5748c79e
      Andreas Klebinger authored
      Jump tables always point to blocks when we first generate them.  However
      there are rare situations where we can shortcut one of these blocks to a
      static address during the asm shortcutting pass.
      
      While we already updated the data section accordingly this patch also
      extends this to the references stored in JMP_TBL.
      
      Test Plan: ci
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie, carter
      
      GHC Trac Issues: #15104
      
      Differential Revision: https://phabricator.haskell.org/D4595
      5748c79e
    • Moritz Angermann's avatar
      dead strip dylibs on macOS · b592bd98
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      When linking dynamic libraries or executables, we compute the full
      transitive closure over the dependencies, and instruct the linker
      to link all dependencies.  With deep dependency trees the number
      of transitive dependencies can grow quickly.
      
      macOS since the Sierra release has an upper limit on the load
      command sizes the linker parses when loading dynamic lirbaries.
      As such it is mandatory to keep the number of load commands (and
      their size) small on recent macOS releases.
      
      An approach that would just link direct dependencies as specified
      by the -package-id flag is insufficient, because GHC can inline
      across packages and the library or executable being linked could
      refer to symbols deep in the dependency tree.
      
      If we just recursively linked librarys and re-exported their
      symbols, this increases the number of symbols in libraries with
      many dependencies and ultimately puts excessive strain on the
      linker to the point where linking takes a lot longer than even
      the compilation of the modules.
      
      We can however build a list of symbols from the obejcts we want
      to link, and try to compute the libraries we need to link that
      contain those symbols from the transitive dependency closure.
      Luckily, we don't need to write this ourselves, but can use
      the ld64 `-dead_strip_dylibs` linker flag on macOS to achive
      the same result.  This will link only the libraries that are
      actually referenced, which is usually a small subset of the
      full transitive dependency closure.  As such we should stay
      within the load command size limit for almost all but pathological
      cases.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: lelf, rwbarton, thomie, carter
      
      GHC Trac Issues: #14444
      
      Differential Revision: https://phabricator.haskell.org/D4714
      b592bd98
    • Ben Gamari's avatar
      base/TimerManager: Clamp timer expiration time to maxBound · 21a9fb5f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Previously we would allow the expiration time to overflow, which in
      practice meant that `threadDelay maxBound` we return far earlier than
      circa 2500 CE. For now we fix this by simply clamping to maxBound.
      
      Fixes #15158.
      
      Test Plan: Validate, run T8089
      
      Reviewers: simonmar, hvr
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15158
      
      Differential Revision: https://phabricator.haskell.org/D4719
      21a9fb5f
    • Simon Jakobi's avatar
      Make HsDocString a newtype of ByteString · d1beebb8
      Simon Jakobi authored and Ben Gamari's avatar Ben Gamari committed
      Docstrings don't profit from FastString's interning, so we switch to
      a different type that doesn't incur this overhead.
      
      Updates the haddock submodule.
      
      Reviewers: alexbiehl, bgamari
      
      Reviewed By: alexbiehl, bgamari
      
      Subscribers: rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #15157
      
      Differential Revision: https://phabricator.haskell.org/D4743
      d1beebb8
    • Ben Gamari's avatar
      users-guide: Fix various issues in debugging flags section · 471b2a09
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: ggreif
      
      Reviewed By: ggreif
      
      Subscribers: rwbarton, thomie, carter, ggreif
      
      Differential Revision: https://phabricator.haskell.org/D4750
      471b2a09
    • Jens Petersen's avatar
      configure: Make sphinx-build version test work on recent versions · 533d3451
      Jens Petersen authored and Ben Gamari's avatar Ben Gamari committed
      On Fedora: `/usr/libexec/sphinx-build --version` outputs `sphinx-build
      1.7.2`.  In bindir we actually have sphinx-build-2 and sphinx-build-3
      (python2 and python3 versions), which output `sphinx-build-2 1.7.2` and
      `sphinx-build-3 1.7.2` respectively.  Dunno what version others are
      using but at least this change should works for most versions I suppose.
      533d3451
    • Andrew Martin's avatar
      base: Improve documentation of indexArray# · 15ece727
      Andrew Martin authored and Ben Gamari's avatar Ben Gamari committed
      15ece727
Loading