Skip to content
Snippets Groups Projects
  1. Jan 14, 2018
    • Ryan Scott's avatar
      Add regression test for #14040 · 0d406936
      Ryan Scott authored
      This adds a regression test for the original program in #14040.
      
      This does not fix #14040 entirely, though, as the program in
      https://ghc.haskell.org/trac/ghc/ticket/14040#comment:2 still
      panics, so there is more work to be done there.
      
      (cherry picked from commit be1ca0e4)
      0d406936
    • Simon Peyton Jones's avatar
      Drop dead Given bindings in setImplicationStatus · 5124b04f
      Simon Peyton Jones authored
      Trac #13032 pointed out that we sometimes generate unused
      bindings for Givens, and (worse still) we can't always discard
      them later (we don't drop a case binding unless we can prove
      that the scrutinee is non-bottom.
      
      It looks as if this may be a major reason for the performace
      problems in #14338 (see comment:29).
      
      This patch fixes the problem at source, by pruning away all the
      dead Givens.  See Note [Delete dead Given evidence bindings]
      
      Remarkably, compiler allocation falls by 23% in
      perf/compiler/T12227!
      
      I have not confirmed whether this change actualy helps with
      
      (cherry picked from commit 954cbc7c)
      5124b04f
    • Simon Peyton Jones's avatar
      Fix floating of equalities · 594879dc
      Simon Peyton Jones authored
      This rather subtle patch fixes Trac #14584.  The problem was
      that we'd allowed a coercion, bound in a nested scope, to escape
      into an outer scope.
      
      The main changes are
      
      * TcSimplify.floatEqualities takes more care when floating
        equalities to make sure we don't float one out that mentions
        a locally-bound coercion.
        See Note [What prevents a constraint from floating]
      
      * TcSimplify.emitResidualConstraints (which emits the residual
        constraints in simplifyInfer) now avoids burying the constraints
        for escaping CoVars inside the implication constraint.
      
      * Since I had do to this stuff with CoVars, I moved the
        fancy footwork about not quantifying over CoVars from
        TcMType.quantifyTyVars to its caller
        TcSimplify.decideQuantifiedTyVars.  I think its other
        callers don't need to worry about all this CoVar stuff.
      
      This turned out to be surprisigly tricky, and took me a solid
      day to get right.  I think the result is reasonably neat, though,
      and well documented with Notes.
      
      (cherry picked from commit f5cf9d1a)
      594879dc
    • Simon Peyton Jones's avatar
      Refactor coercion holes · b586f77b
      Simon Peyton Jones authored
      In fixing Trac #14584 I found that it would be /much/ more
      convenient if a "hole" in a coercion (much like a unification
      variable in a type) acutally had a CoVar associated with it
      rather than just a Unique.  Then I can ask what the free variables
      of a coercion is, and get a set of CoVars including those
      as-yet-un-filled in holes.
      
      Once that is done, it makes no sense to stuff coercion holes
      inside UnivCo.  They were there before so we could know the
      kind and role of a "hole" coercion, but once there is a CoVar
      we can get that info from the CoVar.  So I removed HoleProv
      from UnivCoProvenance and added HoleCo to Coercion.
      
      In summary:
      
      * Add HoleCo to Coercion and remove HoleProv from UnivCoProvanance
      
      * Similarly in IfaceCoercion
      
      * Make CoercionHole have a CoVar in it, not a Unique
      
      * Make tyCoVarsOfCo return the free coercion-hole variables
        as well as the ordinary free CoVars.  Similarly, remember
        to zonk the CoVar in a CoercionHole
      
      We could go further, and remove CoercionHole as a distinct type
      altogther, just collapsing it into HoleCo.  But I have not done
      that yet.
      
      (cherry picked from commit a492af06)
      b586f77b
    • Simon Peyton Jones's avatar
      Check for bogus quantified tyvars in partial type sigs · 87e517c1
      Simon Peyton Jones authored
      This fixes Trac #14479.  Not difficult.
      
      See Note [Quantification and partial signatures] Wrinkle 4,
      in TcSimplify.
      
      (cherry picked from commit 72938f58)
      87e517c1
    • Simon Peyton Jones's avatar
      Fix SigTvs at the kind level · 40a31b38
      Simon Peyton Jones authored
      This patch fixes two bugs in the treatment of SigTvs at the
      kind level:
      
      - We should always generalise them, never default them
        (Trac #14555, #14563)
      
      - We should check if they get unified with each other
        (Trac #11203)
      
      Both are described in TcHsType
         Note [Kind generalisation and SigTvs]
      
      (cherry picked from commit 8361b2c5)
      40a31b38
    • Simon Peyton Jones's avatar
      Refactor kcHsTyVarBndrs · dfe049fd
      Simon Peyton Jones authored
      This refactoring
      
      * Renames kcHsTyVarBndrs to kcLHsQTyVars,
        which is more truthful. It is only used in getInitialKind.
      
      * Pulls out bind_telescope from that function, and calls it
        kcLHsTyVarBndrs, again to reflect its argument
      
      * Uses the new kcLHsTyVarBndrs in kcConDecl, where the old
        function was wild overkill.
      
      There should not be any change in behaviour
      
      (cherry picked from commit de204409)
      dfe049fd
  2. Jan 12, 2018
  3. Jan 08, 2018
    • Ryan Scott's avatar
      Make the Div and Mod type families `infixl 7` · fdfaa56b
      Ryan Scott authored
      Commit fa8035e3 added `Div`
      and `Mod` type families to `GHC.TypeNats`. However, they did not add
      the corresponding fixities! Currently, we have that both `div` and
      `mod` (at the value level) are `infixl 7`, so we should adopt the
      same fixities for the type-level `Div` and `Mod` as well.
      
      Test Plan: It compiles
      
      Reviewers: hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14640
      
      Differential Revision: https://phabricator.haskell.org/D4291
      
      (cherry picked from commit 303106d5)
      fdfaa56b
  4. Jan 04, 2018
    • Ryan Scott's avatar
      Fix #14608 by restoring an unboxed tuple check · ec6af9c4
      Ryan Scott authored
      Commit 714bebff removed
      a check in the bytecode compiler that caught illegal uses of unboxed
      tuples (and now sums) in case alternatives, which causes the program
      in #14608 to panic. This restores the check (using modern,
      levity-polymorphic vocabulary).
      
      Test Plan: make test TEST=T14608
      
      Reviewers: hvr, bgamari, dfeuer, simonpj
      
      Reviewed By: dfeuer, simonpj
      
      Subscribers: simonpj, rwbarton, thomie, carter
      
      GHC Trac Issues: #14608
      
      Differential Revision: https://phabricator.haskell.org/D4276
      
      (cherry picked from commit ecff651f)
      ec6af9c4
    • Tamar Christina's avatar
      Make System.IO.openTempFile thread-safe on Windows · 2fc621df
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      This calls out to the Win32 API `GetTempFileName` to generate
      a temporary file. Using `uUnique = 0` guarantees that the file
      we get back is unique and the file is "reserved" by creating it.
      
      Test Plan:
      ./validate
      
      I can't think of any sensible tests that shouldn't run for a while
      to verify. So the example in #10731 was ran for a while and no
      collisions in new code
      
      Reviewers: hvr, bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, rwbarton, thomie, carter
      
      GHC Trac Issues: #10731
      
      Differential Revision: https://phabricator.haskell.org/D4278
      
      (cherry picked from commit 46287af0)
      2fc621df
  5. Dec 28, 2017
    • Richard Eisenberg's avatar
      Fix #14618 by applying a subst in deeplyInstantiate · 1779e3bf
      Richard Eisenberg authored and Ben Gamari's avatar Ben Gamari committed
      Previously, we were inexplicably not applying an instantiating
      substitution to arguments in non-prenex types. It's amazing this
      has been around for so long! I guess there aren't a lot of non-prenex
      types around.
      
      test case: typecheck/should_fail/T14618
      
      (cherry picked from commit 722a6584)
      1779e3bf
  6. Dec 22, 2017
  7. Dec 21, 2017
  8. Dec 20, 2017
  9. Dec 14, 2017
  10. Dec 11, 2017
    • David Feuer's avatar
      Allow users to ignore optimization changes · 6fd8629d
      David Feuer authored
      * Add a new flag, `-fignore-optim-changes`, allowing them to avoid
        recompilation if the only changes are to the `-O` level or to
        flags controlling optimizations.
      
      * When `-fignore-optim-changes` is *off*, recompile when optimization
        flags (e.g., `-fno-full-laziness`) change. Previously, we ignored
        these unconditionally when deciding whether to recompile a module.
      
      Reviewers: austin, bgamari, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: duog, carter, simonmar, rwbarton, thomie
      
      GHC Trac Issues: #13604
      
      Differential Revision: https://phabricator.haskell.org/D4123
      
      (cherry picked from commit 708ed9ca)
      6fd8629d
    • Ben Gamari's avatar
      rts: Don't default to single capability when profiled · ce8d8c01
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This was presumably a vestige of the days when the profiled RTS couldn't
      run threaded. Fixes #14545.
      
      Test Plan: simonmar
      
      Reviewers: erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14545
      
      Differential Revision: https://phabricator.haskell.org/D4245
      
      (cherry picked from commit 4bfff7a5)
      ce8d8c01
    • Simon Marlow's avatar
      Always use the safe open() call · 56fbfb30
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      open() can sometimes take a long time, for example on NFS or FUSE
      filesystems.  We recently had a case where open() was taking multiple
      seconds to return for a (presumably overloaded) FUSE filesystem, which
      blocked GC and caused severe issues.
      
      Test Plan: validate
      
      Reviewers: niteria, bgamari, nh2, hvr, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13296
      
      Differential Revision: https://phabricator.haskell.org/D4239
      
      (cherry picked from commit cafe9834)
      56fbfb30
    • Ben Gamari's avatar
      Add hadrian as a submodule · 2278c4c7
      Ben Gamari authored
      It will remain a submodule until we are ready to merge Hadrian into the
      tree.
      2278c4c7
    • Ben Gamari's avatar
      Rip out hadrian subtree · 351c460c
      Ben Gamari authored
      Sadly subtrees haven't worked quite as well as we would have liked for
      developers. See Hadrian #440.
      351c460c
    • Ben Gamari's avatar
      Bump version to 8.4 · ee2acdf5
      Ben Gamari authored
      Updates haddock dsubmodule
      ee2acdf5
  11. Dec 04, 2017
    • Ben Gamari's avatar
      Fix ghc_packages · 595f60fd
      Ben Gamari authored
      The LaTeX produced by this previously failed to compile. Changing the first cell
      of the row from an inline to a paragraph fixes this. Then I noticed that the
      table overflowed the page. This is fixed by applying the longtable class.
      595f60fd
    • Ben Gamari's avatar
      template-haskell: Rip out FamFlavour · cfea7450
      Ben Gamari authored
      This was scheduled to happen for 8.2, it looks like it will actually
      happen in 8.4.
      cfea7450
    • David Feuer's avatar
      Make the Con and Con' patterns produce evidence · 1acb922b
      David Feuer authored
      Matching with the `Con` and `Con'` patterns can reveal evidence
      that the type in question is *not* an application. This can help
      the pattern checker.
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: carter, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4139
      1acb922b
  12. Dec 01, 2017
    • David Feuer's avatar
      Cache TypeRep kinds aggressively · bc761ad9
      David Feuer authored
      Cache `TypeRep k` in each `TrApp` or `TrTyCon` constructor of
      `TypeRep (a :: k)`. This makes `typeRepKind` cheap.
      
      With this change, we won't need any special effort to deserialize
      typereps efficiently. The downside, of course, is that we make
      `TypeRep`s slightly larger.
      
      Reviewers: austin, hvr, bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: carter, simonpj, rwbarton, thomie
      
      GHC Trac Issues: #14254
      
      Differential Revision: https://phabricator.haskell.org/D4085
      bc761ad9
    • David Feuer's avatar
      Add trace injection · 12efb230
      David Feuer authored
      Add support for injecting runtime calls to `trace` in `DsM`. This
      allows the desugarer to add compile-time information to a runtime
      trace.
      
      Reviewers: austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: carter, thomie, rwbarton
      
      Differential Revision: https://phabricator.haskell.org/D4162
      12efb230
    • Edward Z. Yang's avatar
      Handle CPP properly in Backpack · e1fb2838
      Edward Z. Yang authored
      
      Summary:
      Previously, we attempted to lookup 'hole' packages for
      include directories; this obviously is not going to work.
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@fb.com>
      
      Test Plan: validate
      
      Reviewers: ekmett, bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14525
      
      Differential Revision: https://phabricator.haskell.org/D4234
      e1fb2838
    • Edward Z. Yang's avatar
      Make use of boot TyThings during typechecking. · 69987720
      Edward Z. Yang authored
      
      Summary:
      Suppose that you are typechecking A.hs, which transitively imports,
      via B.hs, A.hs-boot.  When we poke on B.hs and discover that it
      has a reference to a type from A, what TyThing should we wire
      it up with?  Clearly, if we have already typechecked A, we
      should use the most up-to-date TyThing: the one we freshly
      generated when we typechecked A.  But what if we haven't typechecked
      it yet?
      
      For the longest time, GHC adopted the policy that this was
      *an error condition*; that you MUST NEVER poke on B.hs's reference
      to a thing defined in A.hs until A.hs has gotten around to checking
      this.  However, actually ensuring this is the case has proven
      to be a bug farm.  The problem was especially poignant with
      type family consistency checks, which eagerly happen before
      any typechecking takes place.
      
      This patch takes a different strategy: if we ever try to access
      an entity from A which doesn't exist, we just fall back on the
      definition of A from the hs-boot file.  This means that you may
      end up with a mix of A.hs and A.hs-boot TyThings during the
      course of typechecking.
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@fb.com>
      
      Test Plan: validate
      
      Reviewers: simonpj, bgamari, austin, goldfire
      
      Subscribers: thomie, rwbarton
      
      GHC Trac Issues: #14396
      
      Differential Revision: https://phabricator.haskell.org/D4154
      69987720
Loading