Skip to content
Snippets Groups Projects
  1. Feb 08, 2024
    • Ben Gamari's avatar
      Move `base` to `ghc-internal` · 44f6557a
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Here we move a good deal of the implementation of `base` into a new
      package, `ghc-internal` such that it can be evolved independently
      from the user-visible interfaces of `base`.
      
      While we want to isolate implementation from interfaces, naturally, we
      would like to avoid turning `base` into a mere set of module re-exports.
      However, this is a non-trivial undertaking for a variety of reasons:
      
       * `base` contains numerous known-key and wired-in things, requiring
         corresponding changes in the compiler
      
       * `base` contains a significant amount of C code and corresponding
         autoconf logic, which is very fragile and difficult to break apart
      
       * `base` has numerous import cycles, which are currently dealt with via
         carefully balanced `hs-boot` files
      
       * We must not break existing users
      
      To accomplish this migration, I tried the following approaches:
      
      * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental
        migration of modules into ghc-internal: this knot is simply too
        intertwined to be easily pulled apart, especially given the rather
        tricky import cycles that it contains)
      
      * [Move-Core]: Moving the "core" connected component of base (roughly
        150 modules) into ghc-internal. While the Haskell side of this seems
        tractable, the C dependencies are very subtle to break apart.
      
      * [Move-Incrementally]:
      
        1. Move all of base into ghc-internal
        2. Examine the module structure and begin moving obvious modules (e.g.
           leaves of the import graph) back into base
        3. Examine the modules remaining in ghc-internal, refactor as necessary
           to facilitate further moves
        4. Go to (2) iterate until the cost/benefit of further moves is
           insufficient to justify continuing
        5. Rename the modules moved into ghc-internal to ensure that they don't
           overlap with those in base
        6. For each module moved into ghc-internal, add a shim module to base
           with the declarations which should be exposed and any requisite
           Haddocks (thus guaranteeing that base will be insulated from changes
           in the export lists of modules in ghc-internal
      
      Here I am using the [Move-Incrementally] approach, which is empirically
      the least painful of the unpleasant options above
      
      Bumps haddock submodule.
      
      Metric Decrease:
          haddock.Cabal
          haddock.base
      Metric Increase:
          MultiComponentModulesRecomp
          T16875
          size_hello_artifact
      44f6557a
    • Matthew Pickering's avatar
      Javascript: Don't filter out rtsDeps list · 20b702b5
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This logic appears to be incorrect as it would drop any dependency which
      was not in a direct dependency of the package being linked.
      
      In the ghc-internals split this started to cause errors because
      `ghc-internal` is not a direct dependency of most packages, and hence
      important symbols to keep which are hard coded into the js runtime were
      getting dropped.
      20b702b5
    • Ben Gamari's avatar
      llvmGen: Adapt to allow use of new pass manager. · 77db84ab
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      We now must use `-passes` in place of `-O<n>` due to #21936.
      
      Closes #21936.
      77db84ab
  2. Feb 06, 2024
    • Zubin's avatar
      GHCi: Lookup breakpoint CCs in the correct module · b35dd613
      Zubin authored and Marge Bot's avatar Marge Bot committed
      We need to look up breakpoint CCs in the module that the breakpoint
      points to, and not the current module.
      
      Fixes #24327
      b35dd613
    • Zubin's avatar
      driver: Really don't lose track of nodes when we fail to resolve cycles · 532993c8
      Zubin authored and Marge Bot's avatar Marge Bot committed
      This fixes a bug in 8db8d2fd, where we could lose
      track of acyclic components at the start of an unresolved cycle. We now ensure we
      never loose track of any of these components.
      
      As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC:
      
      When viewed without boot files, we have a single SCC
      
      ```
      [REC main:T24275B [main:T24275B {-# SOURCE #-},
                         main:T24275A {-# SOURCE #-}]
           main:T24275A [main:T24275A {-# SOURCE #-}]]
      ```
      
      But with boot files this turns into
      
      ```
      [NONREC main:T24275B {-# SOURCE #-} [],
       REC main:T24275B [main:T24275B {-# SOURCE #-},
                         main:T24275A {-# SOURCE #-}]
          main:T24275A {-# SOURCE #-} [main:T24275B],
       NONREC main:T24275A [main:T24275A {-# SOURCE #-}]]
      ```
      
      Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot.
      However, we treat this entire group as a single "SCC" because it seems so when we
      analyse the graph without taking boot files into account.
      
      Indeed, we must return a single ResolvedCycle element in the BuildPlan for this
      as described in Note [Upsweep].
      
      However, since after resolving this is not a true SCC anymore, `findCycle` fails
      to find a cycle and we have a sub-optimal error message as a result.
      
      To handle this, I extended `findCycle` to not assume its input is an SCC, and to
      try harder to find cycles in its input.
      
      Fixes #24275
      532993c8
    • Andrei Borzenkov's avatar
      Lazy skolemisation for @a-binders (#17594) · f5d3e03c
      Andrei Borzenkov authored and Marge Bot's avatar Marge Bot committed
      This patch is a preparation for @a-binders implementation.  The main changes are:
      
      * Skolemisation is now prepared to deal with @binders.
        See Note [Skolemisation overview] in GHC.Tc.Utils.Unify.
        Most of the action is in
          - Utils.Unify.matchExpectedFunTys
          - Gen.Pat.tcMatchPats
          - Gen.Expr.tcPolyExprCheck
          - Gen.Binds.tcPolyCheck
      
      Some accompanying refactoring:
      
      * I found that funTyConAppTy_maybe was doing a lot of allocation, and
        rejigged userTypeError_maybe to avoid calling it.
      f5d3e03c
    • Simon Peyton Jones's avatar
      Refactoring in preparation for lazy skolemisation · e2ea933f
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      
      * Make HsMatchContext and HsStmtContext be parameterised over the
        function name itself, rather than over the pass.
        See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr
          - Replace types
              HsMatchContext GhcPs --> HsMatchContextPs
              HsMatchContext GhcRn --> HsMatchContextRn
              HsMatchContext GhcTc --> HsMatchContextRn  (sic! not Tc)
              HsStmtContext  GhcRn --> HsStmtContextRn
          - Kill off convertHsMatchCtxt
      
      * Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing
        a complete user-supplied signature) is its own data type.
          - Split TcIdSigInfo(CompleteSig, PartialSig) into
              TcCompleteSig(CSig)
              TcPartialSig(PSig)
          - Use TcCompleteSig in tcPolyCheck, CheckGen
          - Rename types and data constructors:
              TcIdSigInfo         --> TcIdSig
              TcPatSynInfo(TPSI)  --> TcPatSynSig(PatSig)
          - Shuffle around helper functions:
              tcSigInfoName           (moved to GHC.Tc.Types.BasicTypes)
              completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes)
              tcIdSigName             (inlined and removed)
              tcIdSigLoc              (introduced)
          - Rearrange the pattern match in chooseInferredQuantifiers
      
      * Rename functions and types:
          tcMatchesCase         --> tcCaseMatches
          tcMatchesFun          --> tcFunBindMatches
          tcMatchLambda         --> tcLambdaMatches
          tcPats                --> tcMatchPats
          matchActualFunTysRho  --> matchActualFunTys
          matchActualFunTySigma --> matchActualFunTy
      
      * Add HasDebugCallStack constraints to:
          mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy,
          mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe
      
      * Use `penv` from the outer context in the inner loop of
        GHC.Tc.Gen.Pat.tcMultiple
      
      * Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file,
        factor out and export tcMkScaledFunTy.
      
      * Move isPatSigCtxt down the file.
      
      * Formatting and comments
      
      Co-authored-by: default avatarVladislav Zavialov <vlad.z.4096@gmail.com>
      e2ea933f
  3. Feb 05, 2024
    • Andrei Borzenkov's avatar
      ce90f12f
    • Simon Peyton Jones's avatar
      Stop dropping a case whose binder is demanded · cfd68290
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This MR fixes #24251.
      
      See Note [Case-to-let for strictly-used binders]
      in GHC.Core.Opt.Simplify.Iteration, plus #24251, for
      lots of discussion.
      
      Final Nofib changes over 0.1%:
      +-----------------------------------------
      |        imaginary/digits-of-e2    -2.16%
      |                imaginary/rfib    -0.15%
      |                    real/fluid    -0.10%
      |                   real/gamteb    -1.47%
      |                       real/gg    -0.20%
      |                 real/maillist    +0.19%
      |                      real/pic    -0.23%
      |                      real/scs    -0.43%
      |               shootout/n-body    -0.41%
      |        shootout/spectral-norm    -0.12%
      +========================================
      |                     geom mean    -0.05%
      
      Pleasingly, overall executable size is down by just over 1%.
      
      Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the
      geometric mean is -0.1% which seems good.
      cfd68290
  4. Feb 04, 2024
  5. Feb 03, 2024
    • Apoorv Ingle's avatar
      Expand `do` blocks right before typechecking using the `HsExpansion` philosophy. · 5ff7cc26
      Apoorv Ingle authored
      - Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206
      
      - The change is detailed in
        - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do`
        - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr`
               expains the rational of doing expansions in type checker as opposed to in the renamer
      
      - Adds new datatypes:
        - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier
          1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`)
          2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack
      
        - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated
          This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam`
      
        - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc`
      
      - Ensures warnings such as
        1. Pattern match checks
        2. Failable patterns
        3. non-() return in body statements are preserved
      
      - Kill `HsMatchCtxt` in favor of `TcMatchAltChecker`
      
      - Testcases:
        * T18324 T20020 T23147 T22788 T15598 T22086
        * T23147b (error message check),
        * DoubleMatch (match inside a match for pmc check)
        * pattern-fails (check pattern match with non-refutable pattern, eg. newtype)
        * Simple-rec (rec statements inside do statment)
        * T22788 (code snippet from #22788)
        * DoExpanion1 (Error messages for body statments)
        * DoExpansion2 (Error messages for bind statements)
        * DoExpansion3 (Error messages for let statements)
      
      Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass
      
      Metric Increase 'compile_time/bytes allocated':
          T9020
      
      The testcase is a pathalogical example of a `do`-block with many statements that do nothing.
      Given that we are expanding the statements into function binds, we will have to bear
      a (small) 2% cost upfront in the compiler to unroll the statements.
      5ff7cc26
  6. Feb 01, 2024
    • Andrei Borzenkov's avatar
      Namespacing for WARNING/DEPRECATED pragmas (#24396) · 151dda4e
      Andrei Borzenkov authored and Marge Bot's avatar Marge Bot committed
      New syntax for WARNING and DEPRECATED pragmas was added,
      namely namespace specifierss:
      
        namespace_spec ::= 'type' | 'data' | {- empty -}
      
        warning ::= warning_category namespace_spec namelist strings
      
        deprecation ::= namespace_spec namelist strings
      
      A new data type was introduced to represent these namespace specifiers:
      
        data NamespaceSpecifier =
          NoSpecifier |
          TypeNamespaceSpecifier (EpToken "type") |
          DataNamespaceSpecifier (EpToken "data")
      
      Extension field XWarning now contains this NamespaceSpecifier.
      
      lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier
      and checks that the namespace of the found names matches the passed flag.
      With this change {-# WARNING data D "..." #-} pragma will only affect value
      namespace and {-# WARNING type D "..." #-} will only affect type
      namespace. The same logic is applicable to DEPRECATED pragmas.
      
      Finding duplicated warnings inside rnSrcWarnDecls now takes into
      consideration NamespaceSpecifier flag to allow warnings with the
      same names that refer to different namespaces.
      151dda4e
    • Cheng Shao's avatar
      compiler: enable generic cmm optimizations in wasm backend NCG · c6ce242e
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      This commit enables the generic cmm optimizations in other NCGs to be
      run in the wasm backend as well, followed by a late cmm control-flow
      optimization pass. The added optimizations do catch some corner cases
      not handled by the pre-NCG cmm pipeline and are useful in generating
      smaller CFGs.
      c6ce242e
    • Cheng Shao's avatar
      compiler: explicitly disable PIC in wasm32 NCG · 87e34888
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      This commit explicitly disables the ncgPIC flag for the wasm32 target.
      The wasm backend doesn't support PIC for the time being.
      87e34888
    • Cheng Shao's avatar
      compiler: move generic cmm optimization logic in NCG to a standalone module · 6534da24
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module,
      GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be
      run in the wasm backend NCG code, which is defined in other modules
      that's imported by GHC.CmmToAsm, causing a cyclic dependency issue.
      6534da24
    • Ben Gamari's avatar
      codeGen: Use relaxed-read in closureInfoPtr · 76fe2b75
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      76fe2b75
    • Ben Gamari's avatar
      codeGen: Use relaxed accesses in ticky bumping · 0785cf81
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      0785cf81
    • Ben Gamari's avatar
      cmm: Introduce MO_RelaxedRead · 31553b11
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      In hand-written Cmm it can sometimes be necessary to atomically load
      from memory deep within an expression (e.g. see the `CHECK_GC` macro).
      This MachOp provides a convenient way to do so without breaking the
      expression into multiple statements.
      31553b11
  7. Jan 31, 2024
  8. Jan 29, 2024
  9. Jan 26, 2024
  10. Jan 25, 2024
  11. Jan 24, 2024
    • sheaf's avatar
      Fix FMA instruction on LLVM · a40f4ab2
      sheaf authored and Marge Bot's avatar Marge Bot committed
      We were emitting the wrong instructions for fused multiply-add
      operations on LLVM:
      
        - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd"
        - LLVM does not support other instructions such as "fmsub"; instead
          we implement these by flipping signs of some arguments
        - the instruction is an LLVM intrinsic, which requires handling it
          like a normal function call instead of a machine instruction
      
      Fixes #24223
      a40f4ab2
    • Greg Steuck's avatar
      Avoid utf8 in primops.txt.pp comments · 0325a6e5
      Greg Steuck authored and Marge Bot's avatar Marge Bot committed
      They don't make it through readFile' without explicitly setting the
      encoding. See ghc/ghc#17755
      0325a6e5
    • Cheng Shao's avatar
      rts: enable wasm32 register mapping · 0cda2b8b
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      The wasm backend didn't properly make use of all Cmm global registers
      due to #24347. Now that it is fixed, this patch re-enables full
      register mapping for wasm32, and we can now generate smaller & faster
      wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152.
      0cda2b8b
  12. Jan 20, 2024
  13. Jan 19, 2024
  14. Jan 18, 2024
  15. Jan 17, 2024
    • Matthew Pickering's avatar
      Stop retaining old ModGuts throughout subsequent simplifier phases · 16414d7d
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      Each phase of the simplifier typically rewrites the majority of ModGuts,
      so we want to be able to release the old ModGuts as soon as possible.
      
      `name_ppr_ctxt` lives throught the whole optimiser phase and it was
      retaining a reference to `ModGuts`, so we were failing to release the
      old `ModGuts` until the end of the phase (potentially doubling peak
      memory usage for that particular phase).
      
      This was discovered using eras profiling (#24332)
      
      Fixes #24328
      16414d7d
  16. Jan 16, 2024
    • Simon Peyton Jones's avatar
      Improve SpecConstr (esp nofib/spectral/ansi) · 66dc09b1
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This MR makes three improvements to SpecConstr: see #24282
      
      * It fixes an outright (and recently-introduced) bug in `betterPat`, which
        was wrongly forgetting to compare the lengths of the argument lists.
      
      * It enhances ConVal to inclue a boolean for work-free-ness, so that the
        envt can contain non-work-free constructor applications, so that we
        can do more: see Note [ConVal work-free-ness]
      
      * It rejigs `subsumePats` so that it doesn't reverse the list.  This can
        make a difference because, when patterns overlap, we arbitrarily pick
        the first.  There is no "right" way, but this retains the old
        pre-subsumePats behaviour, thereby "fixing" the regression in #24282.
      
      Nofib results
      
         +========================================
         |                 spectral/ansi  -21.14%
         | spectral/hartel/comp_lab_zift   -0.12%
         |       spectral/hartel/parstof   +0.09%
         |           spectral/last-piece   -2.32%
         |           spectral/multiplier   +6.03%
         |                 spectral/para   +0.60%
         |               spectral/simple   -0.26%
         +========================================
         |                     geom mean   -0.18%
         +----------------------------------------
      
      The regression in `multiplier` is sad, but it simply replicates GHC's
      previous behaviour (e.g. GHC 9.6).
      66dc09b1
  17. Jan 15, 2024
    • sheaf's avatar
      Use lookupOccRn_maybe in TH.lookupName · c5fc7304
      sheaf authored and Marge Bot's avatar Marge Bot committed
      When looking up a value, we want to be able to find both variables
      and record fields. So we should not use the lookupSameOccRn_maybe
      function, as we can't know ahead of time which record field namespace
      a record field with the given textual name will belong to.
      
      Fixes #24293
      c5fc7304
  18. Jan 14, 2024
  19. Jan 13, 2024
  20. Jan 10, 2024
Loading