Haskell.org
Sign In Sign Up
Manage this list Sign In Sign Up

Keyboard Shortcuts

Thread View

  • j: Next unread message
  • k: Previous unread message
  • j a: Jump to all threads
  • j l: Jump to MailingList overview

ghc-commits

Thread Start a new thread
Download
Threads by month
  • ----- 2026 -----
  • January
  • ----- 2025 -----
  • December
  • November
  • October
  • September
  • August
  • July
  • June
  • May
  • April
ghc-commits@haskell.org

December 2025

  • 1 participants
  • 564 discussions
[Git][ghc/ghc][wip/ani/hie-spans] wrap then_op with a generated src span
by Apoorv Ingle (@ani) 22 Dec '25

22 Dec '25
Apoorv Ingle pushed to branch wip/ani/hie-spans at Glasgow Haskell Compiler / GHC Commits: be288632 by Apoorv Ingle at 2025-12-22T10:55:13-06:00 wrap then_op with a generated src span - - - - - 3 changed files: - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Tc/Gen/Do.hs - utils/check-exact/Utils.hs Changes: ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -441,9 +441,6 @@ bindingsOnly (C c n : xs) = do RealSrcSpan span _ -> Node (mkSourcedNodeInfo org nodeinfo) span [] : rest where nodeinfo = NodeInfo S.empty [] (M.singleton (Right n) info) info = mempty{identInfo = S.singleton c} - GeneratedSrcSpan span -> Node (mkSourcedNodeInfo org nodeinfo) span [] : rest - where nodeinfo = NodeInfo S.empty [] (M.singleton (Right n) info) - info = mempty{identInfo = S.singleton c} _ -> rest concatM :: Monad m => [m [a]] -> m [a] @@ -690,26 +687,26 @@ instance ToHie (Context (Located Name)) where (S.singleton context))) span []] - C context (L (GeneratedSrcSpan span) name') - | nameUnique name' == mkBuiltinUnique 1 -> pure [] - -- `mkOneRecordSelector` makes a field var using this unique, which we ignore - | otherwise -> do - m <- lift $ gets name_remapping - org <- ask - let name = case lookupNameEnv m name' of - Just var -> varName var - Nothing -> name' - -- insert the entity info for the name into the entity_infos map - lookupAndInsertEntityName name - lookupAndInsertEntityName name' - pure - [Node - (mkSourcedNodeInfo org $ NodeInfo S.empty [] $ - M.singleton (Right name) - (IdentifierDetails Nothing - (S.singleton context))) - span - []] + -- C context (L (GeneratedSrcSpan span) name') + -- | nameUnique name' == mkBuiltinUnique 1 -> pure [] + -- -- `mkOneRecordSelector` makes a field var using this unique, which we ignore + -- | otherwise -> do + -- m <- lift $ gets name_remapping + -- org <- ask + -- let name = case lookupNameEnv m name' of + -- Just var -> varName var + -- Nothing -> name' + -- -- insert the entity info for the name into the entity_infos map + -- lookupAndInsertEntityName name + -- lookupAndInsertEntityName name' + -- pure + -- [Node + -- (mkSourcedNodeInfo org $ NodeInfo S.empty [] $ + -- M.singleton (Right name) + -- (IdentifierDetails Nothing + -- (S.singleton context))) + -- span + -- []] _ -> pure [] instance ToHie (Context (Located (WithUserRdr Name))) where @@ -1228,9 +1225,6 @@ instance HiePass p => ToHie (LocatedA (HsOverLit (GhcPass p))) where instance HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) where toHie e@(L mspan oexpr) = concatM $ getTypeNode e : case oexpr of - HsVar _ (L loc var) - | GeneratedSrcSpan _ <- locA loc - -> [ toHie $ C Use (L loc var) ] HsVar _ (L _ var) -> [ toHie $ C Use (L mspan var) -- Patch up var location since typechecker removes it ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -14,7 +14,7 @@ module GHC.Tc.Gen.Do (expandDoStmts) where import GHC.Prelude -import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, +import GHC.Rename.Utils ( wrapGenSpan, wrapGenSpan', genHsExpApps, genHsApp, genHsLet, genHsLamDoExp, genHsCaseAltDoExp, genWildPat ) import GHC.Rename.Env ( irrefutableConLikeRn ) @@ -114,18 +114,25 @@ expand_do_stmts doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) | otherwise = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt) -expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ (L _e_lspan e) (SyntaxExprRn then_op) _)) : lstmts) = +expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ (L _e_lspan e) (SyntaxExprRn then_op) _)) : lstmts) -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr -- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below -- stmts ~~> stmts' -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' - do expand_stmts_expr <- expand_do_stmts doFlavour lstmts - let expansion = genHsExpApps then_op -- (>>) - [ -- L e_lspan (mkExpandedStmt stmt doFlavour e) - wrapGenSpan e - , expand_stmts_expr ] - return $ L loc (mkExpandedStmt stmt doFlavour expansion) + | RealSrcSpan sp _ <- locA loc = + do expand_stmts_expr <- expand_do_stmts doFlavour lstmts + let expansion = mkHsApps (wrapGenSpan' sp then_op) -- (>>) + [ wrapGenSpan e + , expand_stmts_expr ] + return $ L loc (mkExpandedStmt stmt doFlavour (unLoc $ expansion)) + + | otherwise = + do expand_stmts_expr <- expand_do_stmts doFlavour lstmts + let expansion = genHsExpApps then_op -- (>>) + [ wrapGenSpan e + , expand_stmts_expr ] + return $ L loc (mkExpandedStmt stmt doFlavour expansion) expand_do_stmts doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts ===================================== utils/check-exact/Utils.hs ===================================== @@ -530,9 +530,10 @@ sortEpaComments cs = sortBy cmp cs -- | Makes a comment which originates from a specific keyword. mkKWComment :: String -> NoCommentsLocation -> Comment -mkKWComment kw (EpaSpan (RealSrcSpan ss mb)) = Comment kw (EpaSpan (RealSrcSpan ss mb)) ss (Just kw) -mkKWComment kw (EpaSpan (UnhelpfulSpan _)) = Comment kw (EpaDelta noSrcSpan (SameLine 0) NoComments) placeholderRealSpan (Just kw) mkKWComment kw (EpaDelta ss dp cs) = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw) +mkKWComment kw (EpaSpan (RealSrcSpan ss mb)) = Comment kw (EpaSpan (RealSrcSpan ss mb)) ss (Just kw) +mkKWComment kw (EpaSpan _) = Comment kw (EpaDelta noSrcSpan (SameLine 0) NoComments) placeholderRealSpan (Just kw) + sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a] sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be2886327cfac70033c8cb9142eca01… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be2886327cfac70033c8cb9142eca01… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/ani/hie-spans] wrap then_op with a generated src span
by Apoorv Ingle (@ani) 22 Dec '25

