Skip to content
Snippets Groups Projects
  1. Jan 18, 2018
    • Ryan Scott's avatar
      Fix #14681 and #14682 with precision-aimed parentheses · 33e3b3eb
      Ryan Scott authored
      It turns out that `Convert` was recklessly leaving off
      parentheses in two places:
      
      * Negative numeric literals
      * Patterns in lambda position
      
      This patch fixes it by adding three new functions, `isCompoundHsLit`,
      `isCompoundHsOverLit`, and `isCompoundPat`, and using them in the
      right places in `Convert`. While I was in town, I also sprinkled
      `isCompoundPat` among some `Pat`-constructing functions in `HsUtils`
      to help avoid the likelihood of this problem happening in other
      places. One of these places is in `TcGenDeriv`, and sprinkling
      `isCompountPat` there fixes #14682
      
      Test Plan: make test TEST="T14681 T14682"
      
      Reviewers: alanz, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14681, #14682
      
      Differential Revision: https://phabricator.haskell.org/D4323
      
      (cherry picked from commit 575c009d)
    • Andreas Klebinger's avatar
      Remove executable filename check on windows · 4eccca7e
      Andreas Klebinger authored
      On Windows GHC enforces currently that the real executable is named
      ghc.exe/ghc-stage[123].exe.
      
      I don't see a good reason why this is neccessary.
      This patch removes this restriction and fixes #14652
      
      Test Plan: ci
      
      Reviewers: bgamari, Phyx
      
      Reviewed By: Phyx
      
      Subscribers: Phyx, rwbarton, thomie, carter
      
      GHC Trac Issues: #14652
      
      Differential Revision: https://phabricator.haskell.org/D4296
      
      (cherry picked from commit 1bf70b20)
      4eccca7e
    • Tao He's avatar
      Fix hash in haddock of ghc-prim. · f28645c0
      Tao He authored
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14653
      
      Differential Revision: https://phabricator.haskell.org/D4305
      
      (cherry picked from commit 2feed118)
      f28645c0
    • Matthías Páll Gissurarson's avatar
      Inform hole substitutions of typeclass constraints (fixes #14273). · 96b52e63
      Matthías Páll Gissurarson authored and Ben Gamari's avatar Ben Gamari committed
      This implements SPJ's suggestion on the ticket (#14273). We find the
      relevant constraints (ones that whose free unification variables are all
      mentioned in the type of the hole), and then clone the free unification
      variables of the hole and the relevant constraints. We then add a
      subsumption constraints and run the simplifier, and then check whether
      all the constraints were solved.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, rwbarton, thomie, carter
      
      GHC Trac Issues: #14273
      
      Differential Revision: https://phabricator.haskell.org/D4315
      
      (cherry picked from commit 1e14fd3e)
      96b52e63
    • Ryan Scott's avatar
      Improve treatment of sectioned holes · da83722c
      Ryan Scott authored
      Previously, GHC was pretty-printing left-section holes
      incorrectly and not parsing right-sectioned holes at all. This patch
      fixes both problems.
      
      Test Plan: make test TEST=T14590
      
      Reviewers: bgamari, simonpj
      
      Reviewed By: simonpj
      
      Subscribers: simonpj, rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #14590
      
      Differential Revision: https://phabricator.haskell.org/D4273
      
      (cherry picked from commit 4d41e921)
      da83722c
  2. Jan 17, 2018
  3. Jan 15, 2018
    • John Ericson's avatar
      configure: Various cleanups · be8d6675
      John Ericson authored and Ben Gamari's avatar Ben Gamari committed
      Substitute RanlibCmd for consistency, and other configure cleanups that
      should have no effect
      
      The other commands are so substituted. Maybe we don't need ranlib at
      all, and the configure snippet can be removed all together, but that
      can always be done later.
      
      Reviewers: bgamari, hvr, angerman
      
      Reviewed By: bgamari, angerman
      
      Subscribers: rwbarton, thomie, erikd, carter
      
      Differential Revision: https://phabricator.haskell.org/D4286
      
      (cherry picked from commit 8de89305)
      be8d6675
    • Ryan Scott's avatar
      Parenthesize forall-type args in cvtTypeKind · b92fb515
      Ryan Scott authored
      Trac #14646 happened because we forgot to parenthesize `forall` types to
      the left of an arrow. This simple patch fixes that.
      
      Test Plan: make test TEST=T14646
      
      Reviewers: alanz, goldfire, bgamari
      
      Reviewed By: alanz
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14646
      
      Differential Revision: https://phabricator.haskell.org/D4298
      
      (cherry picked from commit f380115c)
      b92fb515
    • Simon Peyton Jones's avatar
      Fix join-point decision · 20afdaa7
      Simon Peyton Jones authored
      This patch moves the "ok_unfolding" test
         from  CoreOpt.joinPointBinding_maybe
         to    OccurAnal.decideJoinPointHood
      
      Previously the occurrence analyser was deciding to make
      something a join point, but the simplifier was reversing
      that decision, which made the decision about /other/ bindings
      invalid.
      
      Fixes Trac #14650.
      
      (cherry picked from commit 66ff794f)
      20afdaa7
  4. Jan 14, 2018
    • Simon Peyton Jones's avatar
      Simplify HsPatSynDetails · 7c69f111
      Simon Peyton Jones authored
      This is a pure refactoring.  Use HsConDetails to implement
      HsPatSynDetails, instead of defining a whole new data type.
      Less code, fewer types, all good.
      
      (cherry picked from commit 584cbd4a)
      7c69f111
    • Simon Peyton Jones's avatar
      Fix previous patch · 85535937
      Simon Peyton Jones authored
      This recent patch
          commit 1577908f
          Author: Simon Peyton Jones <simonpj@microsoft.com>
          Date:   Tue Jan 9 16:20:46 2018 +0000
      
              Fix two more bugs in partial signatures
      
              These were shown up by Trac #14643
      
      failed validation for typecheck/should_run/T10846
      (Reported in Trac #14658.)
      
      The fix is simple.
      
      (cherry picked from commit f3f90a07)
      85535937
    • Simon Peyton Jones's avatar
      Fix two more bugs in partial signatures · 3d2664e4
      Simon Peyton Jones authored
      These were shown up by Trac #14643
      
      Bug 1: if we had a single partial signature for
      two functions
         f, g :: forall a. _ -> a
      then we made two different SigTvs but with the sane Name.
      This was jolly confusing and ultimately led to deeply bogus
      results with Any's appearing in the resulting program. Yikes.
      Fix: clone the quantified variables in TcSigs.tcInstSig (as
      indeed its name suggests).
      
      Bug 2: we were not eliminating duplicate/superclass constraints
      in the partial signatures of a mutually recursive group.
      
      Easy to fix: we are already doing dup/superclass elim in
      TcSimplify.decideQuantification.  So we move the partial-sig
      constraints there too.
      
      (cherry picked from commit 1577908f)
      3d2664e4
    • 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
  5. Jan 12, 2018
  6. 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
  7. 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
  8. 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
  9. Dec 22, 2017
  10. Dec 21, 2017
  11. Dec 20, 2017
  12. Dec 14, 2017
  13. 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
Loading