Skip to content
Snippets Groups Projects
  1. Jun 08, 2017
  2. Jun 07, 2017
    • Simon Peyton Jones's avatar
      Test Trac #13750 · ef07010c
      Simon Peyton Jones authored
      ef07010c
    • Simon Peyton Jones's avatar
      Stop the specialiser generating loopy code · 2b74bd9d
      Simon Peyton Jones authored
      This patch fixes a bad bug in the specialiser, which showed up as
      Trac #13429.  When specialising an imported DFun, the specialiser could
      generate a recusive loop where none existed in the original program.
      
      It's all rather tricky, and I've documented it at some length in
         Note [Avoiding loops]
      
      We'd encoutered exactly this before (Trac #3591) but I had failed
      to realise that the very same thing could happen for /imported/
      DFuns.
      
      I did quite a bit of refactoring.
      
      The compiler seems to get a tiny bit faster on
         deriving/perf/T10858
      but almost all the gain had occurred before now; this
      patch just pushed it over the line.
      2b74bd9d
    • Simon Peyton Jones's avatar
      Spelling typos · 92a4f908
      Simon Peyton Jones authored
      92a4f908
  3. Jun 06, 2017
    • Gabor Greif's avatar
      Typo in output of remote slave startup [merge cand] · e77b9a20
      Gabor Greif authored
      The output is not being checked in the test suite.
      However other tools may check it for obtaining the status
      of the remote slave.
      
      So I'd suggest to merge this to 8.2 branch, in order to not
      fragment the tooling's checks.
      e77b9a20
  4. Jun 05, 2017
    • Alan Zimmerman's avatar
      Udate hsSyn AST to use Trees that Grow · 8e6ec0fa
      Alan Zimmerman authored
      Summary:
      See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow
      
      This commit prepares the ground for a full extensible AST, by replacing the type
      parameter for the hsSyn data types with a set of indices into type families,
      
          data GhcPs -- ^ Index for GHC parser output
          data GhcRn -- ^ Index for GHC renamer output
          data GhcTc -- ^ Index for GHC typechecker output
      
      These are now used instead of `RdrName`, `Name` and `Id`/`TcId`/`Var`
      
      Where the original name type is required in a polymorphic context, this is
      accessible via the IdP type family, defined as
      
          type family IdP p
          type instance IdP GhcPs = RdrName
          type instance IdP GhcRn = Name
          type instance IdP GhcTc = Id
      
      These types are declared in the new 'hsSyn/HsExtension.hs' module.
      
      To gain a better understanding of the extension mechanism, it has been applied
      to `HsLit` only, also replacing the `SourceText` fields in them with extension
      types.
      
      To preserve extension generality, a type class is introduced to capture the
      `SourceText` interface, which must be honoured by all of the extension points
      which originally had a `SourceText`.  The class is defined as
      
          class HasSourceText a where
            -- Provide setters to mimic existing constructors
            noSourceText  :: a
            sourceText    :: String -> a
      
            setSourceText :: SourceText -> a
            getSourceText :: a -> SourceText
      
      And the constraint is captured in `SourceTextX`, which is a constraint type
      listing all the extension points that make use of the class.
      
      Updating Haddock submodule to match.
      
      Test Plan: ./validate
      
      Reviewers: simonpj, shayan-najd, goldfire, austin, bgamari
      
      Subscribers: rwbarton, thomie, mpickering
      
      Differential Revision: https://phabricator.haskell.org/D3609
      8e6ec0fa
    • Douglas Wilson's avatar
      Desugar modules compiled with -fno-code · c9eb4385
      Douglas Wilson authored
      Previously modules with hscTarget == HscNothing were not desugared.
      This patch changes behavior so that all modules HsSrcFile Modules except GHC.Prim
      are desugared. Modules with hscTarget == HscNothing are not simplified.
      
      Warnings and errors produced by the desugarer will now be produced when
      compiling with -fno-code.
      
      HscMain.finishTypecheckingOnly is removed, HscMain.hscIncrementalCompile is
      simplified a bit, and HscMain.finish takes in the removed logic. I think this
      is easier to follow.
      
      Updates haddock submodule.
      
      Tests T8101, T8101b, T10600 are no longer expect_broken.
      
      Reviewers: ezyang, austin, bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #10600
      
      Differential Revision: https://phabricator.haskell.org/D3542
      c9eb4385
    • Simon Peyton Jones's avatar
      Make the MR warning more accurage · a65dfea5
      Simon Peyton Jones authored
      Trac #13785 showed that we were emitting monomorphism warnings
      when we shouldn't.  The fix turned out to be simple.
      
      In fact test T10935 then turned out to be another example of
      the over-noisy warning so I changed the test slightly.
      a65dfea5
    • Simon Peyton Jones's avatar
      Test Trac #13784 · 6597f084
      Simon Peyton Jones authored
      6597f084
  5. Jun 02, 2017
    • Ben Gamari's avatar
      ghc.mk: Ensure that ghc-pkg path is quoted · ff363bd7
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Otherwise this will fail if the prefix path contains spaces. Thanks to
      marinelli for pointing this out.
      
      Test Plan: Validate
      
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3604
      ff363bd7
    • Ryan Scott's avatar
      Use lengthIs and friends in more places · a786b136
      Ryan Scott authored
      While investigating #12545, I discovered several places in the code
      that performed length-checks like so:
      
      ```
      length ts == 4
      ```
      
      This is not ideal, since the length of `ts` could be much longer than 4,
      and we'd be doing way more work than necessary! There are already a slew
      of helper functions in `Util` such as `lengthIs` that are designed to do
      this efficiently, so I found every place where they ought to be used and
      did just that. I also defined a couple more utility functions for list
      length that were common patterns (e.g., `ltLength`).
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, goldfire, bgamari, simonmar
      
      Reviewed By: bgamari, simonmar
      
      Subscribers: goldfire, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3622
      a786b136
    • Ryan Scott's avatar
      GHC.Stats cleanup · 811a2986
      Ryan Scott authored
      This does two things:
      
      * The `RtsTime` type wasn't exported, but it is used as the type of
        several record fields. Let's export it and give it some documentation.
      * Neither `RTSStats` nor `GCDetails` have `Read` or `Show` instances,
        but `GCStats` does! Let's fix this discrepancy.
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: goldfire, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3625
      811a2986
    • Ryan Scott's avatar
      Make GHCi work when RebindableSyntax is enabled · 2abe54e1
      Ryan Scott authored
      Previously, we were running some blocks of code at the start of every
      GHCi sessions which use do-notation, something which doesn't work well
      if you start GHCi with the `-XRebindableSyntax` flag on. This tweaks the
      code to avoid the use of do-notation so that `-XRebindableSyntax` won't
      reject it.
      
      Test Plan: make test TEST=T13385
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13385
      
      Differential Revision: https://phabricator.haskell.org/D3621
      2abe54e1
    • Ryan Scott's avatar
      Remove references to static flags in flag reference · bf775e9d
      Ryan Scott authored
      A follow-up to #8440 (Ditch static flags). There are still some
      lingering references to static flags in the flag reference, so let's
      modify those references accordingly.
      
      Test Plan: Build the documentation
      
      Reviewers: bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3615
      bf775e9d
    • Ryan Scott's avatar
      Add a flag reference entry for -XTypeInType · d0fb0df3
      Ryan Scott authored
      Test Plan: Read it
      
      Reviewers: bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13762
      
      Differential Revision: https://phabricator.haskell.org/D3614
      d0fb0df3
    • Tamar Christina's avatar
      Better import library support for Windows · 93489cd3
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      The import library support added for 7.10.3 was only a partial one.
      This support was predicated on using file extensions to determine
      whether or not a library was an import library. It also couldn't handle
      libraries with multiple dll pointers.
      
      This is a rewrite of that patch and fully integrating it into the normal
      archive parsing and loading routines. This solves a host of issues,
      among others allowing us to finally use `-lgcc_s`.
      
      This also fixes a problem with our previous implementation, where we
      just loaded the DLL and moved on. Doing this had the potential of using
      the wrong symbol at resolve time. Say a DLL already loaded (A.dll) has
      symbol a exported (dependency of another dll perhaps).
      
      We find an import library `B.lib` explicitly defining an export of `a`.
      we load `B.dll` but this gets put after `A.dll`, at resolve time we
      would use the value from `A` instead of `B` which is what we wanted.
      
      Test Plan: ./valide and make test TEST=13606
      
      Reviewers: austin, bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, RyanGlScott, thomie, #ghc_windows_task_force
      
      GHC Trac Issues: #13606, #12499, #12498
      
      Differential Revision: https://phabricator.haskell.org/D3513
      93489cd3
    • Ben Gamari's avatar
      aclocal: Fix regression in linker detection · 5164cce2
      Ben Gamari authored
      5ddb307e regressed autoconf's ability to
      find the linker due to a silly variable interpolation issue, causing
      segmentation faults on AArch64.
      5164cce2
    • Moritz Angermann's avatar
      [iserv] move forkIO · 35c7ea8b
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      This moves the forkIO into the `startSlave` function from the
      `startSlave'` function, such that this allows consumers to call
      `forkSlave'` if they want the blocking behaviour.
      
      Reviewers: bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3601
      35c7ea8b
    • Gabor Greif's avatar
      A few typos [ci skip] · 750a25f4
      Gabor Greif authored
      750a25f4
  6. Jun 01, 2017
  7. May 31, 2017
  8. May 30, 2017
    • niteria's avatar
      Efficient checks for stable modules · 8bfab438
      niteria authored
      With a large number of modules in a home package
      (in my case 5000) the costs of linear lookups becomes significant.
      This changes them to efficient IntMap lookups.
      
      It reduces the cost of `:reload` on unchanged source
      from 5.77s to 1.62s on my test case.
      
      I could go further and make `Linker.unload` also take a set,
      but I prefer to concentrate on one thing at a time.
      
      Test Plan: harbormaster
      
      Reviewers: simonmar, austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3611
      8bfab438
  9. May 29, 2017
  10. May 28, 2017
  11. May 27, 2017
  12. May 26, 2017
    • Ryan Scott's avatar
      Add regression test for #13758 · c8231408
      Ryan Scott authored
      c8231408
    • Ben Gamari's avatar
      Revert "Rewrite boot in Python" · 7fce4cbc
      Ben Gamari authored
      This reverts commit 0440af6a.
      Unfortunately this breaks on Windows for tiresome reasons. I'll need to
      reevaluate this.
      7fce4cbc
    • Gabor Greif's avatar
      Typos in comments [ci skip] · 19c4203f
      Gabor Greif authored
      19c4203f
    • Simon Peyton Jones's avatar
      Some tidying up of type pretty-printing · ad14efd5
      Simon Peyton Jones authored
      Triggered by the changes in #13677, I ended up doing a bit of
      refactoring in type pretty-printing.
      
      * We were using TyOpPrec and FunPrec rather inconsitently, so
        I made it consisent.
      
      * That exposed the fact that we were a bit undecided about whether
        to print
           a + b -> c + d   vs   (a+b) -> (c+d)
        and similarly
           a ~ [b] => blah  vs   (a ~ [b]) => blah
      
        I decided to make TyOpPrec and FunPrec compare equal
        (in BasicTypes), so (->) is treated as equal precedence with
        other type operators, so you get the unambiguous forms above,
        even though they have more parens.
      
        We could readily reverse this decision.
        See Note [Type operator precedence] in BasicTypes
      
      * I fixed a bug in pretty-printing of HsType where some
        parens were omitted by mistake.
      ad14efd5
    • Simon Peyton Jones's avatar
      Shrink a couple of hs-boot files · 226860e7
      Simon Peyton Jones authored
      IfaceType.hs-boot and ToIface.hs-boot were bigger than they
      needed to be, so I'm shrinking them.
      226860e7
    • Simon Peyton Jones's avatar
      Re-engineer Given flatten-skolems · 8dc6d645
      Simon Peyton Jones authored
      The big change here is to fix an outright bug in flattening of Givens,
      albeit one that is very hard to exhibit.  Suppose we have the constraint
          forall a. (a ~ F b) => ..., (forall c. ....(F b)...) ...
      
      Then
       - we'll flatten the (F) b to a fsk, say  (F b ~ fsk1)
       - we'll rewrite the (F b) inside the inner implication to 'fsk1'
       - when we leave the outer constraint we are suppose to unflatten;
         but that fsk1 will still be there
       - if we re-simplify the entire outer implication, we'll re-flatten
         the Given (F b) to, say, (F b ~ fsk2)
      Now we have two fsks standing for the same thing, and that is very
      wrong.
      
      Solution: make fsks behave more like fmvs:
       - A flatten-skolem is now a MetaTyVar, whose MetaInfo is FlatSkolTv
       - We "fill in" that meta-tyvar when leaving the implication
       - The old FlatSkol form of TcTyVarDetails is gone completely
       - We track the flatten-skolems for the current implication in
         a new field of InertSet, inert_fsks.
      
      See Note [The flattening story] in TcFlatten.
      
      In doing this I found various other things to fix:
      
      * I removed the zonkSimples from TcFlatten.unflattenWanteds; it wasn't
        needed.   But I added one in TcSimplify.floatEqualities, which does
        the zonk precisely when it is needed.
      
      * Trac #13674 showed up a case where we had
           - an insoluble Given,   e.g.  a ~ [a]
           - the same insoluble Wanted   a ~ [a]
        We don't use the Given to rewwrite the Wanted (obviously), but
        we therefore ended up reporting
            Can't deduce (a ~ [a]) from (a ~ [a])
        which is silly.
      
        Conclusion: when reporting errors, make the occurs check "win"
        See Note [Occurs check wins] in TcErrors
      8dc6d645
    • Simon Peyton Jones's avatar
      Make isInsolubleOccursCheck more aggressive · c2eea089
      Simon Peyton Jones authored
      Consider
        type family F a :: * -> *
      
      Then (a ~ F Int a) is an insoluble occurs check, and can be reported
      as such.  Previous to this patch, TcType.isInsolubleOccursCheck was
      treating any type-family application (including an over-saturated one)
      as unconditionally not-insoluble.
      
      This really only affects error messages, and then only slightly. I
      tripped over this when investigating  Trac #13674.
      c2eea089
    • Simon Peyton Jones's avatar
      A bit more tc-tracing · 17055da1
      Simon Peyton Jones authored
      17055da1
  13. May 25, 2017
    • Sergei Trofimovich's avatar
      rules: add per-library EXTRA_HC_OPTS · f011f587
      Sergei Trofimovich authored
      
      Sometimes it's handy to change a compiler flag
      for a library in stage{0,1,2}.
      
      Usage example:
      
          libraries/binary_EXTRA_HC_OPTS += -O1
          libraries/containers_EXTRA_HC_OPTS += -O1
          libraries/bytestring_EXTRA_HC_OPTS += -O1
      
      Here override default -O2 defined in .cabal files
      for these libraries to speed build up.
      
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      f011f587
    • Simon Peyton Jones's avatar
      Pattern synonyms and higher rank types · c9977385
      Simon Peyton Jones authored
      This patch fixes two separate bugs which contributed to making
      Trac #13752 go wrong
      
      1.  We need to use tcSubType, not tcUnify,
          in tcCheckPatSynDecl.tc_arg.
      
          Reason: Note [Pattern synonyms and higher rank types]
      
      2.  TcUnify.tc_sub_type had a special case designed to improve error
          messages; see Note [Don't skolemise unnecessarily].  But the
          special case was too liberal, and ended up using unification
          (which led to rejecting the program) when it should instead taken
          the normal path (which accepts the program).
      
          I fixed this by making the test more conservative.
      c9977385
    • Simon Peyton Jones's avatar
      Comments only · 10131947
      Simon Peyton Jones authored
      10131947
Loading