Skip to content
Snippets Groups Projects
  1. Mar 03, 2021
    • Sylvain Henry's avatar
      Fix array and cleanup conversion primops (#19026) · d8dc0f96
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      The first change makes the array ones use the proper fixed-size types,
      which also means that just like before, they can be used without
      explicit conversions with the boxed sized types. (Before, it was Int# /
      Word# on both sides, now it is fixed sized on both sides).
      
      For the second change, don't use "extend" or "narrow" in some of the
      user-facing primops names for conversions.
      
        - Names like `narrowInt32#` are misleading when `Int` is 32-bits.
      
        - Names like `extendInt64#` are flat-out wrong when `Int is
          32-bits.
      
        - `narrow{Int,Word}<N>#` however map a type to itself, and so don't
          suffer from this problem. They are left as-is.
      
      These changes are batched together because Alex happend to use the array
      ops. We can only use released versions of Alex at this time, sadly, and
      I don't want to have to have a release thatwon't work for the final GHC
      9.2. So by combining these we get all the changes for Alex done at once.
      
      Bump hackage state in a few places, and also make that workflow slightly
      easier for the future.
      
      Bump minimum Alex version
      
      Bump Cabal, array, bytestring, containers, text, and binary submodules
      d8dc0f96
    • Daniel Winograd-Cort's avatar
      Add cmpNat, cmpSymbol, and cmpChar · eea96042
      Daniel Winograd-Cort authored and Marge Bot's avatar Marge Bot committed
      Add Data.Type.Ord
      Add and update tests
      Metric Increase:
          MultiLayerModules
      eea96042
    • Sebastian Graf's avatar
      Fix typo in docs [skip ci] · 59e95bdf
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      59e95bdf
  2. Mar 02, 2021
  3. Mar 01, 2021
    • Sebastian Graf's avatar
      Pmc: Implement `considerAccessible` (#18610) · e571eda7
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Consider (`T18610`):
      ```hs
        f :: Bool -> Int
        f x = case (x, x) of
          (True,  True)  -> 1
          (False, False) -> 2
          (True,  False) -> 3 -- Warning: Redundant
      ```
      The third clause will be flagged as redundant. Nevertheless, the
      programmer might intend to keep the clause in order to avoid bitrot.
      
      After this patch, the programmer can write
      ```hs
        g :: Bool -> Int
        g x = case (x, x) of
          (True,  True)  -> 1
          (False, False) -> 2
          (True,  False) | GHC.Exts.considerAccessible -> 3 -- No warning
      ```
      And won't be bothered any longer. See also `Note [considerAccessible]`
      and the updated entries in the user's guide.
      
      Fixes #18610 and #19228.
      e571eda7
    • Sebastian Graf's avatar
      Fix a bug causing loss of sharing in `UniqSDFM` · 51828c6d
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      While fixing #18610, I noticed that
      ```hs
      f :: Bool -> Int
      f x = case (x, x) of
        (True,  True)  -> 1
        (False, False) -> 2
      ```
      was *not* detected as exhaustive. I tracked it down to `equateUSDFM`,
      where upon merging equality classes of `x` and `y`, we failed to atually
      indirect the *representative* `x'` of the equality class of `x` to the
      representative `y'` of `y`.
      
      The fixed code is much more naturally and would I should have written in
      the first place. I can confirm that the above example now is detected as
      exhaustive. The commit that fixes #18610 comes directly after and it has
      `f` above as a regression test, so I saw no need to open a ticket or
      commit a separate regression test.
      51828c6d
    • Alan Zimmerman's avatar
      Wrap LHsContext in Maybe in the GHC AST · ce85cffc
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      If the context is missing it is captured as Nothing, rather than
      putting a noLoc in the ParsedSource.
      
      Updates haddock submodule
      ce85cffc
    • Simon Peyton Jones's avatar
      Fix terrible occurrence-analysis bug · 6429943b
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      Ticket #19360 showed up a terrible bug in the occurrence analyser,
      in a situation like this
      
         Rec { f = g
             ; g = ..f...
               {-# RULE g .. = ...f... #-}  }
      
      Then f was postInlineUnconditionally, but not in the RULE (which
      is simplified first), so we had a RULE mentioning a variable that
      was not in scope.
      
      This led me to review (again) the subtle loop-breaker stuff in the
      occurrence analyser. The actual changes are few, and are largely
      simplifications.  I did a /lot/ of comment re-organising though.
      
      There was an unexpected amount of fallout.
      
      * Validation failed when compiling the stage2 compiler with profiling
        on. That turned to tickle a second latent bug in the same OccAnal
        code (at least I think it was always there), which led me to
        simplify still further; see Note [inl_fvs] in GHC.Core.Opt.OccurAnal.
      
      * But that in turn let me to some strange behaviour in CSE when ticks
        are in the picture, which I duly fixed.  See Note [Dealing with ticks]
        in GHC.Core.Opt.CSE.
      
      * Then I got an ASSERT failure in CoreToStg, which again seems to be
        a latent bug.  See Note [Ticks in applications] in GHC.CoreToStg
      
      * I also made one unforced change: I now simplify the RHS of a RULE in
        the same way as the RHS of a stable unfolding. This can allow a
        trivial binding to disappear sooner than otherwise, and I don't
        think it has any downsides.  The change is in
        GHC.Core.Opt.Simplify.simplRules.
      6429943b
    • Krzysztof Gogolewski's avatar
      Infer multiplicity in case expressions · 3b79e8b8
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      This is a first step towards #18738.
      3b79e8b8
    • Simon Peyton Jones's avatar
      Unify result type earlier to improve error messages · 7730713b
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      Ticket #19364 helpfully points out that we do not currently take
      advantage of pushing the result type of an application into the
      arguments.  This makes error messages notably less good.
      
      The fix is rather easy: move the result-type unification step earlier.
      It's even a bit more efficient; in the the checking case we now
      do one less zonk.
      
      See Note [Unify with expected type before typechecking arguments]
      in GHC.Tc.Gen.App
      
      This change generally improves error messages, but it made one worse:
      typecheck/should_fail/T16204c. That led me to the realisation that
      a good error can be replaced by a less-good one, which provoked
      me to change GHC.Tc.Solver.Interact.inertsCanDischarge.  It's
      explained in the new Note [Combining equalities]
      
      One other refactoring: I discovered that KindEqOrigin didn't need a
      Maybe in its type -- a nice simplification.
      7730713b
    • Sebastian Graf's avatar
      Widen acceptance window of `MultiLayerModules` (#19293) [skip ci] · 8c425bd8
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      As #19293 realises, this one keeps on flip flopping by 2.5%
      depending on how many modules there are within the GHC package.
      
      We should revert this once we figured out how to fix what's going on.
      8c425bd8
    • Ben Gamari's avatar
      testsuite: Accept allocations change in T10421 · f512f9e2
      Ben Gamari authored
      Metric Decrease:
          T10421
      f512f9e2
    • Ben Gamari's avatar
      rts/eventlog: Flush MainCapability buffer in non-threaded RTS · e18c430d
      Ben Gamari authored
      Previously flushEventLog failed to flush anything but the global event
      buffer in the non-threaded RTS.
      
      Fixes #19436.
      e18c430d
    • Ben Gamari's avatar
      rts/eventlog: Ensure that all capability buffers are flushed · 2628d61f
      Ben Gamari authored
      The previous approach performed the flush in yieldCapability. However,
      as pointed out in #19435, this is wrong as it idle capabilities will not
      go through this codepath.
      
      The fix is simple: undo the optimisation, flushing in `flushEventLog` by
      calling `flushAllCapsEventsBufs` after acquiring all capabilities.
      
      Fixes #19435.
      2628d61f
  4. Feb 28, 2021
    • Sebastian Graf's avatar
      Reduce code bloat in `Ord Literal` instance (#19443) · 915daf51
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Reduce code bloat by replacing a call to `(==)` (which is defined in
      terms of `compare`) and to `compare` by a single call to `compare`,
      utilising the `Semigroup Ordering` instance.
      
      The compiler was eliminate the code bloat before, so this is a rather
      cosmetical improvement.
      
      Fixes #19443.
      915daf51
    • Sebastian Graf's avatar
      Make `Ord Literal` deterministic (#19438) · 2454bb10
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Previously, non-determinism arising from a use of `uniqCompareFS` in
      `cmpLit` potentially crept into `CoreMap`, which we expect to behave
      deterministically.
      
      So we simply use `lexicalCompareFS` now.
      
      Fixes #19438.
      2454bb10
    • Sylvain Henry's avatar
      Make known names simple ConApps (#19386) · 72c0e078
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      While fixing #17336 we noticed that code like this:
      
       = if | tc == intTyConName     -> ...
            | tc == int8TyConName    -> ...
            | tc == int16TyConName   -> ...
            | tc == int32TyConName   -> ...
            | tc == int64TyConName   -> ...
            | tc == wordTyConName    -> ...
            | tc == word8TyConName   -> ...
            | tc == word16TyConName  -> ...
            | tc == word32TyConName  -> ...
            | tc == word64TyConName  -> ...
            | tc == naturalTyConName -> ...
      
      was not transformed into a single case expression on the Name's unique
      as I would have expected but as a linear search. Bindings for known
      names are not simple constructor applications because of their strict
      `n_occ :: !OccName` field that needs to allocate a `FastString`: this
      field needs to be forced before using the `n_unique` field.
      
      This patch partially reverses ccaf7b66 by
      making `n_occ` lazy and by ensuring that helper functions used to
      declare known names are fully inlined. The code above is then
      optimised as expected.
      
                                               Baseline
                           Test    Metric         value     New value Change
      ---------------------------------------------------------------------------
       ManyAlternatives(normal) ghc/alloc   822810880.0   822104032.0  -0.1%
       ManyConstructors(normal) ghc/alloc  4551734924.0  4480621808.0  -1.6%
      MultiLayerModules(normal) ghc/alloc  6029108292.0  6016024464.0  -0.2%
               Naperian(optasm) ghc/alloc    57396600.0    56826184.0  -1.0%
              PmSeriesG(normal) ghc/alloc    55666656.0    54521840.0  -2.1%
              PmSeriesS(normal) ghc/alloc    70204344.0    69047328.0  -1.6%
              PmSeriesT(normal) ghc/alloc   102273172.0   101070016.0  -1.2%
              PmSeriesV(normal) ghc/alloc    69157156.0    68002176.0  -1.7%
                 T10421(normal) ghc/alloc   129875476.0   128881544.0  -0.8%
                T10421a(normal) ghc/alloc    92031552.0    90982800.0  -1.1%
                 T10547(normal) ghc/alloc    34399800.0    33016760.0  -4.0% GOOD
                 T10858(normal) ghc/alloc   208316964.0   207318616.0  -0.5%
                 T11195(normal) ghc/alloc   304100548.0   302797040.0  -0.4%
                 T11276(normal) ghc/alloc   140586764.0   139469832.0  -0.8%
                T11303b(normal) ghc/alloc    52118960.0    51120248.0  -1.9%
                 T11374(normal) ghc/alloc   241325868.0   240692752.0  -0.3%
                 T11822(normal) ghc/alloc   150612036.0   149582736.0  -0.7%
                 T12150(optasm) ghc/alloc    92738452.0    91897224.0  -0.9%
                 T12227(normal) ghc/alloc   494236296.0   493086728.0  -0.2%
                 T12234(optasm) ghc/alloc    66786816.0    65966096.0  -1.2%
                 T12425(optasm) ghc/alloc   112396704.0   111471016.0  -0.8%
                 T12545(normal) ghc/alloc  1832733768.0  1828021072.0  -0.3%
                 T12707(normal) ghc/alloc  1054991144.0  1053359696.0  -0.2%
                 T13035(normal) ghc/alloc   116173180.0   115112072.0  -0.9%
                 T13056(optasm) ghc/alloc   391749192.0   390687864.0  -0.3%
                 T13253(normal) ghc/alloc   382785700.0   381550592.0  -0.3%
             T13253-spj(normal) ghc/alloc   168806064.0   167987192.0  -0.5%
                 T13379(normal) ghc/alloc   403890296.0   402447920.0  -0.4%
                 T13701(normal) ghc/alloc  2542828108.0  2534392736.0  -0.3%
                 T13719(normal) ghc/alloc  4666717708.0  4659489416.0  -0.2%
                   T14052(ghci) ghc/alloc  2181268580.0  2175320640.0  -0.3%
                 T14683(normal) ghc/alloc  3094166824.0  3094524216.0  +0.0%
                 T14697(normal) ghc/alloc   376323432.0   374024184.0  -0.6%
                 T15164(normal) ghc/alloc  1896324828.0  1893236528.0  -0.2%
                 T15630(normal) ghc/alloc   198932800.0   197783656.0  -0.6%
                 T16190(normal) ghc/alloc   288186840.0   287250024.0  -0.3%
                 T16577(normal) ghc/alloc  8324100940.0  8321580600.0  -0.0%
                 T17096(normal) ghc/alloc   318264420.0   316961792.0  -0.4%
                 T17516(normal) ghc/alloc  1332680768.0  1331635504.0  -0.1%
                 T17836(normal) ghc/alloc  1296308168.0  1291098504.0  -0.4%
                T17836b(normal) ghc/alloc    62008340.0    60745256.0  -2.0%
                 T17977(normal) ghc/alloc    52954564.0    51890248.0  -2.0%
                T17977b(normal) ghc/alloc    47824016.0    46683936.0  -2.4%
                 T18140(normal) ghc/alloc   117408932.0   116353672.0  -0.9%
                 T18223(normal) ghc/alloc  5603767896.0  5602037104.0  -0.0%
                 T18282(normal) ghc/alloc   166456808.0   165396320.0  -0.6%
                 T18304(normal) ghc/alloc   103694052.0   103513136.0  -0.2%
                 T18478(normal) ghc/alloc   816819336.0   814459560.0  -0.3%
                T18698a(normal) ghc/alloc   438652404.0   437041784.0  -0.4%
                T18698b(normal) ghc/alloc   529448324.0   527666608.0  -0.3%
                 T18923(normal) ghc/alloc    78360824.0    77315560.0  -1.3%
                  T1969(normal) ghc/alloc   854223208.0   851303488.0  -0.3%
                  T3064(normal) ghc/alloc   200655808.0   199368872.0  -0.6%
                  T3294(normal) ghc/alloc  1791121792.0  1790033888.0  -0.1%
                  T4801(normal) ghc/alloc   343749816.0   341760680.0  -0.6%
                  T5030(normal) ghc/alloc   377520872.0   376492360.0  -0.3%
                T5321FD(normal) ghc/alloc   312680408.0   311618536.0  -0.3%
               T5321Fun(normal) ghc/alloc   355635656.0   354536264.0  -0.3%
                  T5631(normal) ghc/alloc   629667068.0   629562192.0  -0.0%
                  T5642(normal) ghc/alloc   540913864.0   539569952.0  -0.2%
                  T5837(normal) ghc/alloc    43183652.0    42177928.0  -2.3%
                  T6048(optasm) ghc/alloc    96395616.0    95397032.0  -1.0%
                   T783(normal) ghc/alloc   427778908.0   426307760.0  -0.3%
                  T9020(optasm) ghc/alloc   279523960.0   277010040.0  -0.9%
                  T9233(normal) ghc/alloc   966717488.0   964594096.0  -0.2%
                  T9630(normal) ghc/alloc  1585228636.0  1581428672.0  -0.2%
                  T9675(optasm) ghc/alloc   594817892.0   591703040.0  -0.5%
                 T9872a(normal) ghc/alloc  2216955420.0  2215648024.0  -0.1%
                 T9872b(normal) ghc/alloc  2747814924.0  2746515472.0  -0.0%
                 T9872c(normal) ghc/alloc  2271878772.0  2270554344.0  -0.1%
                 T9872d(normal) ghc/alloc   623661168.0   621434064.0  -0.4%
                  T9961(normal) ghc/alloc   409059124.0   406811120.0  -0.5%
                  WWRec(normal) ghc/alloc   940563924.0   938008112.0  -0.3%
                 hie002(normal) ghc/alloc  9801941116.0  9787675736.0  -0.1%
             parsing001(normal) ghc/alloc   494756632.0   493828512.0  -0.2%
      
      Metric Decrease:
          T10547
          T13035
          T12425
      72c0e078
    • Daniel Gröber (dxld)'s avatar
      d262edad
    • Daniel Gröber (dxld)'s avatar
      CODEOWNERS: Use sections to allow multiple matching entries · 0a85502b
      Daniel Gröber (dxld) authored and Marge Bot's avatar Marge Bot committed
      The CODEOWNERS documentation has this to say on the current matching
      behaviour:
      
      > The path definition order is significant: the last pattern matching a
      > given path is used to find the code owners.
      
      Take this as an example:
      
          /rts/        bgamari [...]
          /rts/win32/  Phyx
      
      (I'm omitting the '@' so as to not notification spam everyone)
      
      This means a change in a file under win23 would only have Phyx but not
      bgamari as approver. I don't think that's the behaviour we want.
      
      Using "sections" we can get additive behaviour instead, from the docs:
      
      > Additionally, the usual guidance that only the last pattern matching the
      > file is applied is expanded such that the last pattern matching for each
      > section is applied.
      
          [RTS]
          /rts/        bgamari [...]
      
          [WinIO]
          /rts/win32/  Phyx
      
      So now since those entries are in different sections both would be added to
      the approvers list.
      
      The sections feature was introduced in Gitlab 13.2, see "Version history"
      on [1] we're currently running 18.8 on gitlab.haskell.org, see [2].
      
      [1]: https://docs.gitlab.com/13.8/ee/user/project/code_owners.html#code-owners-sections
      [2]: https://gitlab.haskell.org/help
      0a85502b
    • Sebastian Graf's avatar
      CPR analysis: Use CPR of scrutinee for Case Binder CPR (#19232) · df2eca94
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      For years we have lived in a supposedly sweet spot that gave case
      binders the CPR property, unconditionally. Which is an optimistic hack
      that is now described in `Historical Note [Optimistic case binder CPR]`.
      
      In #19232 the concern was raised that this might do more harm than good
      and that might be better off simply by taking the CPR property of the
      scrutinee for the CPR type of the case binder. And indeed that's what we
      do now.
      
      Since `Note [CPR in a DataAlt case alternative]` is now only about field
      binders, I renamed and garbage collected it into
      `Note [Optimistic field binder CPR]`.
      
      NoFib approves:
      ```
      NoFib Results
      
      --------------------------------------------------------------------------------
              Program         Allocs    Instrs
      --------------------------------------------------------------------------------
                 anna          +0.1%     +0.1%
             nucleic2          -1.2%     -0.6%
                sched           0.0%     +0.9%
            transform          -0.0%     -0.1%
      --------------------------------------------------------------------------------
                  Min          -1.2%     -0.6%
                  Max          +0.1%     +0.9%
       Geometric Mean          -0.0%     +0.0%
      ```
      
      Fixes #19232.
      df2eca94
    • Sebastian Graf's avatar
      Mark divModInt and friends as INLINE (#19267) · c3ff35bb
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      So that we don't get a silly worker `$wdivModInt` and risk inlining
      `divModInt#` into `divModInt` or `$wdivModInt`, making both unlikely to
      inline at call sites.
      
      Fixes #19267.
      
      There's a spurious metric decrease (was an *increase*) in T12545. That
      seems entirely due to shifts in Unique distribution (+5% more
      `IntMap.$winsert` calls). The inappropriateness of the acceptance window
      is tracked in #19414.
      
      Metric Decrease:
          T12545
      Metric Increase:
          T12545
      c3ff35bb
    • Matthew Pickering's avatar
      Fix two places where TcGblEnv was retained · 035d983d
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      Found with ghc-debug on the ManyConstructors test
      035d983d
    • Sebastian Graf's avatar
      Widen acceptance window of T12545 (#19414) · 856929a5
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      This test flip-flops by +-1% in arbitrary changes in CI.
      While playing around with `-dunique-increment`, I could reproduce
      variations of 3% in compiler allocations, so I set the acceptance window
      accordingly.
      
      Fixes #19414.
      856929a5
    • Alan Zimmerman's avatar
      Add some utility functions to GHC.Types.SrcLoc · 980151aa
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      pprUserSpan, isZeroWidthSpan, pprLocated, combineRealSrcSpans
      980151aa
    • Sylvain Henry's avatar
      configure: avoid empty lines in AC_CONFIG_FILES · 0f2891f0
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Should fix failures on Windows:
      
        configure.ac:1511: error: `
        ' is already registered with AC_CONFIG_FILES.
      0f2891f0
    • Ben Gamari's avatar
      users guide: Update mathjax CDN URL · a3473323
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Fixes #19423.
      
      [skip ci]
      a3473323
    • Krzysztof Gogolewski's avatar
      Fix assertion error with linear types, #19400 · b8d40af1
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      The previous code using TyCoMapper could promote the same metavar twice.
      Use a set instead.
      b8d40af1
    • Ben Gamari's avatar
      Rewrite.split: Fix reboxing · 382cd3b0
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      As noted in #19102, we would previously ended up reboxing the tuple
      result of `split`'s worker and then immediately take apart the boxed
      tuple to again unpack it into an unboxed result.
      
      Fixes #19102.
      382cd3b0
    • Ben Gamari's avatar
      GHC.Tc.Solver.Rewrite: oneShot-ify · 30500a4f
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Following the example of Note [The one-shot state monad trick].
      c.f. #18202.
      30500a4f
    • Ben Gamari's avatar
      TcS: oneShot-ify · 5680f8d4
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Following the example of Note [The one-shot state monad trick].
      c.f. #18202.
      
      Metric Decrease:
          T17836
          T3064
          T5321FD
          T9872a
          T9872b
          T9872c
          T9872d
      5680f8d4
  5. Feb 27, 2021
Loading