Skip to content
Snippets Groups Projects
  1. Jun 26, 2018
    • Simon Peyton Jones's avatar
      Fix TcLevel manipulation in TcDerivInfer.simplifyDeriv · 261dd83c
      Simon Peyton Jones authored
      The level numbers we were getting simply didn't obey the
      invariant (ImplicInv) in TcType
         Note [TcLevel and untouchable type variables]
      
      That leads to chaos. Easy to fix.  I improved the documentation.
      
      I also added an assertion in TcSimplify that checks that
      level numbers go up by 1 as we dive inside implications, so
      that we catch the problem at source rather than than through
      its obscure consequences.
      
      That in turn showed up that TcRules was also generating
      constraints that didn't obey (ImplicInv), so I fixed that too.
      I have no idea what consequences were lurking behing that
      bug, but anyway now it's fixed.  Hooray.
      261dd83c
    • Alan Zimmerman's avatar
      API Annotations when parsing typapp · e53c113d
      Alan Zimmerman authored
      Make sure the original annotations are still accessible for a promoted
      type.
      
      Closes #15303
      e53c113d
  2. Jun 25, 2018
    • Simon Peyton Jones's avatar
      Record some notes about "innocuous" transformations · 1c2c2d3d
      Simon Peyton Jones authored
      I wondered if some transformations (ticks) might be "innocuous",
      in the sense that they do not unlock a later transformation that
      does not occur in the same pass.  If so, we could refrain from
      bumping the overall tick-count for such innocuous transformations,
      and perhaps terminate the simplifier one pass earlier.
      
      BUt alas I found that virtually nothing was innocuous!  This
      commit just adds a Note to record what I learned, in case
      anyone wants to try again.
      1c2c2d3d
    • Simon Peyton Jones's avatar
      Remove unused BottomFound from Tick · cea409a3
      Simon Peyton Jones authored
      cea409a3
    • Simon Peyton Jones's avatar
      More misc comments · b4d54590
      Simon Peyton Jones authored
      ... plus, reorder equations in toIfaceVar to improve
      legibility.  No change in behaviour.
      b4d54590
    • Simon Peyton Jones's avatar
      Coments and debug tracing only · 577399c0
      Simon Peyton Jones authored
      See Trac #15205
      577399c0
    • Simon Peyton Jones's avatar
      Refactor the kind-checking of tyvar binders · 9fc40c73
      Simon Peyton Jones authored
      The refactoring here is driven by the ghastly mess described in
      comment:24 of Trac #1520.  The overall goal is to simplify the
      kind-checking of typev-variable binders, and in particular to narrow
      the use of the "in-scope tyvar binder" stuff,
      which is needed only for associated types: see the new
      Note [Kind-checking tyvar binders for associated types] in TcHsType.
      
      Now
      
      * The "in-scope tyvar binder" stuff is done only in
           - kcLHsQTyVars, which is used for the LHsQTyVars of a
             data/newtype, or type family declaration.
      
           - tcFamTyPats, which is used for associated family instances;
             it now calls tcImplicitQTKBndrs, which in turn usese
             newFlexiKindedQTyVar
      
      * tcExpicitTKBndrs (which is used only for function signatures,
        data con signatures, pattern synonym signatures, and expression
        type signatures) now does not go via the "in-scope tyvar binder"
        stuff at all.
      
      While I'm still not happy with all this code, the code is generally
      simpler, and I think this is a useful step forward. It does cure
      the problem too.
      
      (It's hard to trigger the problem in vanilla Haskell code, because
      the renamer would normally use different names for nested binders,
      so I can't offer a test.)
      9fc40c73
    • Simon Peyton Jones's avatar
      Improve tc-tracing a bit · 95324f01
      Simon Peyton Jones authored
      95324f01
    • Simon Peyton Jones's avatar
      Fix error recovery for pattern synonyms · 2896082e
      Simon Peyton Jones authored
      As Trac #15289 showed, we were carrying on after a type error
      in a pattern synonym, and then crashing.  This patch improves
      error handling for pattern synonyms.
      
      I also moved a bit of code from TcBinds into TcPatSyn, which
      helpfully narrows the API.
      2896082e
  3. Jun 24, 2018
  4. Jun 22, 2018
    • Roland Senn's avatar
      Remove -Wamp flag · 33724fc7
      Roland Senn authored
      Test Plan: "ghc -Wamp XXX.hs"  should give "unrecognised warning flag"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #11477
      
      Differential Revision: https://phabricator.haskell.org/D4785
      33724fc7
    • SantiM's avatar
      rts/linker/{SymbolExtras,elf_got}.c: map code as read-only · 67c422ca
      SantiM authored
      protect mmaped addresses from writes after being initially manipulated
      
      Test Plan: ./validate
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: angerman, carlostome, rwbarton, thomie, carter
      
      GHC Trac Issues: #14069
      
      Differential Revision: https://phabricator.haskell.org/D4817
      67c422ca
    • Ben Gamari's avatar
      rts: Abort if timerfd read fails · c7b1e93b
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Currently we belch some output to stderr but fail to abort, resulting in
      a busy loop. Fixes #15292.
      
      Test Plan:
       * Validate
       * try running program under environment without timerfd capabilities;
      ensure we don't busy-loop
      
      Reviewers: simonmar, erikd
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15929
      
      Differential Revision: https://phabricator.haskell.org/D4875
      c7b1e93b
    • Tao He's avatar
      Include ghc-heap and libiserv in the "package" file. · 63d474bb
      Tao He authored
      Previously, the `make clean` (as well as `make dist-clean`) doesn't work
      for ghc-heap and libiserv, due to these two libraries are not presented
      in the "packages" file.
      
      Test Plan: [skip ci]
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4878
      63d474bb
    • Andreas Klebinger's avatar
      Explain why opt-cmm is not dumped by ddump-cmm-verbose. · 391b0caf
      Andreas Klebinger authored
      We just update the docs to reflect the state of affairs.
      
      opt-cmm is run by the NCG backend so not always run.
      ddump-cmm-verbose only dumps passes of the cmm
      pipeline so it's not included there. [skip-ci]
      
      Test Plan: doc change
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4879
      391b0caf
    • Alan Zimmerman's avatar
      TTG for IPBind had wrong extension name · 5f06cf6b
      Alan Zimmerman authored
      The standard[1] for extension naming is to use the XC prefix for the
      internal extension points, rather than for a new constructor.
      
      This is violated for IPBind, having
      
          data IPBind id
            = IPBind
                  (XIPBind id)
                  (Either (Located HsIPName) (IdP id))
                  (LHsExpr id)
            | XCIPBind (XXIPBind id)
      
      Swap the usage of XIPBind and XCIPBind
      
      [1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow#Namingconventions
      
      Closes #15302
      5f06cf6b
    • Simon Peyton Jones's avatar
      122ba98a
    • Simon Peyton Jones's avatar
      Remove unnecessary call to checkReductionDepth · d5459a33
      Simon Peyton Jones authored
      We call checkReductionDepth in chooseInstance, so there's no
      need to call it in selectNextWorkItem too
      d5459a33
    • Simon Peyton Jones's avatar
      Refactor try_solve_fromInstance in shortCutSolver · e0653697
      Simon Peyton Jones authored
      This patch just removes the CtLoc parameter from trySolveFromInstance,
      since it can just as easily (and more uniformly) be gotten from the
      CtEvidence it is trying to solve.
      e0653697
    • Simon Peyton Jones's avatar
      Instances in no-evidence implications · 32eb4199
      Simon Peyton Jones authored
      Trac #15290 showed that it's possible that we might attempt to use a
      quantified constraint to solve an equality in a situation where we
      don't have anywhere to put the evidence bindings.  This made GHC crash.
      
      This patch stops the crash, but still rejects the pogram.  See
      Note [Instances in no-evidence implications] in TcInteract.
      
      Finding this bug revealed another lurking bug:
      
      * An infelicity in the treatment of superclasses -- we were expanding
        them locally at the leaves, rather than at their binding site; see
        (3a) in Note [The superclass story].
      
        As a consequence, TcRnTypes.superclassesMightHelp must look inside
        implications.
      
      In more detail:
      
      * Stop the crash, by making TcInteract.chooseInstance test for
        the no-evidence-bindings case.  In that case we simply don't
        use the instance.  This entailed a slight change to the type
        of chooseInstance.
      
      * Make TcSMonad.getPendingScDicts (now renamed getPendingGivenScs)
        return only Givens from the /current level/; and make
        TcRnTypes.superClassesMightHelp look inside implications.
      
      * Refactor the simpl_loop and superclass-expansion stuff in
        TcSimplify.  The logic is much easier to understand now, and
        has less duplication.
      32eb4199
  5. Jun 21, 2018
  6. Jun 20, 2018
  7. Jun 19, 2018
Loading