Skip to content
Snippets Groups Projects
  1. Oct 11, 2017
  2. Oct 10, 2017
    • Tamar Christina's avatar
      Split SysTools up some · e51e565d
      Tamar Christina authored
      Summary:
      SysTools and DriverTools have an annoying mutual dependency.
      They also each contain pieces of the linker. In order for
      changes to be shared between the library and the exe linking
      code this dependency needs to be broken in order to avoid
      using hs-boot files.
      
      Reviewers: austin, bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4071
      e51e565d
  3. Oct 07, 2017
    • Ryan Scott's avatar
      Simply Data instance context for AmbiguousFieldOcc · f337a208
      Ryan Scott authored
      The current, verbose instance context can be compacted into
      `DataId pass`. Indeed, that's what most of the `Data` instances
      in this module already do, so this just makes things consistent.
      f337a208
    • Ryan Scott's avatar
      Fix #14320 by looking through HsParTy in more places · f1d2db68
      Ryan Scott authored
      Summary:
      GHC was needlessly rejecting GADT constructors' type
      signatures that were surrounded in parentheses due to the fact that
      `splitLHsForAllTy` and `splitLHsQualTy` (which are used to check as
      part of checking if GADT constructor return types are correct)
      weren't looking through parentheses (i.e., `HsParTy`). This is
      easily fixed, though.
      
      Test Plan: make test TEST=T14320
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14320
      
      Differential Revision: https://phabricator.haskell.org/D4072
      f1d2db68
    • Ryan Scott's avatar
      Incorporate changes from #11721 into Template Haskell · 341d3a78
      Ryan Scott authored
      Summary:
      #11721 changed the order of type variables in GADT
      constructor type signatures, but these changes weren't reflected in
      Template Haskell reification of GADTs. Let's do that.
      
      Along the way, I:
      
      * noticed that the `T13885` test was claiming to test TH reification
        of GADTs, but the reified data type wasn't actually a GADT! Since
        this patch touches that part of the codebase, I decided to fix
        this.
      * incorporated some feedback from @simonpj in
        https://phabricator.haskell.org/D3687#113566. (These changes alone
        don't account for any different in behavior.)
      
      Test Plan: make test TEST=T11721_TH
      
      Reviewers: goldfire, austin, bgamari, simonpj
      
      Reviewed By: goldfire, bgamari, simonpj
      
      Subscribers: rwbarton, thomie, simonpj
      
      GHC Trac Issues: #11721
      
      Differential Revision: https://phabricator.haskell.org/D4070
      341d3a78
  4. Oct 06, 2017
  5. Oct 05, 2017
  6. Oct 04, 2017
  7. Oct 03, 2017
    • Ben Gamari's avatar
      user-guide: Mention COMPLETE pragma in release notes · 3201d85f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14305
      
      Differential Revision: https://phabricator.haskell.org/D4059
      3201d85f
    • Ben Gamari's avatar
      base: Remove deprecated Chan combinators · 361af628
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Removes isEmptyChan and unGetChan, which have been deprecated for a very
      long time. See #13561.
      
      Test Plan: Validate
      
      Reviewers: austin, hvr
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13561
      
      Differential Revision: https://phabricator.haskell.org/D4060
      361af628
    • Douglas Wilson's avatar
      Don't pass HscEnv to functions in the Hsc monad · 4899a86b
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      `Hsc` is a reader monad in `HscEnv`. Several functions in HscMain were
      taking parameters of type `HscEnv` or `DynFlags`, and returning values
      of type `Hsc a`. This patch removes those parameters in favour of asking
      them from the context.
      
      This removes a source of confusion and should make refactoring a bit
      easier.
      
      Test Plan: ./validate
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4061
      4899a86b
    • Edward Z. Yang's avatar
      Include libraries which fill holes as deps when linking. · f3f624ae
      Edward Z. Yang authored
      Fixes the issue reported at https://github.com/haskell/cabal/issues/4755
      
      
      and fixes #14304 in the GHC tracker.
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
      
      Test Plan: validate
      
      Reviewers: bgamari, austin, goldfire
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14304
      
      Differential Revision: https://phabricator.haskell.org/D4057
      f3f624ae
    • Moritz Angermann's avatar
      genapply: Explicitly specify arguments · de1b802b
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      We seem to not be feeding either live registers or the arguments when
      generating the fast call in genapply.  This results in strange signature
      missmatches between the callee (expecting no registers) and the call
      site, expecting to pass registers.
      
      Test Plan: validate
      
      Reviewers: bgamari, simonmar, austin
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4029
      de1b802b
    • Ben Gamari's avatar
      base: Add missing @since annotations in GHC.TypeNats · 377d5a26
      Ben Gamari authored
      [skip ci]
      377d5a26
    • Iavor S. Diatchki's avatar
      Implement Div, Mod, and Log for type-level nats. · fa8035e3
      Iavor S. Diatchki authored
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, dfeuer, adamgundry, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4002
      fa8035e3
    • Ryan Scott's avatar
      Track the order of user-written tyvars in DataCon · ef26182e
      Ryan Scott authored
      After typechecking a data constructor's type signature, its type
      variables are partitioned into two distinct groups: the universally
      quantified type variables and the existentially quantified type
      variables. Then, when prompted for the type of the data constructor,
      GHC gives this:
      
      ```lang=haskell
      MkT :: forall <univs> <exis>. (...)
      ```
      
      For H98-style datatypes, this is a fine thing to do. But for GADTs,
      this can sometimes produce undesired results with respect to
      `TypeApplications`. For instance, consider this datatype:
      
      ```lang=haskell
      data T a where
        MkT :: forall b a. b -> T a
      ```
      
      Here, the user clearly intended to have `b` be available for visible
      type application before `a`. That is, the user would expect
      `MkT @Int @Char` to be of type `Int -> T Char`, //not//
      `Char -> T Int`. But alas, up until now that was not how GHC
      operated—regardless of the order in which the user actually wrote
      the tyvars, GHC would give `MkT` the type:
      
      ```lang=haskell
      MkT :: forall a b. b -> T a
      ```
      
      Since `a` is universal and `b` is existential. This makes predicting
      what order to use for `TypeApplications` quite annoying, as
      demonstrated in #11721 and #13848.
      
      This patch cures the problem by tracking more carefully the order in
      which a user writes type variables in data constructor type
      signatures, either explicitly (with a `forall`) or implicitly
      (without a `forall`, in which case the order is inferred). This is
      accomplished by adding a new field `dcUserTyVars` to `DataCon`, which
      is a subset of `dcUnivTyVars` and `dcExTyVars` that is permuted to
      the order in which the user wrote them. For more details, refer to
      `Note [DataCon user type variables]` in `DataCon.hs`.
      
      An interesting consequence of this design is that more data
      constructors require wrappers. This is because the workers always
      expect the first arguments to be the universal tyvars followed by the
      existential tyvars, so when the user writes the tyvars in a different
      order, a wrapper type is needed to swizzle the tyvars around to match
      the order that the worker expects. For more details, refer to
      `Note [Data con wrappers and GADT syntax]` in `MkId.hs`.
      
      Test Plan: ./validate
      
      Reviewers: austin, goldfire, bgamari, simonpj
      
      Reviewed By: goldfire, simonpj
      
      Subscribers: ezyang, goldfire, rwbarton, thomie
      
      GHC Trac Issues: #11721, #13848
      
      Differential Revision: https://phabricator.haskell.org/D3687
      ef26182e
    • Tamar Christina's avatar
      Optimize linker by minimizing calls to tryGCC to avoid fork/exec overhead. · 8d647450
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      On Windows process creations are fairly expensive. As such calling them in
      what's essentially a hot loop is also fairly expensive.
      
      Each time we make a call to `tryGCC` the following fork/exec/wait happen
      
      ```
      gcc -> realgcc -> cc1
      ```
      
      This is very problematic, because according to the profiler about 20% of the
      time is spent on just process creation and spin time.
      
      The goal of the patch is to mitigate this by asking GCC once for it's search
      directories, caching these (because it's very hard to change these at all
      after the process started since GCC's base dirs don't change unless with
      extra supplied `-B` flags.).
      
      We also do the same for the `findSysDll` function, since this computes
      the search path every time by registery accesses etc.
      
      These changes and D3909 drop GHC on Windows startup time from 2-3s to 0.5s.
      
      The remaining issue is a 1.5s wait lock on `CONIN$` which can be addressed
      with the new I/O manager code. But this makes GHCi as responsive on Windows as
      GHC 7.8 was.
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3910
      8d647450
    • Tamar Christina's avatar
      Add ability to produce crash dumps on Windows · ec9ac20d
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      It's often hard to debug things like segfaults on Windows,
      mostly because gdb isn't always of use and users don't know
      how to effectively use it.
      
      This patch provides a way to create a crash drump by passing
      
      `+RTS --generate-crash-dumps` as an option. If any unhandled
      exception is triggered a dump is made that contains enough
      information to be able to diagnose things successfully.
      
      Currently the created dumps are a bit big because I include
      all registers, code and threads information.
      
      This looks like
      
      ```
      $ testsuite/tests/rts/derefnull.run/derefnull.exe +RTS
      --generate-crash-dumps
      
      Access violation in generated code when reading 0000000000000000
      Crash dump created. Dump written to:
              E:\msys64\tmp\ghc-20170901-220250-11216-16628.dmp
      ```
      
      Test Plan: ./validate
      
      Reviewers: austin, hvr, bgamari, erikd, simonmar
      
      Reviewed By: bgamari, simonmar
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3912
      ec9ac20d
    • Herbert Valerio Riedel's avatar
      Sync base/changelog.md · 55001c0c
      Herbert Valerio Riedel authored
      This updates the base-4.10.0.0 entry heading which has diverged from
      
       http://hackage.haskell.org/package/base-4.10.0.0/src/changelog.md
      
      and while at it also sets the GHC version for the base-4.11 entry to
      avoid confusion about what GHC 8.2.2's base is going to include.
      
      [skip ci]
      55001c0c
    • Joachim Breitner's avatar
      Revert installing texinfo in CI systems · a36eea1a
      Joachim Breitner authored
      This reverts commit 00ff0235.
      This reverts commit 11a59de2.
      a36eea1a
    • Ryan Scott's avatar
      Add regression test for #9725 · a02039c7
      Ryan Scott authored
      Kind equalities saves the day!
      a02039c7
    • Simon Peyton Jones's avatar
      Suppress error cascade in record fields · cb767542
      Simon Peyton Jones authored
      When a record contruction or pattern uses a data constructor
      that isn't in scope, we may produce spurious ambiguous-field
      errors (Trac #14307).  E.g.
      
         f (A { fld = x }) = e
      
      where 'A' is not in scope.  We want to draw attention to the
      out-of-scope data constructor first; once that is fixed we
      can think about the fields.
      
      This patch suppresses the field errors if the data con is out
      of scope.
      cb767542
    • Simon Peyton Jones's avatar
      Fix nasty bug in w/w for absence analysis · dbbee1ba
      Simon Peyton Jones authored
      This dark corner was exposed by Trac #14285.  It involves the
      interaction between absence analysis and INLINABLE pragmas.
      
      There is a full explanation in Note [aBSENT_ERROR_ID] in MkCore,
      which you can read there.  The changes in this patch are
      
      * Make exprIsHNF return True for absentError, treating
        absentError like an honorary data constructor.
      
      * Make absentError /not/ be diverging, unlike other error Ids.
      
      This is all a bit horrible.
      
      * While doing this I found that exprOkForSpeculation didn't
        have a case for value lambdas so I added one.  It's not
        really called on lifted types much, but it seems like the
        right thing
      dbbee1ba
    • Simon Peyton Jones's avatar
      Make GHC.IO.Buffer.summaryBuffer strict · b1e0c65a
      Simon Peyton Jones authored
      I came across this when debugging something else.  Making it strict
      improves the code slightly without affecting behaviour.
      b1e0c65a
    • Simon Peyton Jones's avatar
      Fix bug in the short-cut solver · a8fde183
      Simon Peyton Jones authored
      Trac #13943 showed that the relatively-new short-cut solver
      for class constraints (aka -fsolve-constant-dicts) was wrong.
      In particular, see "Type families" under Note [Shortcut solving]
      in TcInteract.
      
      The short-cut solver recursively solves sub-goals, but it doesn't
      flatten type-family applications, and as a result it erroneously
      thought that C (F a) cannot possibly match (C 0), which is
      simply untrue.  That led to an inifinte loop in the short-cut
      solver.
      
      The significant change is the one line
      
      +                 , all isTyFamFree preds  -- See "Type families" in
      +                                          -- Note [Shortcut solving]
      
      but, as ever, I do some other refactoring.  (E.g. I changed the
      name of the function to shortCutSolver rather than the more
      generic trySolveFromInstance.)
      
      I also made the short-cut solver respect the solver-depth limit,
      so that if this happens again it won't just produce an infinite
      loop.
      
      A bit of other refactoring, notably moving isTyFamFree
      from TcValidity to TcType
      a8fde183
    • Simon Peyton Jones's avatar
      Comments only · a1fc7ce3
      Simon Peyton Jones authored
      a1fc7ce3
    • Moritz Angermann's avatar
      Adds x86 NONE relocation type · a4ee2897
      Moritz Angermann authored
      Summary:
      As reported by Alex Lang, R_X86_64_NONE relocations
      appear in per-package object files, not per-module object
      files. This diff adds _NONE relocations for x86.
      
      Reviewers: bgamari, geekosaur, austin, erikd, simonmar
      
      Reviewed By: geekosaur
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4062
      a4ee2897
    • Moritz Angermann's avatar
      No libffi docs · d0c5d8de
      Moritz Angermann authored
      Summary:
      building libffi docs with our intree-libffi seems
      rather pointless.
      
      Reviewers: bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4054
      d0c5d8de
Loading