Skip to content
Snippets Groups Projects
  1. Feb 10, 2024
  2. Feb 08, 2024
    • Jade's avatar
      Improve Monad, Functor & Applicative docs · 762b2120
      Jade authored and Matthew Pickering's avatar Matthew Pickering committed
      This patch aims to improve the documentation of Functor, Applicative,
      Monad and related symbols. The main goal is to make it more consistent
      and make accessible. See also: !10979 (closed) and !10985 (closed)
      
      Ticket #17929
      
      Updates haddock submodule
      762b2120
    • Apoorv Ingle's avatar
      Enable mdo statements to use HsExpansions · 9f987235
      Apoorv Ingle authored and Marge Bot's avatar Marge Bot committed
      Fixes: #24411
      Added test T24411 for regression
      9f987235
    • John Ericson's avatar
      Generate LLVM min/max bound policy via Hadrian · c37931b3
      John Ericson authored and Marge Bot's avatar Marge Bot committed
      Per #23966, I want the top-level configure to only generate
      configuration data for Hadrian, not do any "real" tasks on its own.
      This is part of that effort --- one less file generated by it.
      
      (It is still done with a `.in` file, so in a future world non-Hadrian
      also can easily create this file.)
      
      Split modules:
      
      - GHC.CmmToLlvm.Config
      - GHC.CmmToLlvm.Version
      - GHC.CmmToLlvm.Version.Bounds
      - GHC.CmmToLlvm.Version.Type
      
      This also means we can get rid of the silly `unused.h` introduced in
      !6803 / 7dfcab2f as temporary kludge.
      
      Part of #23966
      c37931b3
    • Matthew Pickering's avatar
      Add alpine 3_18 release job · 707a32f5
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This is mainly experimental and future proofing to enable a smooth
      transition to newer alpine releases once 3_12 is too old.
      707a32f5
    • Matthew Pickering's avatar
      Update bootstrap plans for 9.4.8 and 9.6.4 · 5fcd58be
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      5fcd58be
    • Matthew Pickering's avatar
      c32b6426
    • Matthew Pickering's avatar
      Use specific clang assembler when compiling with -fllvm · ab533e71
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      There are situations where LLVM will produce assembly which older gcc
      toolchains can't handle. For example on Deb10, it seems that LLVM >= 13
      produces assembly which the default gcc doesn't support.
      
      A more robust solution in the long term is to require a specific LLVM
      compatible assembler when using -fllvm.
      
      Fixes #16354
      ab533e71
    • Ben Gamari's avatar
      Bump filepath to 1.5.0.0 · f2dffd2e
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Required bumps of the following submodules:
      
       * `directory`
       * `filepath`
       * `haskeline`
       * `process`
       * `unix`
       * `hsc2hs`
       * `Win32`
       * `semaphore-compat`
      
      and the addition of `os-string` as a boot package.
      f2dffd2e
    • Ben Gamari's avatar
      hadrian: Set -this-package-name · d7ee12ea
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      When constructing the GHC flags for a package Hadrian must take care to
      set `-this-package-name` in addition to `-this-unit-id`. This hasn't
      broken until now as we have not had any uses of qualified package
      imports. However, this will change with `filepath-1.5` and the
      corresponding `unix` bump, breaking `hadrian/multi-ghci`.
      d7ee12ea
    • Ben Gamari's avatar
      gitignore: Ignore .hadrian_ghci_multi/ · 9d65235a
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      9d65235a
    • Ben Gamari's avatar
      Add os-string as a boot package · 9060d55b
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Introduces `os-string` submodule. This will be necessary for
      `filepath-1.5`.
      9060d55b
    • Vladislav Zavialov's avatar
      Haddock comments on infix constructors (#24221) · e8fb2451
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for
      infix constructors.
      
      This change fixes a Haddock regression (introduced in 19e80b9a)
      that affected leading comments on infix data constructor declarations:
      
      	-- | Docs for infix constructor
      	| Int :* Bool
      
      The comment should be associated with the data constructor (:*), not
      with its left-hand side Int.
      e8fb2451
    • 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
    • Ben Gamari's avatar
      base: Cleanup whitespace in cbits · 2df96366
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      2df96366
    • 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
    • Matthew Pickering's avatar
      testsuite: Mark length001 as fragile on javascript · 3c9ddf97
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      Modifying the timeout multiplier is not a robust way to get this test to
      reliably fail. Therefore we mark it as fragile until/if javascript ever
      supports the stack limit.
      3c9ddf97
    • 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
  3. Feb 07, 2024
    • Matthew Pickering's avatar
      distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable · d309f4e7
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we
      were missing passing `--target` when invoking the linker.
      
      Fixes #24414
      d309f4e7
    • Rodrigo Mesquita's avatar
      Synchronize bindist configure for #24324 · c9731d6d
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      In cdddeb0f, we set up a
      workaround for #24324 in the in-tree configure script, but forgot to
      update the bindist configure script accordingly. This updates it.
      c9731d6d
    • jeffrey young's avatar
      ts: add wasm_arch, heapprof002 wasm extension · 75a31379
      jeffrey young authored and Marge Bot's avatar Marge Bot committed
      75a31379
    • jeffrey young's avatar
      ts: add compile_artifact, ignore_extension flag · 569b4c10
      jeffrey young authored and Marge Bot's avatar Marge Bot committed
      In b5213542 the testsuite gained the
      capability to collect generic metrics. But this assumed that the test
      was not linking and producing artifacts and we only wanted to track
      object files, interface files, or build artifacts from the compiler
      build. However, some backends, such as the JS backend, produce artifacts when
      compiling, such as the jsexe directory which we want to track.
      
      This patch:
      
      - tweaks the testsuite to collect generic metrics on any build artifact
      in the test directory.
      
      - expands the exe_extension function to consider windows and adds the
      ignore_extension flag.
      
      - Modifies certain tests to add the ignore_extension flag. Tests such as
      heaprof002 expect a .ps file, but on windows without ignore_extensions
      the testsuite will look for foo.exe.ps. Hence the flag.
      
      - adds the size_hello_artifact test
      569b4c10
  4. Feb 06, 2024
    • Zubin's avatar
      testsuite: Add test for #24327 · b09e6958
      Zubin authored and Marge Bot's avatar Marge Bot committed
      b09e6958
    • 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
  5. Feb 05, 2024
    • Andrei Borzenkov's avatar
      ce90f12f
    • Simon Peyton Jones's avatar
      Add Note [Bangs in Integer functions] · e4d137bb
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      ...to document the bangs in the functions in GHC.Num.Integer
      e4d137bb
    • 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
  6. Feb 04, 2024
  7. 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
    • Rodrigo Mesquita's avatar
      Work around autotools setting C11 standard in CC/CXX · cdddeb0f
      Rodrigo Mesquita authored and Marge Bot's avatar Marge Bot committed
      In autoconf >=2.70, C11 is set by default for $CC and $CXX via the
      -std=...11 flag. In this patch, we split the "-std" flag out of the $CC
      and $CXX variables, which we traditionally assume to be just the
      executable name/path, and move it to $CFLAGS/$CXXFLAGS instead.
      
      Fixes #24324
      cdddeb0f
    • Matthew Craven's avatar
      Bump bytestring submodule to something closer to 0.12.1 · 27020458
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c
      (which reworks unaligned writes in Builder) and the stuff in
      https://github.com/haskell/bytestring/pull/631 can see wider testing.
      
      The less-terrible code for unaligned writes used in Builder on
      hosts not known to be ulaigned-friendly also takes less effort
      for GHC to compile, resulting in a metric decrease for T21839c
      on some platforms.
      
      The metric increase on T21839r is caused by the unrelated commit
      750dac33465e7b59100698a330b44de7049a345c.  It perhaps warrants
      further analysis and discussion (see #23822) but is not critical.
      
      Metric Decrease:
      T21839c
      Metric Increase:
      T21839r
      27020458
  8. Feb 01, 2024
    • Bryan R's avatar
      CI: Disable the test-cabal-reinstall job · 38c3afb6
      Bryan R authored and Marge Bot's avatar Marge Bot committed
      Fixes #24363
      38c3afb6
    • 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
Loading