Skip to content
Snippets Groups Projects
  1. Jan 22, 2021
    • Sylvain Henry's avatar
      Enhance Data instance generation · 887eb6ec
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Use `mkConstrTag` to explicitly pass the constructor tag instead of
      using `mkConstr` which queries the tag at runtime by querying the index
      of the constructor name (a string) in the list of constructor names.
      
      Perf improvement:
      
          T16577(normal) ghc/alloc 11325573876.0  9249786992.0 -18.3% GOOD
      
      Thanks to @sgraf812 for suggesting an additional list fusion fix during
      reviews.
      
      Metric Decrease:
          T16577
      887eb6ec
    • John Ericson's avatar
      Test constant folding for sized types · 6fbfde95
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      6fbfde95
    • John Ericson's avatar
      Add missing fixed-sized primops and constant folding · 0eaf63b6
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      - `inversePrimOp` is renamed to `semiInversePrimOp` to indicate the
        given primop is only a right inverse, not left inverse (and
        contra-wise for the primop which we are giving rules for). This
        explains why are new usage is not incorrect.
      
      - The removed `subsumedByPrimOp` calls were actually dead as the match
        on ill-typed code. @hsyl20 pointed this out in
        ghc/ghc!4390 (comment 311912),
      
      Metric Decrease:
          T13701
      0eaf63b6
    • John Ericson's avatar
      Cleanup primop constant folding rules in a few ways · faf164db
      John Ericson authored and Marge Bot's avatar Marge Bot committed
       - `leftZero`, `rightZero` and `zeroElem` could all be written using `isZeroLit`
      
       - "modulo 1" rules could be written with `nonOneLit 1 $> Lit zero<type>`
      
      All are due to @hsyl20; thanks!
      faf164db
    • John Ericson's avatar
      C-- shift amount is always native size, not shiftee size · 22d01924
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      This isn't a bug yet, because we only shift native-sized types, but I
      hope to change that.
      22d01924
    • John Ericson's avatar
      Add 32-bit ops to T file I forgot to add before · 2267d42a
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      2267d42a
    • Alfredo Di Napoli's avatar
      Fix tests relying on same-line diagnostic ordering · c36a4f63
      Alfredo Di Napoli authored and Marge Bot's avatar Marge Bot committed
      This commit fixes 19 tests which were failing due to the use of
      `consBag` / `snocBag`, which have been now replaced by `addMessage`.
      This means that now GHC would output things in different order but
      only for /diagnostics on the same line/, so this is just reflecting
      that. The "normal" order of messages is still guaranteed.
      c36a4f63
    • Alfredo Di Napoli's avatar
      Parameterise Messages over e · a64f21e9
      Alfredo Di Napoli authored and Marge Bot's avatar Marge Bot committed
      This commit paves the way to a richer and more structured representation
      of GHC error messages, as per GHC proposal #306. More specifically
      'Messages' from 'GHC.Types.Error' now gains an extra type parameter,
      that we instantiate to 'ErrDoc' for now. Later, this will allow us to
      replace ErrDoc with something more structure (for example messages
      coming from the parser, the typechecker etc).
      a64f21e9
    • Simon Peyton Jones's avatar
      Fix error recovery in solveEqualities · 34950fb8
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      As #19142 showed, with -fdefer-type-errors we were allowing
      compilation to proceed despite a fatal kind error. This patch
      fixes it, as described in the new note in GHC.Tc.Solver,
           Note [Wrapping failing kind equalities]
      
      Also fixes #19158
      
      Also when checking
         default( ty1, ty2, ... )
      
      only consider a possible default (C ty2) if ty2 is kind-compatible
      with C.  Previously we could form kind-incompatible constraints, with
      who knows what kind of chaos resulting.  (Actually, no chaos results,
      but that's only by accident.  It's plain wrong to form the constraint
      (Num Either) for example.)  I just happened to notice
      this during fixing #19142.
      34950fb8
    • Matthew Pickering's avatar
      ghc-heap: Allow more control about decoding CCS fields · a255b4e3
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      We have to be careful not to decode too much, too eagerly, as in
      ghc-debug this will lead to references to memory locations outside of
      the currently copied closure.
      
      Fixes #19038
      a255b4e3
    • Sylvain Henry's avatar
      Factorize and document binder collect functions · 29173f88
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Parameterize collect*Binders functions with a flag indicating if
      evidence binders should be collected.
      
      The related note in GHC.Hs.Utils has been updated.
      
      Bump haddock submodule
      29173f88
    • Sylvain Henry's avatar
      Arrows: collect evidence binders · 01ea56a2
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Evidence binders were not collected by
      GHC.HsToCore.Arrows.collectStmtBinders, hence bindings for dictionaries
      were not taken into account while computing local variables in
      statements. As a consequence we had a transformation similar to this:
      
          data Point a where Point :: RealFloat a => a -> Point a
      
          do
              p -< ...
              returnA -< ... (Point 0)
      
      ===> { Type-checking }
      
          do
              let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
              p -< ...
              returnA -< ... (Point $dRealFloat_xyz 0)
      
      ===> { Arrows HsToCore }
      
          first ...
          >>> arr (\(p, ()) -> case p of ... ->
                  let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
                  in case .. of () -> ())
          >>> \((),()) -> ... (Point $dRealFloat_xyz 0) -- dictionary not in scope
      
      Now evidences are passed in the environment if necessary and we get:
      
      ===> { Arrows HsToCore }
      
          first ...
          >>> arr (\(p, ()) -> case p of ... ->
                  let $dRealFloat_xyz = GHC.Float.$fRealFloatFloat
                  in case .. of () -> $dRealFloat_xyz)
          >>> \(ds,()) ->
                  let $dRealFloat_xyz = ds
                  in ... (Point $dRealFloat_xyz 0) -- dictionary in scope
      
      Note that collectStmtBinders has been copy-pasted from GHC.Hs.Utils.
      This ought to be factorized but Note [Dictionary binders in ConPatOut]
      claims that:
      
          Do *not* gather (a) dictionary and (b) dictionary bindings as
          binders of a ConPatOut pattern.  For most calls it doesn't matter,
          because it's pre-typechecker and there are no ConPatOuts.  But it
          does matter more in the desugarer; for example,
          GHC.HsToCore.Utils.mkSelectorBinds uses collectPatBinders.  In a
          lazy pattern, for example f ~(C x y) = ..., we want to generate
          bindings for x,y but not for dictionaries bound by C.  (The type
          checker ensures they would not be used.)
      
          Desugaring of arrow case expressions needs these bindings (see
          GHC.HsToCore.Arrows and arrowcase1), but SPJ (Jan 2007) says it's
          safer for it to use its own pat-binder-collector:
      
      Accordingly to the last sentence, this patch doesn't make any attempt at
      factorizing both codes.
      
      Fix #18950
      01ea56a2
    • Ben Gamari's avatar
      dataToTag#: Avoid unnecessary entry · b4b2be61
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      When the pointer is already tagged we can avoid entering the closure.
      b4b2be61
    • Ben Gamari's avatar
      Use pointer tag in dataToTag# · 2ed96c68
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      While looking at !2873 I noticed that dataToTag# previously didn't look
      at a pointer's tag to determine its constructor. To be fair, there is a
      bit of a trade-off here: using the pointer tag requires a bit more code
      and another branch. On the other hand, it allows us to eliminate looking
      at the info table in many cases (especially now since we tag large
      constructor families; see #14373).
      2ed96c68
    • Andreas Klebinger's avatar
      When deriving Eq always use tag based comparisons for nullary constructors · 092f0532
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      
      Instead of producing auxiliary con2tag bindings we now rely on
      dataToTag#, eliminating a fair bit of generated code.
      
      Co-Authored-By: default avatarBen Gamari <ben@well-typed.com>
      092f0532
    • Sylvain Henry's avatar
      Fix wrong comment about UnitState · 1ff61314
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      [CI skip]
      1ff61314
  2. Jan 19, 2021
    • Cheng Shao's avatar
      Correct documentation in System.Mem.Weak · 6cfdca9f
      Cheng Shao authored
      [ci skip] Since #13167 is closed, exceptions thrown in finalizers are
      ignored and doesn't affect other finalizers in the same batch. This MR
      updates the documentation in System.Mem.Weak to reflect that.
      6cfdca9f
  3. Jan 18, 2021
  4. Jan 17, 2021
Loading