Skip to content
Snippets Groups Projects
  1. Apr 20, 2022
    • Andreas Klebinger's avatar
      Fix a shadowing issue in StgUnarise. · 49bd7584
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      For I assume performance reasons we don't record no-op replacements
      during unarise. This lead to problems with code like this:
      
          f = \(Eta_B0 :: VoidType) x1 x2 ->
             ... let foo = \(Eta_B0 :: LiftedType) -> g x y Eta_B0
                 in ...
      
      Here we would record the outer Eta_B0 as void rep, but would not
      shadow Eta_B0 inside `foo` because this arg is single-rep and so
      doesn't need to replaced. But this means when looking at occurence
      sites we would check the env and assume it's void rep based on the
      entry we made for the (no longer in scope) outer `Eta_B0`.
      
      Fixes #21396 and the ticket has a few more details.
      49bd7584
    • Krzysztof Gogolewski's avatar
      Remove LevityInfo · a5ea65c9
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      Every Id was storing a boolean whether it could be levity-polymorphic.
      This information is no longer needed since representation-checking
      has been moved to the typechecker.
      a5ea65c9
    • Alan Zimmerman's avatar
      Add -dkeep-comments flag to keep comments in the parser · 83c67f76
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      This provides a way to set the Opt_KeepRawTokenStream from the command
      line, allowing exact print annotation users to see exactly what is
      produced for a given parsed file, when used in conjunction with
      -ddump-parsed-ast
      
      Discussed in #19706, but this commit does not close the issue.
      83c67f76
  2. Apr 15, 2022
  3. Apr 14, 2022
  4. Apr 13, 2022
  5. Apr 12, 2022
    • Sebastian Graf's avatar
      Specialise: Check `typeDeterminesValue` before specialising on an interesting dictionary · b06f4f47
      Sebastian Graf authored
      I extracted the checks from `Note [Type determines value]` into its own
      function, so that we share the logic properly. Then I made sure that we
      actually call `typeDeterminesValue` everywhere we check for `interestingDict`.
      b06f4f47
    • Sebastian Graf's avatar
      Specialising through specialised method calls (#19644) · 4d2ee313
      Sebastian Graf authored
      In #19644, we discovered that the ClassOp/DFun rules from
      Note [ClassOp/DFun selection] inhibit transitive specialisation in a scenario
      like
      ```
      class C a where m :: Show b => a -> b -> ...; n :: ...
      instance C Int where m = ... -- $cm :: Show b => Int -> b -> ...
      f :: forall a b. (C a, Show b) => ...
      f $dC $dShow = ... m @a $dC @b $dShow ...
      main = ... f @Int @Bool ...
      ```
      After we specialise `f` for `Int`, we'll see `m @a $dC @b $dShow` in the body of
      `$sf`. But before this patch, Specialise doesn't apply the ClassOp/DFun rule to
      rewrite to a call of the instance method for `C Int`, e.g., `$cm @Bool $dShow`.
      As a result, Specialise couldn't further specialise `$cm` for `Bool`.
      
      There's a better example in `Note [Specialisation modulo dictionary selectors]`.
      
      This patch enables proper Specialisation, as follows:
      
      1. In the App case of `specExpr`, try to apply the CalssOp/DictSel rule on the
         head of the application
      2. Attach an unfolding to freshly-bound dictionary ids such as `$dC` and
         `$dShow` in `bindAuxiliaryDict`
      
      NB: Without (2), (1) would be pointless, because `lookupRule` wouldn't be able
      to look into the RHS of `$dC` to see the DFun.
      
      (2) triggered #21332, because the Specialiser floats around dictionaries without
      accounting for them in the `SpecEnv`'s `InScopeSet`, triggering a panic when
      rewriting dictionary unfoldings.
      
      Fixes #19644 and #21332.
      4d2ee313
    • Sebastian Graf's avatar
      Eta reduction based on evaluation context (#21261) · 0090ad7b
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      I completely rewrote our Notes surrounding eta-reduction. The new entry point is
      `Note [Eta reduction makes sense]`.
      
      Then I went on to extend the Simplifier to maintain an evaluation context in the
      form of a `SubDemand` inside a `SimplCont`. That `SubDemand` is useful for doing
      eta reduction according to `Note [Eta reduction based on evaluation context]`,
      which describes how Demand analysis, Simplifier and `tryEtaReduce` interact to
      facilitate eta reduction in more scenarios.
      
      Thus we fix #21261.
      
      ghc/alloc perf marginally improves (-0.0%). A medium-sized win is when compiling
      T3064 (-3%). It seems that haddock improves by 0.6% to 1.0%, too.
      
      Metric Decrease:
          T3064
      0090ad7b
    • Hécate Kleidukos's avatar
      Document that DuplicateRecordFields doesn't tolerates ambiguous fields · 5440f63e
      Hécate Kleidukos authored and Marge Bot's avatar Marge Bot committed
      Fix #19891
      5440f63e
  6. Apr 09, 2022
    • Vladislav Zavialov's avatar
      Refactor: simplify lexing of the dot · 20eca489
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      Before this patch, the lexer did a truly roundabout thing with the dot:
      
      1. look up the varsym in reservedSymsFM and turn it into ITdot
      2. under OverloadedRecordDot, turn it into ITvarsym
      3. in varsym_(prefix|suffix|...) turn it into ITvarsym, ITdot, or
         ITproj, depending on extensions and whitespace
      
      Turns out, the last step is sufficient to handle the dot correctly.
      This patch removes the first two steps.
      20eca489
    • sheaf's avatar
      Fix missing SymCo in pushCoercionIntoLambda · 5f8d6e65
      sheaf authored and Marge Bot's avatar Marge Bot committed
      There was a missing SymCo in pushCoercionIntoLambda. Currently
      this codepath is only used with rewrite rules, so this bug managed
      to slip by, but trying to use pushCoercionIntoLambda in other contexts
      revealed the bug.
      5f8d6e65
    • Andreas Klebinger's avatar
      Add regression test for #19569 · 47d18b0b
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      47d18b0b
    • Phil Hazelden's avatar
      Update changelog. · 20bbf3ac
      Phil Hazelden authored and Marge Bot's avatar Marge Bot committed
      20bbf3ac
    • Phil Hazelden's avatar
      Add tests for several trace functions. · 8fafacf7
      Phil Hazelden authored and Marge Bot's avatar Marge Bot committed
      8fafacf7
    • Phil Hazelden's avatar
    • Joachim Breitner's avatar
      Drop the app invariant · dcf30da8
      Joachim Breitner authored and Marge Bot's avatar Marge Bot committed
      
      previously, GHC had the "let/app-invariant" which said that the RHS of a
      let or the argument of an application must be of lifted type or ok for
      speculation. We want this on let to freely float them around, and we
      wanted that on app to freely convert between the two (e.g. in
      beta-reduction or inlining).
      
      However, the app invariant meant that simple code didn't stay simple and
      this got in the way of rules matching. By removing the app invariant,
      this thus fixes #20554.
      
      The new invariant is now called "let-can-float invariant", which is
      hopefully easier to guess its meaning correctly.
      
      Dropping the app invariant means that everywhere where we effectively do
      beta-reduction (in the two simplifiers, but also in `exprIsConApp_maybe`
      and other innocent looking places) we now have to check if the argument
      must be evaluated (unlifted and side-effecting), and analyses have to be
      adjusted to the new semantics of `App`.
      
      Also, `LetFloats` in the simplifier can now also carry such non-floating
      bindings.
      
      The fix for DmdAnal, refine by Sebastian, makes functions with unlifted
      arguments strict in these arguments, which changes some signatures.
      
      This causes some extra calls to `exprType` and `exprOkForSpeculation`,
      so some perf benchmarks regress a bit (while others improve).
      
      Metric Decrease:
          T9020
      Metric Increase:
          LargeRecord
          T12545
          T15164
          T16577
          T18223
          T5642
          T9961
      
      Co-authored-by: default avatarSebastian Graf <sebastian.graf@kit.edu>
      dcf30da8
    • Matthew Pickering's avatar
      Bump deepseq to 1.4.7.0 · 27362265
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      Updates deepseq submodule
      
      Fixes #20653
      27362265
    • Matthew Pickering's avatar
      ci: Remove doc-tarball dependency from perf and perf-nofib jobs · 3c48e12a
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      These don't depend on the contents of the tarball so we can run them
      straight after the fedora33 job finishes.
      3c48e12a
    • Matthew Pickering's avatar
      ci: Fix nightly head.hackage pipelines · 4bb00839
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This also needs a corresponding commit to head.hackage, I also made the
      job explicitly depend on the fedora33 job so that it isn't blocked by a
      failing windows job, which causes docs-tarball to fail.
      4bb00839
  7. Apr 08, 2022
    • Simon Peyton Jones's avatar
      Tiny documentation wibble · e58d5eeb
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This commit
         commit 83363c8b
         Author: Simon Peyton Jones <simon.peytonjones@gmail.com>
         Date:   Fri Mar 11 16:55:38 2022 +0000
      
             Use prepareBinding in tryCastWorkerWrapper
      
      refactored completeNonRecX away, but left a Note referring to it.
      This MR fixes that Note.
      e58d5eeb
    • Vladislav Zavialov's avatar
      Disallow (->) as a data constructor name (#16999) · 0736e949
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      The code was misusing isLexCon, which was never meant for validation.
      In fact, its documentation states the following:
      
      	Use these functions to figure what kind of name a 'FastString'
      	represents; these functions do /not/ check that the identifier
      	is valid.
      
      Ha! This sign can't stop me because I can't read.
      
      The fix is to use okConOcc instead. The other checks (isTcOcc or
      isDataOcc) seem superfluous, so I also removed those.
      0736e949
    • Matthew Pickering's avatar
      ci: Replace "always" with "on_success" to stop build jobs running before hadrian-ghci has finished · d4480490
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      See https://docs.gitlab.com/ee/ci/yaml/#when
      
      * always means, always run not matter what
      * on_success means, run if the dependencies have built successfully
      d4480490
    • sheaf's avatar
      Docs: datacon eta-expansion, rep-poly checks · 23f95735
      sheaf authored and Marge Bot's avatar Marge Bot committed
      The existing notes weren't very clear on how the eta-expansion of
      data constructors that occurs in tcInferDataCon/dsConLike interacts
      with the representation polymorphism invariants. So we explain with
      a few more details how we ensure that the representation-polymorphic
      lambdas introduced by tcInferDataCon/dsConLike don't end up causing
      problems, by checking they are properly instantiated and then relying
      on the simple optimiser to perform beta reduction.
      
      A few additional changes:
      
        - ConLikeTc just take type variables instead of binders, as we
          never actually used the binders.
        - Removed the FRRApp constructor of FRROrigin; it was no longer used
          now that we use ExpectedFunTyOrigin.
        - Adds a bit of documentation to the constructors
          of ExpectedFunTyOrigin.
      23f95735
    • Vladislav Zavialov's avatar
      HsUniToken for :: in GADT constructors (#19623) · 3415981c
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      One more step towards the new design of EPA.
      
      Updates the haddock submodule.
      3415981c
    • Andreas Klebinger's avatar
      Add flag -fprof-manual which controls if GHC should honour manual cost centres. · 85f4a3c9
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      This allows disabling of manual control centres in code a user doesn't control like
      libraries.
      
      Fixes #18867
      85f4a3c9
    • Matthew Pickering's avatar
      driver: Introduce HomeModInfoCache abstraction · 6e2c3b7c
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      The HomeModInfoCache is a mutable cache which is updated incrementally
      as the driver completes, this makes it robust to exceptions including
      (SIGINT)
      
      The interface for the cache is described by the `HomeMOdInfoCache` data
      type:
      
      ```
      data HomeModInfoCache = HomeModInfoCache { hmi_clearCache :: IO [HomeModInfo]
                                               , hmi_addToCache :: HomeModInfo -> IO () }
      ```
      
      The first operation clears the cache and returns its contents. This is
      designed so it's harder to end up in situations where the cache is
      retained throughout the execution of upsweep.
      
      The second operation allows a module to be added to the cache.
      
      The one slightly nasty part is in `interpretBuildPlan` where we have to
      be careful to ensure that the cache writes happen:
      
      1. In parralel
      2. Before the executation continues after upsweep.
      
      This requires some simple, localised MVar wrangling.
      
      Fixes #20780
      6e2c3b7c
    • Ben Gamari's avatar
      Merge remote-tracking branch 'origin/master' · 56254e6b
      Ben Gamari authored
      56254e6b
    • Vladislav Zavialov's avatar
      Reject illegal quote mark in data con declarations (#17865) · af300a43
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      * Non-fatal (i.e. recoverable) parse error
      * Checking infix constructors
      * Extended the regression test
      af300a43
    • sheaf's avatar
      Correctly report SrcLoc of redundant constraints · 777365f1
      sheaf authored and Marge Bot's avatar Marge Bot committed
      We were accidentally dropping the source location information in
      certain circumstances when reporting redundant constraints. This patch
      makes sure that we set the TcLclEnv correctly before reporting the
      warning.
      
      Fixes #21315
      777365f1
    • Krzysztof Gogolewski's avatar
      Fixes to 9.4 release notes · c44432db
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      - Mention -Wforall-identifier
      - Improve description of withDict
      - Fix formatting
      c44432db
    • Ben Gamari's avatar
      testsuite: Lint RTS #includes · cb1f31f5
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Verifies two important properties of #includes in the RTS:
      
       * That system headers don't appear inside of a `<BeginPrivate.h>` block
         as this can hide system library symbols, resulting in very
         hard-to-diagnose linker errors
      
       * That no headers precede `Rts.h`, ensuring that __USE_MINGW_ANSI_STDIO
         is set correctly before system headers are included.
      cb1f31f5
    • Ben Gamari's avatar
      rts: Fix various #include issues · 56f85d62
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This fixes various violations of the newly-added RTS includes linter.
      56f85d62
    • Ben Gamari's avatar
      rts: Move __USE_MINGW_ANSI_STDIO definition to PosixSource.h · c32c4db6
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      It's easier to ensure that this is included first than Rts.h
      c32c4db6
    • sheaf's avatar
      Add test for #21338 · 64ac20a7
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This no-skolem-info bug was fixed by the no-skolem-info patch
      that will be part of GHC 9.4. This patch adds a regression test for
      the issue reported in issue #21338.
      
      Fixes #21338.
      64ac20a7
    • Simon Jakobi's avatar
      Improve seq[D]VarSet · b2dbcc7d
      Simon Jakobi authored and Marge Bot's avatar Marge Bot committed
      Previously, the use of size[D]VarSet would involve a traversal of the
      entire underlying IntMap. Since IntMaps are already spine-strict,
      this is unnecessary.
      b2dbcc7d
  8. Apr 07, 2022
Loading