22 Dec '25
Apoorv Ingle pushed to branch wip/ani/hie-spans at Glasgow Haskell Compiler / GHC Commits: 6d4a3e14 by Apoorv Ingle at 2025-12-22T10:44:49-06:00 wrap then_op with a generated src span - - - - - 3 changed files: - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Tc/Gen/Do.hs - utils/check-exact/Utils.hs Changes: ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -441,9 +441,6 @@ bindingsOnly (C c n : xs) = do RealSrcSpan span _ -> Node (mkSourcedNodeInfo org nodeinfo) span [] : rest where nodeinfo = NodeInfo S.empty [] (M.singleton (Right n) info) info = mempty{identInfo = S.singleton c} - GeneratedSrcSpan span -> Node (mkSourcedNodeInfo org nodeinfo) span [] : rest - where nodeinfo = NodeInfo S.empty [] (M.singleton (Right n) info) - info = mempty{identInfo = S.singleton c} _ -> rest concatM :: Monad m => [m [a]] -> m [a] @@ -690,26 +687,26 @@ instance ToHie (Context (Located Name)) where (S.singleton context))) span []] - C context (L (GeneratedSrcSpan span) name') - | nameUnique name' == mkBuiltinUnique 1 -> pure [] - -- `mkOneRecordSelector` makes a field var using this unique, which we ignore - | otherwise -> do - m <- lift $ gets name_remapping - org <- ask - let name = case lookupNameEnv m name' of - Just var -> varName var - Nothing -> name' - -- insert the entity info for the name into the entity_infos map - lookupAndInsertEntityName name - lookupAndInsertEntityName name' - pure - [Node - (mkSourcedNodeInfo org $ NodeInfo S.empty [] $ - M.singleton (Right name) - (IdentifierDetails Nothing - (S.singleton context))) - span - []] + -- C context (L (GeneratedSrcSpan span) name') + -- | nameUnique name' == mkBuiltinUnique 1 -> pure [] + -- -- `mkOneRecordSelector` makes a field var using this unique, which we ignore + -- | otherwise -> do + -- m <- lift $ gets name_remapping + -- org <- ask + -- let name = case lookupNameEnv m name' of + -- Just var -> varName var + -- Nothing -> name' + -- -- insert the entity info for the name into the entity_infos map + -- lookupAndInsertEntityName name + -- lookupAndInsertEntityName name' + -- pure + -- [Node + -- (mkSourcedNodeInfo org $ NodeInfo S.empty [] $ + -- M.singleton (Right name) + -- (IdentifierDetails Nothing + -- (S.singleton context))) + -- span + -- []] _ -> pure [] instance ToHie (Context (Located (WithUserRdr Name))) where @@ -1228,9 +1225,6 @@ instance HiePass p => ToHie (LocatedA (HsOverLit (GhcPass p))) where instance HiePass p => ToHie (LocatedA (HsExpr (GhcPass p))) where toHie e@(L mspan oexpr) = concatM $ getTypeNode e : case oexpr of - HsVar _ (L loc var) - | GeneratedSrcSpan _ <- locA loc - -> [ toHie $ C Use (L loc var) ] HsVar _ (L _ var) -> [ toHie $ C Use (L mspan var) -- Patch up var location since typechecker removes it ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -14,7 +14,7 @@ module GHC.Tc.Gen.Do (expandDoStmts) where import GHC.Prelude -import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, +import GHC.Rename.Utils ( wrapGenSpan, wrapGenSpan', genHsExpApps, genHsApp, genHsLet, genHsLamDoExp, genHsCaseAltDoExp, genWildPat ) import GHC.Rename.Env ( irrefutableConLikeRn ) @@ -121,11 +121,11 @@ expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ (L _e_lspan e) (SyntaxExprRn -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' do expand_stmts_expr <- expand_do_stmts doFlavour lstmts - let expansion = genHsExpApps then_op -- (>>) + let expansion = mkHsApp (wrapGenSpan' loc then_op) -- (>>) [ -- L e_lspan (mkExpandedStmt stmt doFlavour e) wrapGenSpan e , expand_stmts_expr ] - return $ L loc (mkExpandedStmt stmt doFlavour expansion) + return $ L loc (mkExpandedStmt stmt doFlavour (unLoc $ expansion)) expand_do_stmts doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts ===================================== utils/check-exact/Utils.hs ===================================== @@ -530,9 +530,10 @@ sortEpaComments cs = sortBy cmp cs -- | Makes a comment which originates from a specific keyword. mkKWComment :: String -> NoCommentsLocation -> Comment -mkKWComment kw (EpaSpan (RealSrcSpan ss mb)) = Comment kw (EpaSpan (RealSrcSpan ss mb)) ss (Just kw) -mkKWComment kw (EpaSpan (UnhelpfulSpan _)) = Comment kw (EpaDelta noSrcSpan (SameLine 0) NoComments) placeholderRealSpan (Just kw) mkKWComment kw (EpaDelta ss dp cs) = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw) +mkKWComment kw (EpaSpan (RealSrcSpan ss mb)) = Comment kw (EpaSpan (RealSrcSpan ss mb)) ss (Just kw) +mkKWComment kw (EpaSpan _) = Comment kw (EpaDelta noSrcSpan (SameLine 0) NoComments) placeholderRealSpan (Just kw) + sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a] sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d4a3e14c6a69efcfd04a779ef6c7e6… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d4a3e14c6a69efcfd04a779ef6c7e6… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Remove unused known keys and names for type representations
by Marge Bot (@marge-bot) 22 Dec '25

22 Dec '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: bc36268a by Wolfgang Jeltsch at 2025-12-21T16:23:24-05:00 Remove unused known keys and names for type representations This removes the known-key and corresponding name variables for `TrName`, `TrNameD`, `TypeRep`, `KindRepTypeLitD`, `TypeLitSort`, and `mkTrType`, as they are apparently nowhere used in GHC’s source code. - - - - - ff5050e9 by Wolfgang Jeltsch at 2025-12-21T16:24:04-05:00 Remove unused known keys and names for natural operations This removes the known-key and corresponding name variables for `naturalAndNot`, `naturalLog2`, `naturalLogBaseWord`, `naturalLogBase`, `naturalPowMod`, `naturalSizeInBase`, `naturalToFloat`, and `naturalToDouble`, as they are apparently nowhere used in GHC’s source code. - - - - - 424388c2 by Wolfgang Jeltsch at 2025-12-21T16:24:45-05:00 Remove the unused known key and name for `Fingerprint` This removes the variables for the known key and the name of the `Fingerprint` data constructor, as they are apparently nowhere used in GHC’s source code. - - - - - a1ed86fe by Wolfgang Jeltsch at 2025-12-21T16:25:26-05:00 Remove the unused known key and name for `failIO` This removes the variables for the known key and the name of the `failIO` operation, as they are apparently nowhere used in GHC’s source code. - - - - - b8220daf by Wolfgang Jeltsch at 2025-12-21T16:26:07-05:00 Remove the unused known key and name for `liftM` This removes the variables for the known key and the name of the `liftM` operation, as they are apparently nowhere used in GHC’s source code. - - - - - eb0628b1 by Wolfgang Jeltsch at 2025-12-21T16:26:47-05:00 Fix the documentation of `hIsClosed` - - - - - 4ed8f5b6 by sheaf at 2025-12-22T11:30:30-05:00 Do deep subsumption when computing valid hole fits This commit makes a couple of improvements to the code that computes "valid hole fits": 1. It uses deep subsumption for data constructors. This matches up the multiplicities, as per Note [Typechecking data constructors]. This fixes #26338 (test: LinearHoleFits). 2. It now suggests (non-unidirectional) pattern synonyms as valid hole fits. This fixes #26339 (test: PatSynHoleFit). 3. It uses 'stableNameCmp', to make the hole fit output deterministic. ------------------------- Metric Increase: hard_hole_fits ------------------------- - - - - - 8699696a by sheaf at 2025-12-22T11:30:31-05:00 Speed up hole fits with a quick pre-test This speeds up the machinery for valid hole fits by doing a small check to rule out obviously wrong hole fits, such as: 1. A hole fit identifier whose type has a different TyCon at the head, after looking through foralls and (=>) arrows, e.g.: hole_ty = Int cand_ty = Maybe a or hole_ty = forall a b. a -> b cand_ty = forall x y. Either x y 2. A hole fit identifier that is not polymorphic when the hole type is polymorphic, e.g. hole_ty = forall a. a -> a cand_ty = Int -> Int ------------------------- Metric Decrease: hard_hole_fits ------------------------- - - - - - f969370e by Cheng Shao at 2025-12-22T11:30:31-05:00 configure: remove unused win32-tarballs.md5sum This patch removes the unused `win32-tarballs.md5sum` file from the tree. The current mingw tarball download logic in `mk/get-win32-tarballs.py` fetches and checks against `SHA256SUM` from the same location where the tarballs are fetched, and this file has been unused for a few years. - - - - - 33 changed files: - .gitattributes - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Unify.hs - docs/users_guide/9.16.1-notes.rst - libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs - − mk/win32-tarballs.md5sum - testsuite/tests/ghci/scripts/T8353.stderr - testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr - testsuite/tests/perf/compiler/hard_hole_fits.stderr - testsuite/tests/plugins/test-hole-plugin.stderr - testsuite/tests/th/T15321.stderr - testsuite/tests/typecheck/should_compile/T13050.stderr - testsuite/tests/typecheck/should_compile/T14273.stderr - testsuite/tests/typecheck/should_compile/T14590.stderr - testsuite/tests/typecheck/should_compile/T25180.stderr - testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/constraint_hole_fits.stderr - testsuite/tests/typecheck/should_compile/free_monad_hole_fits.stderr - testsuite/tests/typecheck/should_compile/hole_constraints.stderr - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes2.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr - testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr - testsuite/tests/typecheck/should_compile/valid_hole_fits_interactions.stderr - testsuite/tests/typecheck/should_fail/T14884.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c26d74bc31eb4c2d2c366adda863d… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c26d74bc31eb4c2d2c366adda863d… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/fix-26670] 13 commits: rts: workaround -Werror=maybe-uninitialized false positives
by recursion-ninja (@recursion-ninja) 22 Dec '25

22 Dec '25
recursion-ninja pushed to branch wip/fix-26670 at Glasgow Haskell Compiler / GHC Commits: 224446a2 by Cheng Shao at 2025-12-20T07:49:54-05:00 rts: workaround -Werror=maybe-uninitialized false positives In some cases gcc might report -Werror=maybe-uninitialized that we know are false positives, but need to workaround it to make validate builds with -Werror pass. - - - - - 251ec087 by Cheng Shao at 2025-12-20T07:49:54-05:00 hadrian: use -Og as C/C++ optimization level when debugging This commit enables -Og as optimization level when compiling the debug ways of rts. According to gcc documentation (https://gcc.gnu.org/onlinedocs/gcc/Optimize-Options.html#index-Og) -Og is a better choice than -O0 for producing debuggable code. It's also supported by clang as well, so it makes sense to use it as a default for debugging. Also add missing -g3 flag to C++ compilation flags in +debug_info flavour transformer. - - - - - fb586c67 by Cheng Shao at 2025-12-20T07:50:36-05:00 compiler: replace DList with OrdList This patch removes `DList` logic from the compiler and replaces it with `OrdList` which also supports O(1) concatenation and should be more memory efficient than the church-encoded `DList`. - - - - - 8149c987 by Cheng Shao at 2025-12-20T17:06:51-05:00 hadrian: add with_profiled_libs flavour transformer This patch adds a `with_profiled_libs` flavour transformer to hadrian which is the exact opposite of `no_profiled_libs`. It adds profiling ways to stage1+ rts/library ways, and doesn't alter other flavour settings. It is useful when needing to test profiling logic locally with a quick flavour. - - - - - 746b18cd by Cheng Shao at 2025-12-20T17:06:51-05:00 hadrian: fix missing profiled dynamic libraries in profiled_ghc This commit fixes the profiled_ghc flavour transformer to include profiled dynamic libraries as well, since they're supported by GHC since !12595. - - - - - 4dd7e3b9 by Cheng Shao at 2025-12-20T17:07:33-05:00 ci: set http.postBuffer to mitigate perf notes timeout on some runners This patch sets http.postBuffer to mitigate the timeout when fetching perf notes on some runners with slow internet connection. Fixes #26684. - - - - - bc36268a by Wolfgang Jeltsch at 2025-12-21T16:23:24-05:00 Remove unused known keys and names for type representations This removes the known-key and corresponding name variables for `TrName`, `TrNameD`, `TypeRep`, `KindRepTypeLitD`, `TypeLitSort`, and `mkTrType`, as they are apparently nowhere used in GHC’s source code. - - - - - ff5050e9 by Wolfgang Jeltsch at 2025-12-21T16:24:04-05:00 Remove unused known keys and names for natural operations This removes the known-key and corresponding name variables for `naturalAndNot`, `naturalLog2`, `naturalLogBaseWord`, `naturalLogBase`, `naturalPowMod`, `naturalSizeInBase`, `naturalToFloat`, and `naturalToDouble`, as they are apparently nowhere used in GHC’s source code. - - - - - 424388c2 by Wolfgang Jeltsch at 2025-12-21T16:24:45-05:00 Remove the unused known key and name for `Fingerprint` This removes the variables for the known key and the name of the `Fingerprint` data constructor, as they are apparently nowhere used in GHC’s source code. - - - - - a1ed86fe by Wolfgang Jeltsch at 2025-12-21T16:25:26-05:00 Remove the unused known key and name for `failIO` This removes the variables for the known key and the name of the `failIO` operation, as they are apparently nowhere used in GHC’s source code. - - - - - b8220daf by Wolfgang Jeltsch at 2025-12-21T16:26:07-05:00 Remove the unused known key and name for `liftM` This removes the variables for the known key and the name of the `liftM` operation, as they are apparently nowhere used in GHC’s source code. - - - - - eb0628b1 by Wolfgang Jeltsch at 2025-12-21T16:26:47-05:00 Fix the documentation of `hIsClosed` - - - - - ebec9a71 by Recursion Ninja at 2025-12-22T09:12:16-05:00 Decoupling Language.Haskell.Syntax.Binds from GHC.Types.Basic by transfering InlinePragma types between the modules. * Moved InlinePragma data-types to Language.Haskell.Syntax.Binds.InlinePragma * Partitioned of Arity type synonyms to GHC.Types.Arity * InlinePragma is now extensible via Trees That Grow * Activation is now extensible via Trees That Grow * Maybe Arity change to more descriptive InlineSaturation data-type * InlineSaturation information removed from InlinePragma during GHS parsing pass * Cleaned up the exposed module interfaces of the new modules - - - - - 74 changed files: - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps/Ids.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Pipeline/Types.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Iteration.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Ppr.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Unfold/Make.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/Core/Opt/Simplify.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/ThToHs.hs - + compiler/GHC/Types/Arity.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - + compiler/GHC/Types/InlinePragma.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Outputable.hs - compiler/Language/Haskell/Syntax/Binds.hs - + compiler/Language/Haskell/Syntax/Binds/InlinePragma.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Packages.hs - libraries/exceptions - libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs - rts/linker/InitFini.c - rts/sm/Sanity.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ebe82b033bd5c2d169b55c5d779ff… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ebe82b033bd5c2d169b55c5d779ff… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL] 2 commits: Increase timeout for emulators
by Sven Tennie (@supersven) 22 Dec '25

22 Dec '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL at Glasgow Haskell Compiler / GHC Commits: f910d9e5 by Sven Tennie at 2025-12-22T15:57:39+01:00 Increase timeout for emulators Test runs with emulators naturally take longer than on native machines. Generate jobs.yml - - - - - e34073d4 by Sven Tennie at 2025-12-22T15:57:39+01:00 ghc: Distinguish between having an interpreter and having an internal one Otherwise, we fail with warnings when compiling tools. Actually, these are related but different things: - ghc can run an interpreter (either internal or external) - ghc is compiled with an internal interpreter - - - - - 7 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/src/Settings/Packages.hs Changes: ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -20,6 +20,7 @@ import qualified Data.ByteString.Lazy.Char8 as B import qualified Data.Set as S import System.Environment import Data.List +import Data.Char (isSpace) {- Note [Generating the CI pipeline] @@ -893,14 +894,24 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} } Emulator s -> "CROSS_EMULATOR" =: s NoEmulatorNeeded -> mempty , if withNuma buildConfig then "ENABLE_NUMA" =: "1" else mempty - , let runtestArgs = + , let testTimeoutArg = + case crossEmulator buildConfig of + -- Emulators are naturally slower than native machines. + -- Triple the default of 300. + Emulator _ -> "-e config.timeout=900" :: String + _ -> mempty + runtestArgs = + testTimeoutArg : [ "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity" | validateNonmovingGc buildConfig ] - in "RUNTEST_ARGS" =: unwords runtestArgs + in "RUNTEST_ARGS" =: (trim . unwords) runtestArgs , if testsuiteUsePerf buildConfig then "RUNTEST_ARGS" =: "--config perf_path=perf" else mempty ] + trim :: String -> String + trim = dropWhileEnd isSpace . dropWhile isSpace + -- Keep in sync with the exclude list in `function clean()` in -- `.gitlab/ci.sh`! jobArtifacts = Artifacts ===================================== .gitlab/jobs.yaml ===================================== @@ -389,7 +389,7 @@ "OBJCOPY": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objcopy", "OBJDUMP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objdump", "RANLIB": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-llvm-ranlib", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "SIZE": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-size", "STRINGS": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strings", "STRIP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strip", @@ -471,7 +471,7 @@ "OBJCOPY": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objcopy", "OBJDUMP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objdump", "RANLIB": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-llvm-ranlib", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "SIZE": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-size", "STRINGS": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strings", "STRIP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strip", @@ -1060,7 +1060,7 @@ "OBJCOPY": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objcopy", "OBJDUMP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objdump", "RANLIB": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-llvm-ranlib", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "SIZE": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-size", "STRINGS": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strings", "STRIP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strip", @@ -1143,7 +1143,7 @@ "OBJCOPY": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objcopy", "OBJDUMP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-objdump", "RANLIB": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-llvm-ranlib", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "SIZE": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-size", "STRINGS": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strings", "STRIP": "/opt/llvm-mingw-linux/bin/aarch64-w64-mingw32-strip", @@ -2055,7 +2055,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "aarch64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate", "XZ_OPT": "-9" } @@ -2118,6 +2118,7 @@ "BUILD_FLAVOUR": "validate", "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check", "CONFIGURE_WRAPPER": "emconfigure", + "CROSS_STAGE": "2", "CROSS_TARGET": "javascript-unknown-ghcjs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "RUNTEST_ARGS": "", @@ -2502,7 +2503,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "riscv64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate", "XZ_OPT": "-9" } @@ -3581,7 +3582,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "loongarch64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-ubuntu24_04-loongarch-cross_loongarch64-linux-gnu-validate", "XZ_OPT": "-9" } @@ -6228,7 +6229,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "aarch64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate" } }, @@ -6290,6 +6291,7 @@ "BUILD_FLAVOUR": "validate", "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check", "CONFIGURE_WRAPPER": "emconfigure", + "CROSS_STAGE": "2", "CROSS_TARGET": "javascript-unknown-ghcjs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "RUNTEST_ARGS": "", @@ -6669,7 +6671,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "riscv64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate" } }, @@ -7732,7 +7734,7 @@ "CROSS_STAGE": "2", "CROSS_TARGET": "loongarch64-linux-gnu", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "RUNTEST_ARGS": "", + "RUNTEST_ARGS": "-e config.timeout=900", "TEST_ENV": "x86_64-linux-ubuntu24_04-loongarch-cross_loongarch64-linux-gnu-validate" } }, ===================================== ghc/GHC/Driver/Session/Mode.hs ===================================== @@ -132,7 +132,7 @@ isDoEvalMode :: Mode -> Bool isDoEvalMode (Right (Right (DoEval _))) = True isDoEvalMode _ = False -#if defined(HAVE_INTERNAL_INTERPRETER) +#if defined(HAVE_INTERPRETER) isInteractiveMode :: PostLoadMode -> Bool isInteractiveMode DoInteractive = True isInteractiveMode _ = False ===================================== ghc/GHCi/UI.hs ===================================== @@ -1900,7 +1900,9 @@ changeDirectory dir = do fhv <- compileGHCiExpr $ "System.Directory.setCurrentDirectory " ++ show dir' liftIO $ evalIO interp fhv +#if defined(HAVE_INTERNAL_INTERPRETER) _ -> pure () +#endif trySuccess :: GhciMonad m => m SuccessFlag -> m SuccessFlag trySuccess act = ===================================== ghc/Main.hs ===================================== @@ -35,7 +35,7 @@ import GHC.Driver.Config.Diagnostic import GHC.Platform import GHC.Platform.Host -#if defined(HAVE_INTERNAL_INTERPRETER) +#if defined(HAVE_INTERPRETER) import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings ) #endif @@ -287,7 +287,7 @@ doRun units srcs args = do args' = drop 1 $ dropWhile (/= "--") $ map unLoc args ghciUI :: [String] -> [(FilePath, Maybe Phase)] -> Maybe [String] -> Ghc () -#if !defined(HAVE_INTERNAL_INTERPRETER) +#if !defined(HAVE_INTERPRETER) ghciUI _ _ _ = throwGhcException (CmdLineError "not built for interactive use") #else @@ -331,7 +331,7 @@ showBanner :: PostLoadMode -> DynFlags -> IO () showBanner _postLoadMode dflags = do let verb = verbosity dflags -#if defined(HAVE_INTERNAL_INTERPRETER) +#if defined(HAVE_INTERPRETER) -- Show the GHCi banner when (isInteractiveMode _postLoadMode && verb >= 1) $ putStrLn ghciWelcomeMsg #endif ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -22,6 +22,11 @@ Flag internal-interpreter Default: False Manual: True +Flag interpreter + Description: Build with interpreter support, both internal and external. + Default: False + Manual: True + Flag threaded Description: Link the ghc executable against the threaded RTS Default: True @@ -56,7 +61,7 @@ Executable ghc -rtsopts=all "-with-rtsopts=-K512M -H -I5 -T" - if flag(internal-interpreter) + if flag(interpreter) -- NB: this is never built by the bootstrapping GHC+libraries Build-depends: deepseq >= 1.4 && < 1.6, @@ -65,7 +70,7 @@ Executable ghc haskeline == 0.8.*, exceptions == 0.10.*, time >= 1.8 && < 1.16 - CPP-Options: -DHAVE_INTERNAL_INTERPRETER + CPP-Options: -DHAVE_INTERPRETER Other-Modules: GHCi.Leak GHCi.UI @@ -82,6 +87,9 @@ Executable ghc UnboxedTuples ViewPatterns + if flag(internal-interpreter) + CPP-Options: -DHAVE_INTERNAL_INTERPRETER + if flag(threaded) ghc-options: -threaded ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -88,11 +88,10 @@ packageArgs = do -- 1. ghcWithInterpreter must be True ("Use interpreter" = -- "YES") -- 2. For non-cross case it can be enabled - -- 3. For cross case, disable for stage0 since that runs - -- on the host and must rely on external interpreter to - -- load target code, otherwise enable for stage1 since - -- that runs on the target and can use target's own - -- ghci object linker + -- 3. For cross case, disable for stage0 and stage1 since these run + -- on the host and must rely on external interpreter to load + -- target code, otherwise enable for stage2 since that runs on + -- the target and can use target's own ghci object linker [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage2]] `cabalFlag` "internal-interpreter" , orM [ notM cross, haveCurses ] `cabalFlag` "terminfo" , arg "-build-tool-depends" @@ -115,7 +114,8 @@ packageArgs = do , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ] , builder (Cabal Flags) ? mconcat - [ (expr (ghcWithInterpreter stage)) `cabalFlag` "internal-interpreter" + [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage1]] `cabalFlag` "interpreter" + , andM [expr (ghcWithInterpreter stage), notM (expr cross)] `cabalFlag` "internal-interpreter" , ifM stage0 -- We build a threaded stage 1 if the bootstrapping compiler -- supports it. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c88f0d8c82558f06f4b12470b6a939… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c88f0d8c82558f06f4b12470b6a939… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/jeltsch/known-key-removals/lists] 13 commits: rts: workaround -Werror=maybe-uninitialized false positives
by Wolfgang Jeltsch (@jeltsch) 22 Dec '25

22 Dec '25
Wolfgang Jeltsch pushed to branch wip/jeltsch/known-key-removals/lists at Glasgow Haskell Compiler / GHC Commits: 224446a2 by Cheng Shao at 2025-12-20T07:49:54-05:00 rts: workaround -Werror=maybe-uninitialized false positives In some cases gcc might report -Werror=maybe-uninitialized that we know are false positives, but need to workaround it to make validate builds with -Werror pass. - - - - - 251ec087 by Cheng Shao at 2025-12-20T07:49:54-05:00 hadrian: use -Og as C/C++ optimization level when debugging This commit enables -Og as optimization level when compiling the debug ways of rts. According to gcc documentation (https://gcc.gnu.org/onlinedocs/gcc/Optimize-Options.html#index-Og) -Og is a better choice than -O0 for producing debuggable code. It's also supported by clang as well, so it makes sense to use it as a default for debugging. Also add missing -g3 flag to C++ compilation flags in +debug_info flavour transformer. - - - - - fb586c67 by Cheng Shao at 2025-12-20T07:50:36-05:00 compiler: replace DList with OrdList This patch removes `DList` logic from the compiler and replaces it with `OrdList` which also supports O(1) concatenation and should be more memory efficient than the church-encoded `DList`. - - - - - 8149c987 by Cheng Shao at 2025-12-20T17:06:51-05:00 hadrian: add with_profiled_libs flavour transformer This patch adds a `with_profiled_libs` flavour transformer to hadrian which is the exact opposite of `no_profiled_libs`. It adds profiling ways to stage1+ rts/library ways, and doesn't alter other flavour settings. It is useful when needing to test profiling logic locally with a quick flavour. - - - - - 746b18cd by Cheng Shao at 2025-12-20T17:06:51-05:00 hadrian: fix missing profiled dynamic libraries in profiled_ghc This commit fixes the profiled_ghc flavour transformer to include profiled dynamic libraries as well, since they're supported by GHC since !12595. - - - - - 4dd7e3b9 by Cheng Shao at 2025-12-20T17:07:33-05:00 ci: set http.postBuffer to mitigate perf notes timeout on some runners This patch sets http.postBuffer to mitigate the timeout when fetching perf notes on some runners with slow internet connection. Fixes #26684. - - - - - bc36268a by Wolfgang Jeltsch at 2025-12-21T16:23:24-05:00 Remove unused known keys and names for type representations This removes the known-key and corresponding name variables for `TrName`, `TrNameD`, `TypeRep`, `KindRepTypeLitD`, `TypeLitSort`, and `mkTrType`, as they are apparently nowhere used in GHC’s source code. - - - - - ff5050e9 by Wolfgang Jeltsch at 2025-12-21T16:24:04-05:00 Remove unused known keys and names for natural operations This removes the known-key and corresponding name variables for `naturalAndNot`, `naturalLog2`, `naturalLogBaseWord`, `naturalLogBase`, `naturalPowMod`, `naturalSizeInBase`, `naturalToFloat`, and `naturalToDouble`, as they are apparently nowhere used in GHC’s source code. - - - - - 424388c2 by Wolfgang Jeltsch at 2025-12-21T16:24:45-05:00 Remove the unused known key and name for `Fingerprint` This removes the variables for the known key and the name of the `Fingerprint` data constructor, as they are apparently nowhere used in GHC’s source code. - - - - - a1ed86fe by Wolfgang Jeltsch at 2025-12-21T16:25:26-05:00 Remove the unused known key and name for `failIO` This removes the variables for the known key and the name of the `failIO` operation, as they are apparently nowhere used in GHC’s source code. - - - - - b8220daf by Wolfgang Jeltsch at 2025-12-21T16:26:07-05:00 Remove the unused known key and name for `liftM` This removes the variables for the known key and the name of the `liftM` operation, as they are apparently nowhere used in GHC’s source code. - - - - - eb0628b1 by Wolfgang Jeltsch at 2025-12-21T16:26:47-05:00 Fix the documentation of `hIsClosed` - - - - - 50804ce7 by Wolfgang Jeltsch at 2025-12-22T15:26:18+02:00 Remove unused known keys and names for list operations This removes the known-key and corresponding name variables for `concat`, `filter`, `zip`, and `(++)`, as they are apparently nowhere used in GHC’s source code. - - - - - 12 changed files: - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Parser/String.hs - compiler/GHC/StgToCmm/InfoTableProv.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Settings/Packages.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs - rts/linker/InitFini.c - rts/sm/Sanity.c - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr Changes: ===================================== .gitlab/ci.sh ===================================== @@ -265,6 +265,15 @@ function setup() { # testsuite driver! git config gc.auto 0 + # Some runners still choke at the perf note fetch step, which has to + # do with slow internet connection, see + # https://docs.gitlab.com/topics/git/troubleshooting_git/#error-stream-0-was-… + # for the http.postBuffer mitigation. It might seem + # counter-intuitive that "post buffer" helps with fetching, but git + # indeed issues post requests when fetching over https, it's a + # bidirectional negotiation with the remote. + git config http.postBuffer 52428800 + info "=====================================================" info "Toolchain versions" info "=====================================================" ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -222,12 +222,11 @@ basicKnownKeyNames -- Type representation types trModuleTyConName, trModuleDataConName, - trNameTyConName, trNameSDataConName, trNameDDataConName, + trNameSDataConName, trTyConTyConName, trTyConDataConName, -- Typeable typeableClassName, - typeRepTyConName, someTypeRepTyConName, someTypeRepDataConName, kindRepTyConName, @@ -237,13 +236,10 @@ basicKnownKeyNames kindRepFunDataConName, kindRepTYPEDataConName, kindRepTypeLitSDataConName, - kindRepTypeLitDDataConName, - typeLitSortTyConName, typeLitSymbolDataConName, typeLitNatDataConName, typeLitCharDataConName, typeRepIdName, - mkTrTypeName, mkTrConName, mkTrAppCheckedName, mkTrFunName, @@ -296,7 +292,7 @@ basicKnownKeyNames fmapName, -- Monad stuff - thenIOName, bindIOName, returnIOName, failIOName, bindMName, thenMName, + thenIOName, bindIOName, returnIOName, bindMName, thenMName, returnMName, joinMName, -- MonadFail @@ -343,8 +339,7 @@ basicKnownKeyNames getFieldName, setFieldName, -- List operations - concatName, filterName, mapName, - zipName, foldrName, buildName, augmentName, appendName, + mapName, foldrName, buildName, augmentName, -- FFI primitive types that are not wired-in. stablePtrTyConName, ptrTyConName, funPtrTyConName, constPtrConName, @@ -409,26 +404,18 @@ basicKnownKeyNames naturalQuotName, naturalRemName, naturalAndName, - naturalAndNotName, naturalOrName, naturalXorName, naturalTestBitName, naturalBitName, naturalGcdName, naturalLcmName, - naturalLog2Name, - naturalLogBaseWordName, - naturalLogBaseName, - naturalPowModName, - naturalSizeInBaseName, bignatEqName, -- Float/Double integerToFloatName, integerToDoubleName, - naturalToFloatName, - naturalToDoubleName, rationalToFloatName, rationalToDoubleName, @@ -479,7 +466,6 @@ basicKnownKeyNames -- Monad comprehensions , guardMName - , liftMName , mzipName -- GHCi Sandbox @@ -491,9 +477,6 @@ basicKnownKeyNames , staticPtrDataConName, staticPtrInfoDataConName , fromStaticPtrName - -- Fingerprint - , fingerprintDataConName - -- Custom type errors , errorMessageTypeErrorFamName , typeErrorTextDataConName @@ -710,9 +693,8 @@ ltTag_RDR = nameRdrName ordLTDataConName eqTag_RDR = nameRdrName ordEQDataConName gtTag_RDR = nameRdrName ordGTDataConName -map_RDR, append_RDR :: RdrName +map_RDR :: RdrName map_RDR = nameRdrName mapName -append_RDR = nameRdrName appendName foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR :: RdrName @@ -1084,7 +1066,7 @@ considerAccessibleName = varQual gHC_INTERNAL_EXTS (fsLit "considerAccessible") -- Random GHC.Internal.Base functions fromStringName, otherwiseIdName, foldrName, buildName, augmentName, - mapName, appendName, assertName, + mapName, assertName, dollarName :: Name dollarName = varQual gHC_INTERNAL_BASE (fsLit "$") dollarIdKey otherwiseIdName = varQual gHC_INTERNAL_BASE (fsLit "otherwise") otherwiseIdKey @@ -1092,7 +1074,6 @@ foldrName = varQual gHC_INTERNAL_BASE (fsLit "foldr") foldrIdKey buildName = varQual gHC_INTERNAL_BASE (fsLit "build") buildIdKey augmentName = varQual gHC_INTERNAL_BASE (fsLit "augment") augmentIdKey mapName = varQual gHC_INTERNAL_BASE (fsLit "map") mapIdKey -appendName = varQual gHC_INTERNAL_BASE (fsLit "++") appendIdKey assertName = varQual gHC_INTERNAL_BASE (fsLit "assert") assertIdKey fromStringName = varQual gHC_INTERNAL_DATA_STRING (fsLit "fromString") fromStringClassOpKey @@ -1154,18 +1135,12 @@ integerFromNaturalName , naturalQuotName , naturalRemName , naturalAndName - , naturalAndNotName , naturalOrName , naturalXorName , naturalTestBitName , naturalBitName , naturalGcdName , naturalLcmName - , naturalLog2Name - , naturalLogBaseWordName - , naturalLogBaseName - , naturalPowModName - , naturalSizeInBaseName , bignatEqName , bignatCompareName , bignatCompareWordName @@ -1194,18 +1169,12 @@ naturalQuotRemName = bnnVarQual "naturalQuotRem#" naturalQuotRe naturalQuotName = bnnVarQual "naturalQuot" naturalQuotIdKey naturalRemName = bnnVarQual "naturalRem" naturalRemIdKey naturalAndName = bnnVarQual "naturalAnd" naturalAndIdKey -naturalAndNotName = bnnVarQual "naturalAndNot" naturalAndNotIdKey naturalOrName = bnnVarQual "naturalOr" naturalOrIdKey naturalXorName = bnnVarQual "naturalXor" naturalXorIdKey naturalTestBitName = bnnVarQual "naturalTestBit#" naturalTestBitIdKey naturalBitName = bnnVarQual "naturalBit#" naturalBitIdKey naturalGcdName = bnnVarQual "naturalGcd" naturalGcdIdKey naturalLcmName = bnnVarQual "naturalLcm" naturalLcmIdKey -naturalLog2Name = bnnVarQual "naturalLog2#" naturalLog2IdKey -naturalLogBaseWordName = bnnVarQual "naturalLogBaseWord#" naturalLogBaseWordIdKey -naturalLogBaseName = bnnVarQual "naturalLogBase#" naturalLogBaseIdKey -naturalPowModName = bnnVarQual "naturalPowMod" naturalPowModIdKey -naturalSizeInBaseName = bnnVarQual "naturalSizeInBase#" naturalSizeInBaseIdKey integerFromNaturalName = bniVarQual "integerFromNatural" integerFromNaturalIdKey integerToNaturalClampName = bniVarQual "integerToNaturalClamp" integerToNaturalClampIdKey @@ -1276,12 +1245,9 @@ realFloatClassName = clsQual gHC_INTERNAL_FLOAT (fsLit "RealFloat") realFloatCla -- other GHC.Internal.Float functions integerToFloatName, integerToDoubleName, - naturalToFloatName, naturalToDoubleName, rationalToFloatName, rationalToDoubleName :: Name integerToFloatName = varQual gHC_INTERNAL_FLOAT (fsLit "integerToFloat#") integerToFloatIdKey integerToDoubleName = varQual gHC_INTERNAL_FLOAT (fsLit "integerToDouble#") integerToDoubleIdKey -naturalToFloatName = varQual gHC_INTERNAL_FLOAT (fsLit "naturalToFloat#") naturalToFloatIdKey -naturalToDoubleName = varQual gHC_INTERNAL_FLOAT (fsLit "naturalToDouble#") naturalToDoubleIdKey rationalToFloatName = varQual gHC_INTERNAL_FLOAT (fsLit "rationalToFloat") rationalToFloatIdKey rationalToDoubleName = varQual gHC_INTERNAL_FLOAT (fsLit "rationalToDouble") rationalToDoubleIdKey @@ -1292,17 +1258,13 @@ ixClassName = clsQual gHC_INTERNAL_IX (fsLit "Ix") ixClassKey -- Typeable representation types trModuleTyConName , trModuleDataConName - , trNameTyConName , trNameSDataConName - , trNameDDataConName , trTyConTyConName , trTyConDataConName :: Name trModuleTyConName = tcQual gHC_TYPES (fsLit "Module") trModuleTyConKey trModuleDataConName = dcQual gHC_TYPES (fsLit "Module") trModuleDataConKey -trNameTyConName = tcQual gHC_TYPES (fsLit "TrName") trNameTyConKey trNameSDataConName = dcQual gHC_TYPES (fsLit "TrNameS") trNameSDataConKey -trNameDDataConName = dcQual gHC_TYPES (fsLit "TrNameD") trNameDDataConKey trTyConTyConName = tcQual gHC_TYPES (fsLit "TyCon") trTyConTyConKey trTyConDataConName = dcQual gHC_TYPES (fsLit "TyCon") trTyConDataConKey @@ -1313,7 +1275,6 @@ kindRepTyConName , kindRepFunDataConName , kindRepTYPEDataConName , kindRepTypeLitSDataConName - , kindRepTypeLitDDataConName :: Name kindRepTyConName = tcQual gHC_TYPES (fsLit "KindRep") kindRepTyConKey kindRepTyConAppDataConName = dcQual gHC_TYPES (fsLit "KindRepTyConApp") kindRepTyConAppDataConKey @@ -1322,24 +1283,19 @@ kindRepAppDataConName = dcQual gHC_TYPES (fsLit "KindRepApp") kindR kindRepFunDataConName = dcQual gHC_TYPES (fsLit "KindRepFun") kindRepFunDataConKey kindRepTYPEDataConName = dcQual gHC_TYPES (fsLit "KindRepTYPE") kindRepTYPEDataConKey kindRepTypeLitSDataConName = dcQual gHC_TYPES (fsLit "KindRepTypeLitS") kindRepTypeLitSDataConKey -kindRepTypeLitDDataConName = dcQual gHC_TYPES (fsLit "KindRepTypeLitD") kindRepTypeLitDDataConKey -typeLitSortTyConName - , typeLitSymbolDataConName +typeLitSymbolDataConName , typeLitNatDataConName , typeLitCharDataConName :: Name -typeLitSortTyConName = tcQual gHC_TYPES (fsLit "TypeLitSort") typeLitSortTyConKey typeLitSymbolDataConName = dcQual gHC_TYPES (fsLit "TypeLitSymbol") typeLitSymbolDataConKey typeLitNatDataConName = dcQual gHC_TYPES (fsLit "TypeLitNat") typeLitNatDataConKey typeLitCharDataConName = dcQual gHC_TYPES (fsLit "TypeLitChar") typeLitCharDataConKey -- Class Typeable, and functions for constructing `Typeable` dictionaries typeableClassName - , typeRepTyConName , someTypeRepTyConName , someTypeRepDataConName - , mkTrTypeName , mkTrConName , mkTrAppCheckedName , mkTrFunName @@ -1350,11 +1306,9 @@ typeableClassName , trGhcPrimModuleName :: Name typeableClassName = clsQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "Typeable") typeableClassKey -typeRepTyConName = tcQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "TypeRep") typeRepTyConKey someTypeRepTyConName = tcQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "SomeTypeRep") someTypeRepTyConKey someTypeRepDataConName = dcQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "SomeTypeRep") someTypeRepDataConKey typeRepIdName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "typeRep#") typeRepIdKey -mkTrTypeName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrType") mkTrTypeKey mkTrConName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrCon") mkTrConKey mkTrAppCheckedName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrAppChecked") mkTrAppCheckedKey mkTrFunName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrFun") mkTrFunKey @@ -1452,12 +1406,6 @@ enumFromThenName = varQual gHC_INTERNAL_ENUM (fsLit "enumFromThen") enumFrom enumFromThenToName = varQual gHC_INTERNAL_ENUM (fsLit "enumFromThenTo") enumFromThenToClassOpKey boundedClassName = clsQual gHC_INTERNAL_ENUM (fsLit "Bounded") boundedClassKey --- List functions -concatName, filterName, zipName :: Name -concatName = varQual gHC_INTERNAL_LIST (fsLit "concat") concatIdKey -filterName = varQual gHC_INTERNAL_LIST (fsLit "filter") filterIdKey -zipName = varQual gHC_INTERNAL_LIST (fsLit "zip") zipIdKey - -- Overloaded lists isListClassName, fromListName, fromListNName, toListName :: Name isListClassName = clsQual gHC_INTERNAL_IS_LIST (fsLit "IsList") isListClassKey @@ -1493,13 +1441,12 @@ ghciStepIoMName = varQual gHC_INTERNAL_GHCI (fsLit "ghciStepIO") ghciStepIoMClas -- IO things ioTyConName, ioDataConName, - thenIOName, bindIOName, returnIOName, failIOName :: Name + thenIOName, bindIOName, returnIOName :: Name ioTyConName = tcQual gHC_TYPES (fsLit "IO") ioTyConKey ioDataConName = dcQual gHC_TYPES (fsLit "IO") ioDataConKey thenIOName = varQual gHC_INTERNAL_BASE (fsLit "thenIO") thenIOIdKey bindIOName = varQual gHC_INTERNAL_BASE (fsLit "bindIO") bindIOIdKey returnIOName = varQual gHC_INTERNAL_BASE (fsLit "returnIO") returnIOIdKey -failIOName = varQual gHC_INTERNAL_IO (fsLit "failIO") failIOIdKey -- IO things printName :: Name @@ -1544,9 +1491,8 @@ choiceAName = varQual gHC_INTERNAL_ARROW (fsLit "|||") choiceAIdKey loopAName = varQual gHC_INTERNAL_ARROW (fsLit "loop") loopAIdKey -- Monad comprehensions -guardMName, liftMName, mzipName :: Name +guardMName, mzipName :: Name guardMName = varQual gHC_INTERNAL_MONAD (fsLit "guard") guardMIdKey -liftMName = varQual gHC_INTERNAL_MONAD (fsLit "liftM") liftMIdKey mzipName = varQual gHC_INTERNAL_CONTROL_MONAD_ZIP (fsLit "mzip") mzipIdKey @@ -1634,10 +1580,6 @@ fromStaticPtrName :: Name fromStaticPtrName = varQual gHC_INTERNAL_STATICPTR (fsLit "fromStaticPtr") fromStaticPtrClassOpKey -fingerprintDataConName :: Name -fingerprintDataConName = - dcQual gHC_INTERNAL_FINGERPRINT_TYPE (fsLit "Fingerprint") fingerprintDataConKey - constPtrConName :: Name constPtrConName = tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey @@ -1915,13 +1857,11 @@ pluginTyConKey, frontendPluginTyConKey :: Unique pluginTyConKey = mkPreludeTyConUnique 102 frontendPluginTyConKey = mkPreludeTyConUnique 103 -trTyConTyConKey, trModuleTyConKey, trNameTyConKey, - kindRepTyConKey, typeLitSortTyConKey :: Unique +trTyConTyConKey, trModuleTyConKey, + kindRepTyConKey :: Unique trTyConTyConKey = mkPreludeTyConUnique 104 trModuleTyConKey = mkPreludeTyConUnique 105 -trNameTyConKey = mkPreludeTyConUnique 106 kindRepTyConKey = mkPreludeTyConUnique 107 -typeLitSortTyConKey = mkPreludeTyConUnique 108 -- Generics (Unique keys) v1TyConKey, u1TyConKey, par1TyConKey, rec1TyConKey, @@ -1990,8 +1930,7 @@ callStackTyConKey :: Unique callStackTyConKey = mkPreludeTyConUnique 191 -- Typeables -typeRepTyConKey, someTypeRepTyConKey, someTypeRepDataConKey :: Unique -typeRepTyConKey = mkPreludeTyConUnique 192 +someTypeRepTyConKey, someTypeRepDataConKey :: Unique someTypeRepTyConKey = mkPreludeTyConUnique 193 someTypeRepDataConKey = mkPreludeTyConUnique 194 @@ -2123,19 +2062,15 @@ staticPtrDataConKey = mkPreludeDataConUnique 33 staticPtrInfoDataConKey :: Unique staticPtrInfoDataConKey = mkPreludeDataConUnique 34 -fingerprintDataConKey :: Unique -fingerprintDataConKey = mkPreludeDataConUnique 35 - srcLocDataConKey :: Unique srcLocDataConKey = mkPreludeDataConUnique 37 trTyConDataConKey, trModuleDataConKey, - trNameSDataConKey, trNameDDataConKey, + trNameSDataConKey, trGhcPrimModuleKey :: Unique trTyConDataConKey = mkPreludeDataConUnique 41 trModuleDataConKey = mkPreludeDataConUnique 43 trNameSDataConKey = mkPreludeDataConUnique 45 -trNameDDataConKey = mkPreludeDataConUnique 46 trGhcPrimModuleKey = mkPreludeDataConUnique 47 typeErrorTextDataConKey, @@ -2210,7 +2145,7 @@ vecElemDataConKeys = map mkPreludeDataConUnique [96..105] -- Typeable things kindRepTyConAppDataConKey, kindRepVarDataConKey, kindRepAppDataConKey, kindRepFunDataConKey, kindRepTYPEDataConKey, - kindRepTypeLitSDataConKey, kindRepTypeLitDDataConKey + kindRepTypeLitSDataConKey :: Unique kindRepTyConAppDataConKey = mkPreludeDataConUnique 106 kindRepVarDataConKey = mkPreludeDataConUnique 107 @@ -2218,7 +2153,6 @@ kindRepAppDataConKey = mkPreludeDataConUnique 108 kindRepFunDataConKey = mkPreludeDataConUnique 109 kindRepTYPEDataConKey = mkPreludeDataConUnique 110 kindRepTypeLitSDataConKey = mkPreludeDataConUnique 111 -kindRepTypeLitDDataConKey = mkPreludeDataConUnique 112 typeLitSymbolDataConKey, typeLitNatDataConKey, typeLitCharDataConKey :: Unique typeLitSymbolDataConKey = mkPreludeDataConUnique 113 @@ -2258,7 +2192,7 @@ naturalNBDataConKey = mkPreludeDataConUnique 124 ************************************************************************ -} -wildCardKey, absentErrorIdKey, absentConstraintErrorIdKey, augmentIdKey, appendIdKey, +wildCardKey, absentErrorIdKey, absentConstraintErrorIdKey, augmentIdKey, buildIdKey, foldrIdKey, recSelErrorIdKey, seqIdKey, eqStringIdKey, noMethodBindingErrorIdKey, nonExhaustiveGuardsErrorIdKey, @@ -2275,7 +2209,6 @@ wildCardKey = mkPreludeMiscIdUnique 0 -- See Note [WildCard absentErrorIdKey = mkPreludeMiscIdUnique 1 absentConstraintErrorIdKey = mkPreludeMiscIdUnique 2 augmentIdKey = mkPreludeMiscIdUnique 3 -appendIdKey = mkPreludeMiscIdUnique 4 buildIdKey = mkPreludeMiscIdUnique 5 foldrIdKey = mkPreludeMiscIdUnique 6 recSelErrorIdKey = mkPreludeMiscIdUnique 7 @@ -2304,18 +2237,13 @@ divIntIdKey = mkPreludeMiscIdUnique 26 modIntIdKey = mkPreludeMiscIdUnique 27 cstringLengthIdKey = mkPreludeMiscIdUnique 28 -concatIdKey, filterIdKey, zipIdKey, - bindIOIdKey, returnIOIdKey, newStablePtrIdKey, - printIdKey, failIOIdKey, nullAddrIdKey, voidArgIdKey, +bindIOIdKey, returnIOIdKey, newStablePtrIdKey, + printIdKey, nullAddrIdKey, voidArgIdKey, otherwiseIdKey, assertIdKey :: Unique -concatIdKey = mkPreludeMiscIdUnique 31 -filterIdKey = mkPreludeMiscIdUnique 32 -zipIdKey = mkPreludeMiscIdUnique 33 bindIOIdKey = mkPreludeMiscIdUnique 34 returnIOIdKey = mkPreludeMiscIdUnique 35 newStablePtrIdKey = mkPreludeMiscIdUnique 36 printIdKey = mkPreludeMiscIdUnique 37 -failIOIdKey = mkPreludeMiscIdUnique 38 nullAddrIdKey = mkPreludeMiscIdUnique 39 voidArgIdKey = mkPreludeMiscIdUnique 40 otherwiseIdKey = mkPreludeMiscIdUnique 43 @@ -2354,11 +2282,9 @@ considerAccessibleIdKey = mkPreludeMiscIdUnique 125 noinlineIdKey = mkPreludeMiscIdUnique 126 noinlineConstraintIdKey = mkPreludeMiscIdUnique 127 -integerToFloatIdKey, integerToDoubleIdKey, naturalToFloatIdKey, naturalToDoubleIdKey :: Unique +integerToFloatIdKey, integerToDoubleIdKey :: Unique integerToFloatIdKey = mkPreludeMiscIdUnique 128 integerToDoubleIdKey = mkPreludeMiscIdUnique 129 -naturalToFloatIdKey = mkPreludeMiscIdUnique 130 -naturalToDoubleIdKey = mkPreludeMiscIdUnique 131 rationalToFloatIdKey, rationalToDoubleIdKey :: Unique rationalToFloatIdKey = mkPreludeMiscIdUnique 132 @@ -2436,9 +2362,8 @@ toIntegerClassOpKey = mkPreludeMiscIdUnique 192 toRationalClassOpKey = mkPreludeMiscIdUnique 193 -- Monad comprehensions -guardMIdKey, liftMIdKey, mzipIdKey :: Unique +guardMIdKey, mzipIdKey :: Unique guardMIdKey = mkPreludeMiscIdUnique 194 -liftMIdKey = mkPreludeMiscIdUnique 195 mzipIdKey = mkPreludeMiscIdUnique 196 -- GHCi @@ -2461,7 +2386,6 @@ proxyHashKey = mkPreludeMiscIdUnique 502 -- Used to make `Typeable` dictionaries mkTyConKey - , mkTrTypeKey , mkTrConKey , mkTrAppCheckedKey , mkTrFunKey @@ -2471,7 +2395,6 @@ mkTyConKey , typeRepIdKey :: Unique mkTyConKey = mkPreludeMiscIdUnique 503 -mkTrTypeKey = mkPreludeMiscIdUnique 504 mkTrConKey = mkPreludeMiscIdUnique 505 mkTrAppCheckedKey = mkPreludeMiscIdUnique 506 typeNatTypeRepKey = mkPreludeMiscIdUnique 507 @@ -2584,18 +2507,12 @@ integerFromNaturalIdKey , naturalQuotIdKey , naturalRemIdKey , naturalAndIdKey - , naturalAndNotIdKey , naturalOrIdKey , naturalXorIdKey , naturalTestBitIdKey , naturalBitIdKey , naturalGcdIdKey , naturalLcmIdKey - , naturalLog2IdKey - , naturalLogBaseWordIdKey - , naturalLogBaseIdKey - , naturalPowModIdKey - , naturalSizeInBaseIdKey , bignatEqIdKey , bignatCompareIdKey , bignatCompareWordIdKey @@ -2650,18 +2567,12 @@ naturalQuotRemIdKey = mkPreludeMiscIdUnique 669 naturalQuotIdKey = mkPreludeMiscIdUnique 670 naturalRemIdKey = mkPreludeMiscIdUnique 671 naturalAndIdKey = mkPreludeMiscIdUnique 672 -naturalAndNotIdKey = mkPreludeMiscIdUnique 673 naturalOrIdKey = mkPreludeMiscIdUnique 674 naturalXorIdKey = mkPreludeMiscIdUnique 675 naturalTestBitIdKey = mkPreludeMiscIdUnique 676 naturalBitIdKey = mkPreludeMiscIdUnique 677 naturalGcdIdKey = mkPreludeMiscIdUnique 678 naturalLcmIdKey = mkPreludeMiscIdUnique 679 -naturalLog2IdKey = mkPreludeMiscIdUnique 680 -naturalLogBaseWordIdKey = mkPreludeMiscIdUnique 681 -naturalLogBaseIdKey = mkPreludeMiscIdUnique 682 -naturalPowModIdKey = mkPreludeMiscIdUnique 683 -naturalSizeInBaseIdKey = mkPreludeMiscIdUnique 684 bignatEqIdKey = mkPreludeMiscIdUnique 691 bignatCompareIdKey = mkPreludeMiscIdUnique 692 ===================================== compiler/GHC/Parser/String.hs ===================================== @@ -19,6 +19,7 @@ import Data.Char (chr, ord) import qualified Data.Foldable1 as Foldable1 import qualified Data.List.NonEmpty as NonEmpty import Data.Maybe (listToMaybe, mapMaybe) +import GHC.Data.OrdList (fromOL, nilOL, snocOL) import GHC.Data.StringBuffer (StringBuffer) import qualified GHC.Data.StringBuffer as StringBuffer import GHC.Parser.CharClass ( @@ -167,16 +168,16 @@ collapseGaps = go [] -> panic "gap unexpectedly ended" resolveEscapes :: HasChar c => [c] -> Either (c, LexErr) [c] -resolveEscapes = go dlistEmpty +resolveEscapes = go nilOL where go !acc = \case - [] -> pure $ dlistToList acc + [] -> pure $ fromOL acc Char '\\' : Char '&' : cs -> go acc cs backslash@(Char '\\') : cs -> case resolveEscapeChar cs of - Right (esc, cs') -> go (acc `dlistSnoc` setChar esc backslash) cs' + Right (esc, cs') -> go (acc `snocOL` setChar esc backslash) cs' Left (c, e) -> Left (c, e) - c : cs -> go (acc `dlistSnoc` c) cs + c : cs -> go (acc `snocOL` c) cs -- ----------------------------------------------------------------------------- -- Escape characters @@ -420,17 +421,3 @@ It's more precisely defined with the following algorithm: * Lines with only whitespace characters 3. Calculate the longest prefix of whitespace shared by all lines in the remaining list -} - --- ----------------------------------------------------------------------------- --- DList - -newtype DList a = DList ([a] -> [a]) - -dlistEmpty :: DList a -dlistEmpty = DList id - -dlistToList :: DList a -> [a] -dlistToList (DList f) = f [] - -dlistSnoc :: DList a -> a -> DList a -dlistSnoc (DList f) x = DList (f . (x :)) ===================================== compiler/GHC/StgToCmm/InfoTableProv.hs ===================================== @@ -11,6 +11,7 @@ import GHC.IO (unsafePerformIO) #endif import Data.Char +import Data.Foldable import GHC.Prelude import GHC.Platform import GHC.Types.SrcLoc (pprUserRealSpan, srcSpanFile) @@ -18,6 +19,7 @@ import GHC.Types.Unique.DSM import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Data.FastString (fastStringToShortText, unpackFS, LexicalFastString(..)) +import GHC.Data.OrdList (OrdList, nilOL, snocOL) import GHC.Cmm import GHC.Cmm.CLabel @@ -286,7 +288,7 @@ data CgInfoProvEnt = CgInfoProvEnt , ipeSrcSpan :: !StrTabOffset } -data StringTable = StringTable { stStrings :: DList ShortText +data StringTable = StringTable { stStrings :: !(OrdList ShortText) , stLength :: !Int , stLookup :: !(M.Map ShortText StrTabOffset) } @@ -295,7 +297,7 @@ type StrTabOffset = Word32 emptyStringTable :: StringTable emptyStringTable = - StringTable { stStrings = emptyDList + StringTable { stStrings = nilOL , stLength = 0 , stLookup = M.empty } @@ -303,7 +305,7 @@ emptyStringTable = getStringTableStrings :: StringTable -> BS.ByteString getStringTableStrings st = BSL.toStrict $ BSB.toLazyByteString - $ foldMap f $ dlistToList (stStrings st) + $ foldMap' f $ stStrings st where f x = BSB.shortByteString (ST.contents x) `mappend` BSB.word8 0 @@ -312,7 +314,7 @@ lookupStringTable str = state $ \st -> case M.lookup str (stLookup st) of Just off -> (off, st) Nothing -> - let !st' = st { stStrings = stStrings st `snoc` str + let !st' = st { stStrings = stStrings st `snocOL` str , stLength = stLength st + ST.byteLength str + 1 , stLookup = M.insert str res (stLookup st) } @@ -359,14 +361,3 @@ foreign import ccall unsafe "ZSTD_compressBound" defaultCompressionLevel :: Int defaultCompressionLevel = 3 - -newtype DList a = DList ([a] -> [a]) - -emptyDList :: DList a -emptyDList = DList id - -snoc :: DList a -> a -> DList a -snoc (DList f) x = DList (f . (x:)) - -dlistToList :: DList a -> [a] -dlistToList (DList f) = f [] ===================================== hadrian/doc/flavours.md ===================================== @@ -249,10 +249,6 @@ The supported transformers are listed below: <tr> <td><code>profiled_ghc</code></td> <td>Build the GHC executable with cost-centre profiling support. - It is recommended that you use this in conjunction with `no_dynamic_ghc` since - GHC does not support loading of profiled libraries with the - dynamic linker. You should use a flavour that builds profiling libs and rts, - i.e. not <code>quick</code>. <br> This flag adds cost centres with the -fprof-late flag.</td> </tr> <tr> @@ -274,6 +270,10 @@ The supported transformers are listed below: <td><code>text_simdutf</code></td> <td>Enable building the <code>text</code> package with <code>simdutf</code> support.</td> </tr> + <tr> + <td><code>with_profiled_libs</code></td> + <td>Enables building of stage1+ libraries and the RTS in profiled build ways (the opposite of <code>no_profiled_libs</code>).</td> + </tr> <tr> <td><code>no_profiled_libs</code></td> <td>Disables building of libraries in profiled build ways.</td> ===================================== hadrian/src/Flavour.hs ===================================== @@ -15,6 +15,7 @@ module Flavour , enableProfiledGhc , disableDynamicGhcPrograms , disableDynamicLibs + , enableProfiledLibs , disableProfiledLibs , enableLinting , enableHaddock @@ -62,6 +63,7 @@ flavourTransformers = M.fromList , "no_dynamic_libs" =: disableDynamicLibs , "native_bignum" =: useNativeBignum , "text_simdutf" =: enableTextWithSIMDUTF + , "with_profiled_libs" =: enableProfiledLibs , "no_profiled_libs" =: disableProfiledLibs , "omit_pragmas" =: omitPragmas , "ipe" =: enableIPE @@ -169,6 +171,7 @@ enableDebugInfo :: Flavour -> Flavour enableDebugInfo = addArgs $ notStage0 ? mconcat [ builder (Ghc CompileHs) ? pure ["-g3"] , builder (Ghc CompileCWithGhc) ? pure ["-optc-g3"] + , builder (Ghc CompileCppWithGhc) ? pure ["-optcxx-g3"] , builder (Cc CompileC) ? arg "-g3" , builder (Cabal Setup) ? arg "--disable-library-stripping" , builder (Cabal Setup) ? arg "--disable-executable-stripping" @@ -307,29 +310,11 @@ enableUBSan = viaLlvmBackend :: Flavour -> Flavour viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm" --- | Build the GHC executable with profiling enabled in stages 2 and later. It --- is also recommended that you use this with @'dynamicGhcPrograms' = False@ --- since GHC does not support loading of profiled libraries with the --- dynamically-linker. +-- | Build the GHC executable with profiling enabled in stages 2 and +-- later. enableProfiledGhc :: Flavour -> Flavour enableProfiledGhc flavour = - enableLateCCS flavour - { rtsWays = do - ws <- rtsWays flavour - mconcat - [ pure ws - , buildingCompilerStage' (>= Stage2) ? pure (foldMap profiled_ways ws) - ] - , libraryWays = mconcat - [ libraryWays flavour - , buildingCompilerStage' (>= Stage2) ? pure (Set.singleton profiling) - ] - , ghcProfiled = (>= Stage2) - } - where - profiled_ways w - | wayUnit Dynamic w = Set.empty - | otherwise = Set.singleton (w <> profiling) + enableLateCCS $ enableProfiledLibs flavour { ghcProfiled = (>= Stage2) } -- | Disable 'dynamicGhcPrograms'. disableDynamicGhcPrograms :: Flavour -> Flavour @@ -346,6 +331,20 @@ disableDynamicLibs flavour = prune :: Ways -> Ways prune = fmap $ Set.filter (not . wayUnit Dynamic) +-- | Build libraries and the RTS in profiled ways (opposite of +-- 'disableProfiledLibs'). +enableProfiledLibs :: Flavour -> Flavour +enableProfiledLibs flavour = + flavour + { libraryWays = addProfilingWays $ libraryWays flavour, + rtsWays = addProfilingWays $ rtsWays flavour + } + where + addProfilingWays :: Ways -> Ways + addProfilingWays ways = do + ws <- ways + buildProfiled <- notStage0 + pure $ if buildProfiled then ws <> Set.map (<> profiling) ws else ws -- | Don't build libraries in profiled 'Way's. disableProfiledLibs :: Flavour -> Flavour ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -351,7 +351,7 @@ rtsPackageArgs = package rts ? do , Debug `wayUnit` way ? pure [ "-DDEBUG" , "-fno-omit-frame-pointer" , "-g3" - , "-O0" ] + , "-Og" ] -- Set the namespace for the rts fs functions , arg $ "-DFS_NAMESPACE=rts" ===================================== libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs ===================================== @@ -480,7 +480,7 @@ hIsOpen handle = SemiClosedHandle -> return False _ -> return True --- | @'hIsOpen' hdl@ returns whether the handle is closed. +-- | @'hIsClosed' hdl@ returns whether the handle is closed. -- If the 'haType' of @hdl@ is 'ClosedHandle' this returns 'True' -- and 'False' otherwise. hIsClosed :: Handle -> IO Bool ===================================== rts/linker/InitFini.c ===================================== @@ -75,7 +75,7 @@ static void sortInitFiniList(struct InitFiniList **slist, enum SortOrder order) while (*last != NULL && (*last)->next != NULL) { struct InitFiniList *s0 = *last; struct InitFiniList *s1 = s0->next; - bool flip; + bool flip = false; switch (order) { case INCREASING: flip = s0->priority > s1->priority; break; case DECREASING: flip = s0->priority < s1->priority; break; ===================================== rts/sm/Sanity.c ===================================== @@ -692,7 +692,7 @@ checkCompactObjects(bdescr *bd) ASSERT((W_)str == (W_)block + sizeof(StgCompactNFDataBlock)); StgWord totalW = 0; - StgCompactNFDataBlock *last; + StgCompactNFDataBlock *last = block; for ( ; block ; block = block->next) { last = block; ASSERT(block->owner == str); ===================================== testsuite/tests/typecheck/should_compile/holes.stderr ===================================== @@ -74,8 +74,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] putStrLn :: String -> IO () readFile :: FilePath -> IO String writeFile :: FilePath -> String -> IO () - (++) :: forall a. [a] -> [a] -> [a] - filter :: forall a. (a -> Bool) -> [a] -> [a] fromInteger :: forall a. Num a => Integer -> a (-) :: forall a. Num a => a -> a -> a fromRational :: forall a. Fractional a => Rational -> a @@ -87,6 +85,7 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] Nothing :: forall a. Maybe a Just :: forall a. a -> Maybe a [] :: forall a. [a] + (++) :: forall a. [a] -> [a] -> [a] asTypeOf :: forall a. a -> a -> a id :: forall a. a -> a until :: forall a. (a -> Bool) -> (a -> a) -> a -> a @@ -102,6 +101,7 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] [a] -> [a] drop :: forall a. Int -> [a] -> [a] dropWhile :: forall a. (a -> Bool) -> [a] -> [a] + filter :: forall a. (a -> Bool) -> [a] -> [a] head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => @@ -171,7 +171,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] quot :: forall a. Integral a => a -> a -> a quotRem :: forall a. Integral a => a -> a -> (a, a) rem :: forall a. Integral a => a -> a -> a - zip :: forall a b. [a] -> [b] -> [(a, b)] map :: forall a b. (a -> b) -> [a] -> [b] realToFrac :: forall a b. (Real a, Fractional b) => a -> b Left :: forall a b. a -> Either a b @@ -184,6 +183,7 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] scanl :: forall b a. (b -> a -> b) -> b -> [a] -> [b] scanr :: forall a b. (a -> b -> b) -> b -> [a] -> [b] unzip :: forall a b. [(a, b)] -> ([a], [b]) + zip :: forall a b. [a] -> [b] -> [(a, b)] (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a ceiling :: forall a b. (RealFrac a, Integral b) => a -> b floor :: forall a b. (RealFrac a, Integral b) => a -> b ===================================== testsuite/tests/typecheck/should_compile/holes3.stderr ===================================== @@ -77,8 +77,6 @@ holes3.hs:11:15: error: [GHC-88464] putStrLn :: String -> IO () readFile :: FilePath -> IO String writeFile :: FilePath -> String -> IO () - (++) :: forall a. [a] -> [a] -> [a] - filter :: forall a. (a -> Bool) -> [a] -> [a] fromInteger :: forall a. Num a => Integer -> a (-) :: forall a. Num a => a -> a -> a fromRational :: forall a. Fractional a => Rational -> a @@ -90,6 +88,7 @@ holes3.hs:11:15: error: [GHC-88464] Nothing :: forall a. Maybe a Just :: forall a. a -> Maybe a [] :: forall a. [a] + (++) :: forall a. [a] -> [a] -> [a] asTypeOf :: forall a. a -> a -> a id :: forall a. a -> a until :: forall a. (a -> Bool) -> (a -> a) -> a -> a @@ -105,6 +104,7 @@ holes3.hs:11:15: error: [GHC-88464] [a] -> [a] drop :: forall a. Int -> [a] -> [a] dropWhile :: forall a. (a -> Bool) -> [a] -> [a] + filter :: forall a. (a -> Bool) -> [a] -> [a] head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => @@ -174,7 +174,6 @@ holes3.hs:11:15: error: [GHC-88464] quot :: forall a. Integral a => a -> a -> a quotRem :: forall a. Integral a => a -> a -> (a, a) rem :: forall a. Integral a => a -> a -> a - zip :: forall a b. [a] -> [b] -> [(a, b)] map :: forall a b. (a -> b) -> [a] -> [b] realToFrac :: forall a b. (Real a, Fractional b) => a -> b Left :: forall a b. a -> Either a b @@ -187,6 +186,7 @@ holes3.hs:11:15: error: [GHC-88464] scanl :: forall b a. (b -> a -> b) -> b -> [a] -> [b] scanr :: forall a b. (a -> b -> b) -> b -> [a] -> [b] unzip :: forall a b. [(a, b)] -> ([a], [b]) + zip :: forall a b. [a] -> [b] -> [(a, b)] (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a ceiling :: forall a b. (RealFrac a, Integral b) => a -> b floor :: forall a b. (RealFrac a, Integral b) => a -> b View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22ad7992670f325c7f5fcc302534a9… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22ad7992670f325c7f5fcc302534a9… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/jeltsch/querying-newline-modes] Add an operation `System.IO.hGetNewlineMode`
by Wolfgang Jeltsch (@jeltsch) 22 Dec '25

22 Dec '25
Wolfgang Jeltsch pushed to branch wip/jeltsch/querying-newline-modes at Glasgow Haskell Compiler / GHC Commits: 9c8a9fda by Wolfgang Jeltsch at 2025-12-22T15:05:53+02:00 Add an operation `System.IO.hGetNewlineMode` This commit also contains some small code and documentation changes for related operations, for the sake of consistency. - - - - - 8 changed files: - libraries/base/changelog.md - libraries/base/src/System/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs - libraries/ghc-internal/src/GHC/Internal/System/IO.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== libraries/base/changelog.md ===================================== @@ -1,6 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.23.0.0 *TBA* + * Add `System.IO.hGetNewlineMode`. ([CLC proposal #370](https://github.com/haskell/core-libraries-committee/issues/370)) * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{init,last}`. Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it. ([CLC proposal #87](https://github.com/haskell/core-libraries-committee/issues/292)) ===================================== libraries/base/src/System/IO.hs ===================================== @@ -175,6 +175,7 @@ module System.IO -- Binary-mode 'Handle's do no newline translation at all. hSetNewlineMode, + hGetNewlineMode, Newline(..), nativeNewline, NewlineMode(..), ===================================== libraries/ghc-internal/src/GHC/Internal/IO/Handle.hs ===================================== @@ -40,7 +40,7 @@ module GHC.Internal.IO.Handle ( hIsOpen, hIsClosed, hIsReadable, hIsWritable, hGetBuffering, hIsSeekable, hSetEcho, hGetEcho, hIsTerminalDevice, - hSetNewlineMode, Newline(..), NewlineMode(..), nativeNewline, + hSetNewlineMode, hGetNewlineMode, Newline(..), NewlineMode(..), nativeNewline, noNewlineTranslation, universalNewlineMode, nativeNewlineMode, hShow, @@ -238,7 +238,7 @@ hSetBuffering handle mode = return Handle__{ haBufferMode = mode,.. } -- ----------------------------------------------------------------------------- --- hSetEncoding +-- Setting and getting the text encoding -- | The action 'hSetEncoding' @hdl@ @encoding@ changes the text encoding -- for the handle @hdl@ to @encoding@. The default encoding when a 'Handle' is @@ -624,16 +624,24 @@ hSetBinaryMode handle bin = haOutputNL = outputNL nl, .. } -- ----------------------------------------------------------------------------- --- hSetNewlineMode +-- Setting and getting the newline mode --- | Set the 'NewlineMode' on the specified 'Handle'. All buffered +-- | Set the 'NewlineMode' for the specified 'Handle'. All buffered -- data is flushed first. hSetNewlineMode :: Handle -> NewlineMode -> IO () -hSetNewlineMode handle NewlineMode{ inputNL=i, outputNL=o } = +hSetNewlineMode handle NewlineMode{..} = withAllHandles__ "hSetNewlineMode" handle $ \h_@Handle__{} -> do flushBuffer h_ - return h_{ haInputNL=i, haOutputNL=o } + return h_{ haInputNL = inputNL, haOutputNL = outputNL } + +-- | Return the current 'NewlineMode' for the specified 'Handle'. +-- +-- @since 4.23.0.0 +hGetNewlineMode :: Handle -> IO NewlineMode +hGetNewlineMode hdl = + withHandle_ "hGetNewlineMode" hdl $ \h_@Handle__{..} -> + return NewlineMode{ inputNL = haInputNL, outputNL = haOutputNL } -- ----------------------------------------------------------------------------- -- Duplicating a Handle ===================================== libraries/ghc-internal/src/GHC/Internal/System/IO.hs ===================================== @@ -214,6 +214,7 @@ module GHC.Internal.System.IO ( -- Binary-mode 'Handle's do no newline translation at all. -- hSetNewlineMode, + hGetNewlineMode, Newline(..), nativeNewline, NewlineMode(..), noNewlineTranslation, universalNewlineMode, nativeNewlineMode, ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -10263,6 +10263,7 @@ module System.IO where hGetEcho :: Handle -> IO GHC.Internal.Types.Bool hGetEncoding :: Handle -> IO (GHC.Internal.Maybe.Maybe TextEncoding) hGetLine :: Handle -> IO GHC.Internal.Base.String + hGetNewlineMode :: Handle -> IO NewlineMode hGetPosn :: Handle -> IO HandlePosn hIsClosed :: Handle -> IO GHC.Internal.Types.Bool hIsEOF :: Handle -> IO GHC.Internal.Types.Bool ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -13309,6 +13309,7 @@ module System.IO where hGetEcho :: Handle -> IO GHC.Internal.Types.Bool hGetEncoding :: Handle -> IO (GHC.Internal.Maybe.Maybe TextEncoding) hGetLine :: Handle -> IO GHC.Internal.Base.String + hGetNewlineMode :: Handle -> IO NewlineMode hGetPosn :: Handle -> IO HandlePosn hIsClosed :: Handle -> IO GHC.Internal.Types.Bool hIsEOF :: Handle -> IO GHC.Internal.Types.Bool ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -10543,6 +10543,7 @@ module System.IO where hGetEcho :: Handle -> IO GHC.Internal.Types.Bool hGetEncoding :: Handle -> IO (GHC.Internal.Maybe.Maybe TextEncoding) hGetLine :: Handle -> IO GHC.Internal.Base.String + hGetNewlineMode :: Handle -> IO NewlineMode hGetPosn :: Handle -> IO HandlePosn hIsClosed :: Handle -> IO GHC.Internal.Types.Bool hIsEOF :: Handle -> IO GHC.Internal.Types.Bool ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -10263,6 +10263,7 @@ module System.IO where hGetEcho :: Handle -> IO GHC.Internal.Types.Bool hGetEncoding :: Handle -> IO (GHC.Internal.Maybe.Maybe TextEncoding) hGetLine :: Handle -> IO GHC.Internal.Base.String + hGetNewlineMode :: Handle -> IO NewlineMode hGetPosn :: Handle -> IO HandlePosn hIsClosed :: Handle -> IO GHC.Internal.Types.Bool hIsEOF :: Handle -> IO GHC.Internal.Types.Bool View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c8a9fda71b3ca2acf730da4446de93… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c8a9fda71b3ca2acf730da4446de93… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL] 8 commits: hadrian: Build stage 2 cross compilers
by Sven Tennie (@supersven) 22 Dec '25

22 Dec '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL at Glasgow Haskell Compiler / GHC Commits: 78df276a by Matthew Pickering at 2025-12-22T13:43:18+01:00 hadrian: Build stage 2 cross compilers * Most of hadrian is abstracted over the stage in order to remove the assumption that the target of all stages is the same platform. This allows the RTS to be built for two different targets for example. * Abstracts the bindist creation logic to allow building either normal or cross bindists. Normal bindists use stage 1 libraries and a stage 2 compiler. Cross bindists use stage 2 libararies and a stage 2 compiler. * hadrian: Make binary-dist-dir the default build target. This allows us to have the logic in one place about which libraries/stages to build with cross compilers. Fixes #24192 New hadrian target: * `binary-dist-dir-cross`: Build a cross compiler bindist (compiler = stage 1, libraries = stage 2) This commit also contains various changes to make stage2 compilers feasible. ------------------------- Metric Decrease: T10421a T10858 T11195 T11276 T11374 T11822 T15630 T17096 T18478 T20261 Metric Increase: parsing001 ------------------------- Co-authored-by: Sven Tennie <sven.tennie(a)gmail.com> - - - - - 8b95cf12 by Sven Tennie at 2025-12-22T13:43:18+01:00 Align CI scripts with master Fixup - - - - - 18552d50 by Matthew Pickering at 2025-12-22T13:43:18+01:00 ci: Test cross bindists We remove the special logic for testing in-tree cross compilers and instead test cross compiler bindists, like we do for all other platforms. - - - - - f769d19c by Matthew Pickering at 2025-12-22T13:43:18+01:00 ci: Javascript don't set CROSS_EMULATOR There is no CROSS_EMULATOR needed to run javascript binaries, so we don't set the CROSS_EMULATOR to some dummy value. - - - - - cfa5cd14 by Matthew Pickering at 2025-12-22T13:43:18+01:00 ci: Introduce CROSS_STAGE variable In preparation for building and testing stage3 bindists we introduce the CROSS_STAGE variable which is used by a CI job to determine what kind of bindist the CI job should produce. At the moment we are only using CROSS_STAGE=2 but in the future we will have some jobs which set CROSS_STAGE=3 to produce native bindists for a target, but produced by a cross compiler, which can be tested on by another CI job on the native platform. CROSS_STAGE=2: Build a normal cross compiler bindist CROSS_STAGE=3: Build a stage 3 bindist, one which is a native compiler and library for the target - - - - - 5b4a5d93 by Matthew Pickering at 2025-12-22T13:43:18+01:00 hadrian: Refactor system-cxx-std-lib rules0 I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules. * For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`. * The `system-cxx-std-lib` dependency is not read from cabal files. * Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`. Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`. Fixes #25303 - - - - - 90fee2c1 by Sven Tennie at 2025-12-22T13:43:18+01:00 Increase timeout for emulators Test runs with emulators naturally take longer than on native machines. - - - - - c88f0d8c by Sven Tennie at 2025-12-22T13:43:18+01:00 ghc: Distinguish between having an interpreter and having an internal one Otherwise, we fail with warnings when compiling tools. Actually, these are related but different things: - ghc can run an interpreter (either internal or external) - ghc is compiled with an internal interpreter - - - - - 68 changed files: - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - configure.ac - distrib/configure.ac.in - ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/README.md - hadrian/bindist/config.mk.in - + hadrian/cfg/system.config.host.in - hadrian/cfg/system.config.in - + hadrian/cfg/system.config.target.in - hadrian/hadrian.cabal - hadrian/src/Base.hs - + hadrian/src/BindistConfig.hs - hadrian/src/Builder.hs - hadrian/src/Context.hs - hadrian/src/Expression.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Hadrian/Builder.hs - hadrian/src/Hadrian/Expression.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Haskell/Cabal/Type.hs - hadrian/src/Hadrian/Haskell/Hash.hs - hadrian/src/Hadrian/Oracles/TextFile.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Oracles/TestSettings.hs - hadrian/src/Packages.hs - hadrian/src/Rules.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Compile.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Program.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Common.hs - hadrian/src/Settings/Builders/Configure.hs - hadrian/src/Settings/Builders/DeriveConstants.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Builders/Hsc2Hs.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Builders/SplitSections.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Benchmark.hs - hadrian/src/Settings/Flavours/Development.hs - hadrian/src/Settings/Flavours/GhcInGhci.hs - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Quick.hs - hadrian/src/Settings/Flavours/QuickCross.hs - hadrian/src/Settings/Flavours/Quickest.hs - hadrian/src/Settings/Flavours/Validate.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - hadrian/src/Settings/Warnings.hs - testsuite/ghc-config/ghc-config.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbd1390e1626820f962750655bdeac… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbd1390e1626820f962750655bdeac… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL] 8 commits: hadrian: Build stage 2 cross compilers
by Sven Tennie (@supersven) 22 Dec '25

22 Dec '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL at Glasgow Haskell Compiler / GHC Commits: 795adcb9 by Matthew Pickering at 2025-12-22T13:35:41+01:00 hadrian: Build stage 2 cross compilers * Most of hadrian is abstracted over the stage in order to remove the assumption that the target of all stages is the same platform. This allows the RTS to be built for two different targets for example. * Abstracts the bindist creation logic to allow building either normal or cross bindists. Normal bindists use stage 1 libraries and a stage 2 compiler. Cross bindists use stage 2 libararies and a stage 2 compiler. * hadrian: Make binary-dist-dir the default build target. This allows us to have the logic in one place about which libraries/stages to build with cross compilers. Fixes #24192 New hadrian target: * `binary-dist-dir-cross`: Build a cross compiler bindist (compiler = stage 1, libraries = stage 2) ------------------------- Metric Decrease: T10421a T10858 T11195 T11276 T11374 T11822 T15630 T17096 T18478 T20261 Metric Increase: parsing001 ------------------------- Fix hardcoded stage1 Don't recache Additional SIMD flags are required for the host The files with specific SIMD flags are built for GHC's RTS (host), not for the programs built by it (target.) This matters when cross-compiling, because host and target differ then. Split up system.config into host/target config files There were a number of settings which were not applied per-stage, for example if you specified `--ffi-include-dir` then that was applied to both host and target. Now this will just be passed when building the crosscompiler. The solution for now is to separate these two files into host/target and the host file contains very bare-bones . There isn't currently a way to specify with configure anything in the host file, so if you are building a cross-compiler and you need to do that, you have to modify the file yourself. Fix location of emsdk-version fix distrib/configure file hadrian: Make text_simdutf flavour transformer configurable per-stage Before it was globally enabled, which was probably not what you want as you don't need text-simd for your boot compiler nor your boot compiler if you're building a cross-compiler. This brings it into line with the other modifiers.. such as ghcProfiled etc Fixes #25302 fixes for simdutf8 Hard-code ways in settings Fix ghcconfig lookup error This seems to be the fix with least friction for the issue stated below. Though, in the long run it might be better to rename `TargetARCH_CPP` to `TargetARCH` (the `_CPP` suffix feels a bit odd.) Fixed error: ``` Key 'TargetARCH' not found in file '_build/test/ghcconfig' ``` target-has-libm -> use-lib-m The flag was renamed. Fix path stage segment to stage mapping in generated rules Cleanup unused imports Fix out-of-tree TestCompilerArgs parsing: WORDSIZE TestWORDSIZE is in bits, not bytes. TestCompilerArgs: Fix arch (out of tree) Calculate "RTS ways" The static string doesn't reflect what GHC provides in tests. Fix libffi configuration Libffi needs to be built with the config of the successor stage. Fix libffi ghcjs hadrian: Fix predicate for building shared libraries in defaultLibraries Obviously we should only attempt to build shared libraries if the target supports building shared libraries. use building for target in llvm flavour transformer WIP: libffi: LD, OBJDUMP, STRIP staged Removing the env variables implies using the programs from $PATH. This kind-of works, but these values should be correctly auto-configured. Make stage2 cross windows build work - somehow Still needs some improvements. Adjust host_fully_static for stage2 cross builds Reference correct package.conf.d for cross Fixup Rebase Fixup: Align Settings Rebase fixup Libffi - no LD for cross host stages NOSMP has to be a C flag for RTS Otherwise building unregisterised fails. This is also in line with master. Rebase fixup: ghcWithInternalInterpreter Prevent settings file creation exception Do not try to reach out to settings beyond finalStage. That cannot work. Fix Asan Provide config.cross flag to testsuite bindist: Pass path to package database we want to recache This fixes recaching on cross compilers - - - - - f1121b73 by Sven Tennie at 2025-12-22T13:35:41+01:00 Align CI scripts with master Fixup - - - - - 4752af56 by Matthew Pickering at 2025-12-22T13:35:41+01:00 ci: Test cross bindists We remove the special logic for testing in-tree cross compilers and instead test cross compiler bindists, like we do for all other platforms. - - - - - a9003cdb by Matthew Pickering at 2025-12-22T13:35:41+01:00 ci: Javascript don't set CROSS_EMULATOR There is no CROSS_EMULATOR needed to run javascript binaries, so we don't set the CROSS_EMULATOR to some dummy value. - - - - - 3b6c746d by Matthew Pickering at 2025-12-22T13:35:41+01:00 ci: Introduce CROSS_STAGE variable In preparation for building and testing stage3 bindists we introduce the CROSS_STAGE variable which is used by a CI job to determine what kind of bindist the CI job should produce. At the moment we are only using CROSS_STAGE=2 but in the future we will have some jobs which set CROSS_STAGE=3 to produce native bindists for a target, but produced by a cross compiler, which can be tested on by another CI job on the native platform. CROSS_STAGE=2: Build a normal cross compiler bindist CROSS_STAGE=3: Build a stage 3 bindist, one which is a native compiler and library for the target - - - - - 5b6d4463 by Matthew Pickering at 2025-12-22T13:35:41+01:00 hadrian: Refactor system-cxx-std-lib rules0 I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules. * For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`. * The `system-cxx-std-lib` dependency is not read from cabal files. * Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`. Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`. Fixes #25303 - - - - - 7f90e5f8 by Sven Tennie at 2025-12-22T13:35:41+01:00 Increase timeout for emulators Test runs with emulators naturally take longer than on native machines. - - - - - fbd1390e by Sven Tennie at 2025-12-22T13:35:41+01:00 Distinguish between having an interpreter and having an internal one Otherwise, we fail with warnings when compiling tools. - - - - - 68 changed files: - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - configure.ac - distrib/configure.ac.in - ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/README.md - hadrian/bindist/config.mk.in - + hadrian/cfg/system.config.host.in - hadrian/cfg/system.config.in - + hadrian/cfg/system.config.target.in - hadrian/hadrian.cabal - hadrian/src/Base.hs - + hadrian/src/BindistConfig.hs - hadrian/src/Builder.hs - hadrian/src/Context.hs - hadrian/src/Expression.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Hadrian/Builder.hs - hadrian/src/Hadrian/Expression.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Haskell/Cabal/Type.hs - hadrian/src/Hadrian/Haskell/Hash.hs - hadrian/src/Hadrian/Oracles/TextFile.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Oracles/TestSettings.hs - hadrian/src/Packages.hs - hadrian/src/Rules.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Compile.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Program.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Common.hs - hadrian/src/Settings/Builders/Configure.hs - hadrian/src/Settings/Builders/DeriveConstants.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Builders/Hsc2Hs.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Builders/SplitSections.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Benchmark.hs - hadrian/src/Settings/Flavours/Development.hs - hadrian/src/Settings/Flavours/GhcInGhci.hs - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Quick.hs - hadrian/src/Settings/Flavours/QuickCross.hs - hadrian/src/Settings/Flavours/Quickest.hs - hadrian/src/Settings/Flavours/Validate.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - hadrian/src/Settings/Warnings.hs - testsuite/ghc-config/ghc-config.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/caa3ed67c19cde9b15a5877aa4bea6… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/caa3ed67c19cde9b15a5877aa4bea6… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL] 10 commits: hadrian: Build stage 2 cross compilers
by Sven Tennie (@supersven) 22 Dec '25

22 Dec '25
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FINAL at Glasgow Haskell Compiler / GHC Commits: e4a70020 by Matthew Pickering at 2025-12-22T13:27:46+01:00 hadrian: Build stage 2 cross compilers * Most of hadrian is abstracted over the stage in order to remove the assumption that the target of all stages is the same platform. This allows the RTS to be built for two different targets for example. * Abstracts the bindist creation logic to allow building either normal or cross bindists. Normal bindists use stage 1 libraries and a stage 2 compiler. Cross bindists use stage 2 libararies and a stage 2 compiler. * hadrian: Make binary-dist-dir the default build target. This allows us to have the logic in one place about which libraries/stages to build with cross compilers. Fixes #24192 New hadrian target: * `binary-dist-dir-cross`: Build a cross compiler bindist (compiler = stage 1, libraries = stage 2) ------------------------- Metric Decrease: T10421a T10858 T11195 T11276 T11374 T11822 T15630 T17096 T18478 T20261 Metric Increase: parsing001 ------------------------- Fix hardcoded stage1 Don't recache Additional SIMD flags are required for the host The files with specific SIMD flags are built for GHC's RTS (host), not for the programs built by it (target.) This matters when cross-compiling, because host and target differ then. Split up system.config into host/target config files There were a number of settings which were not applied per-stage, for example if you specified `--ffi-include-dir` then that was applied to both host and target. Now this will just be passed when building the crosscompiler. The solution for now is to separate these two files into host/target and the host file contains very bare-bones . There isn't currently a way to specify with configure anything in the host file, so if you are building a cross-compiler and you need to do that, you have to modify the file yourself. Fix location of emsdk-version fix distrib/configure file hadrian: Make text_simdutf flavour transformer configurable per-stage Before it was globally enabled, which was probably not what you want as you don't need text-simd for your boot compiler nor your boot compiler if you're building a cross-compiler. This brings it into line with the other modifiers.. such as ghcProfiled etc Fixes #25302 fixes for simdutf8 Hard-code ways in settings Fix ghcconfig lookup error This seems to be the fix with least friction for the issue stated below. Though, in the long run it might be better to rename `TargetARCH_CPP` to `TargetARCH` (the `_CPP` suffix feels a bit odd.) Fixed error: ``` Key 'TargetARCH' not found in file '_build/test/ghcconfig' ``` target-has-libm -> use-lib-m The flag was renamed. Fix path stage segment to stage mapping in generated rules Cleanup unused imports Fix out-of-tree TestCompilerArgs parsing: WORDSIZE TestWORDSIZE is in bits, not bytes. TestCompilerArgs: Fix arch (out of tree) Calculate "RTS ways" The static string doesn't reflect what GHC provides in tests. Fix libffi configuration Libffi needs to be built with the config of the successor stage. Fix libffi ghcjs hadrian: Fix predicate for building shared libraries in defaultLibraries Obviously we should only attempt to build shared libraries if the target supports building shared libraries. use building for target in llvm flavour transformer WIP: libffi: LD, OBJDUMP, STRIP staged Removing the env variables implies using the programs from $PATH. This kind-of works, but these values should be correctly auto-configured. Make stage2 cross windows build work - somehow Still needs some improvements. Adjust host_fully_static for stage2 cross builds Reference correct package.conf.d for cross Fixup Rebase Fixup: Align Settings Rebase fixup Libffi - no LD for cross host stages NOSMP has to be a C flag for RTS Otherwise building unregisterised fails. This is also in line with master. Rebase fixup: ghcWithInternalInterpreter Prevent settings file creation exception Do not try to reach out to settings beyond finalStage. That cannot work. Fix Asan - - - - - 09edd16f by Sven Tennie at 2025-12-22T13:27:47+01:00 Align CI scripts with master Fixup - - - - - 1a37320a by Matthew Pickering at 2025-12-22T13:27:47+01:00 ci: Test cross bindists We remove the special logic for testing in-tree cross compilers and instead test cross compiler bindists, like we do for all other platforms. - - - - - 6aee82c9 by Matthew Pickering at 2025-12-22T13:27:47+01:00 ci: Javascript don't set CROSS_EMULATOR There is no CROSS_EMULATOR needed to run javascript binaries, so we don't set the CROSS_EMULATOR to some dummy value. - - - - - 1d98d10b by Matthew Pickering at 2025-12-22T13:27:47+01:00 ci: Introduce CROSS_STAGE variable In preparation for building and testing stage3 bindists we introduce the CROSS_STAGE variable which is used by a CI job to determine what kind of bindist the CI job should produce. At the moment we are only using CROSS_STAGE=2 but in the future we will have some jobs which set CROSS_STAGE=3 to produce native bindists for a target, but produced by a cross compiler, which can be tested on by another CI job on the native platform. CROSS_STAGE=2: Build a normal cross compiler bindist CROSS_STAGE=3: Build a stage 3 bindist, one which is a native compiler and library for the target - - - - - 51c4f4c8 by Matthew Pickering at 2025-12-22T13:27:47+01:00 hadrian: Refactor system-cxx-std-lib rules0 I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules. * For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`. * The `system-cxx-std-lib` dependency is not read from cabal files. * Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`. Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`. Fixes #25303 - - - - - e0568f84 by Matthew Pickering at 2025-12-22T13:27:47+01:00 bindist: Pass path to package database we want to recache This fixes recaching on cross compilers - - - - - a5b30720 by Sven Tennie at 2025-12-22T13:27:47+01:00 Increase timeout for emulators Test runs with emulators naturally take longer than on native machines. - - - - - 55f080d8 by Sven Tennie at 2025-12-22T13:27:47+01:00 Provide config.cross flag to testsuite - - - - - caa3ed67 by Sven Tennie at 2025-12-22T13:27:47+01:00 Distinguish between having an interpreter and having an internal one Otherwise, we fail with warnings when compiling tools. - - - - - 68 changed files: - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - configure.ac - distrib/configure.ac.in - ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/README.md - hadrian/bindist/config.mk.in - + hadrian/cfg/system.config.host.in - hadrian/cfg/system.config.in - + hadrian/cfg/system.config.target.in - hadrian/hadrian.cabal - hadrian/src/Base.hs - + hadrian/src/BindistConfig.hs - hadrian/src/Builder.hs - hadrian/src/Context.hs - hadrian/src/Expression.hs - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Hadrian/Builder.hs - hadrian/src/Hadrian/Expression.hs - hadrian/src/Hadrian/Haskell/Cabal/Parse.hs - hadrian/src/Hadrian/Haskell/Cabal/Type.hs - hadrian/src/Hadrian/Haskell/Hash.hs - hadrian/src/Hadrian/Oracles/TextFile.hs - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Oracles/TestSettings.hs - hadrian/src/Packages.hs - hadrian/src/Rules.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Compile.hs - hadrian/src/Rules/Documentation.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Gmp.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Program.hs - hadrian/src/Rules/Register.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/Common.hs - hadrian/src/Settings/Builders/Configure.hs - hadrian/src/Settings/Builders/DeriveConstants.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Builders/Hsc2Hs.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Builders/SplitSections.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Flavours/Benchmark.hs - hadrian/src/Settings/Flavours/Development.hs - hadrian/src/Settings/Flavours/GhcInGhci.hs - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Quick.hs - hadrian/src/Settings/Flavours/QuickCross.hs - hadrian/src/Settings/Flavours/Quickest.hs - hadrian/src/Settings/Flavours/Validate.hs - hadrian/src/Settings/Packages.hs - hadrian/src/Settings/Program.hs - hadrian/src/Settings/Warnings.hs - testsuite/ghc-config/ghc-config.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/355bb03ee8c4ea5f93773f65aaa07a… -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/355bb03ee8c4ea5f93773f65aaa07a… You're receiving this email because of your account on gitlab.haskell.org.
1 0
0 0
  • ← Newer
  • 1
  • ...
  • 11
  • 12
  • 13
  • 14
  • 15
  • 16
  • 17
  • ...
  • 57
  • Older →

HyperKitty Powered by HyperKitty version 1.3.9.