
[Git][ghc/ghc] Pushed new branch wip/andreask/spec-float-again
by Andreas Klebinger (@AndreasK) 26 May '25
by Andreas Klebinger (@AndreasK) 26 May '25
26 May '25
Andreas Klebinger pushed new branch wip/andreask/spec-float-again at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/spec-float-again
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T25992] 18 commits: Don't fail when ghcversion.h can't be found (#26018)
by Simon Peyton Jones (@simonpj) 26 May '25
by Simon Peyton Jones (@simonpj) 26 May '25
26 May '25
Simon Peyton Jones pushed to branch wip/T25992 at Glasgow Haskell Compiler / GHC
Commits:
6d058a69 by Andrea Bedini at 2025-05-21T16:00:51-04:00
Don't fail when ghcversion.h can't be found (#26018)
If ghcversion.h can't be found, don't try to include it. This happens
when there is no rts package in the package db and when -ghcversion-file
argument isn't passed.
Co-authored-by: Syvlain Henry <sylvain(a)haskus.fr>
- - - - -
b1212fbf by Vladislav Zavialov at 2025-05-21T16:01:33-04:00
Implement -Wpattern-namespace-specifier (#25900)
In accordance with GHC Proposal #581 "Namespace-specified imports",
section 2.3 "Deprecate use of pattern in import/export lists", the
`pattern` namespace specifier is now deprecated.
Test cases: T25900 T25900_noext
- - - - -
e650ec3e by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Forward port changelog language from 9.12
- - - - -
94cd9ca4 by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Fix RestructuredText-isms in changelog
- - - - -
7722232c by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Note strictness changes made in 4.16.0.0
Addresses #25886.
- - - - -
3f4b823c by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Factor out ProddableBlocks machinery
- - - - -
6e23fef2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Improve efficiency of proddable blocks structure
Previously the linker's "proddable blocks" check relied on a simple
linked list of spans. This resulted in extremely poor complexity while
linking objects with lots of small sections (e.g. objects built with
split sections).
Rework the mechanism to instead use a simple interval set implemented
via binary search.
Fixes #26009.
- - - - -
ea74860c by Ben Gamari at 2025-05-23T03:43:28-04:00
testsuite: Add simple functional test for ProddableBlockSet
- - - - -
74c4db46 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Drop check for LOAD_LIBRARY_SEARCH_*_DIRS
The `LOAD_LIBRARY_SEARCH_USER_DIRS` and
`LOAD_LIBRARY_SEARCH_DEFAULT_DIRS` were introduced in Windows Vista and
have been available every since. As we no longer support Windows XP we
can drop this check.
Addresses #26009.
- - - - -
972d81d6 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Clean up code style
- - - - -
8a1073a5 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/Hash: Factor out hashBuffer
This is a useful helper which can be used for non-strings as well.
- - - - -
44f509f2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Fix incorrect use of break in nested for
Previously the happy path of PEi386 used `break` in a double-`for` loop
resulting in redundant calls to `LoadLibraryEx`.
Fixes #26052.
- - - - -
bfb12783 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts: Correctly mark const arguments
- - - - -
08469ff8 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Don't repeatedly load DLLs
Previously every DLL-imported symbol would result in a call to
`LoadLibraryEx`. This ended up constituting over 40% of the runtime of
`ghc --interactive -e 42` on Windows. Avoid this by maintaining a
hash-set of loaded DLL names, skipping the call if we have already
loaded the requested DLL.
Addresses #26009.
- - - - -
823d1ccf by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Expand comment describing ProddableBlockSet
- - - - -
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
bf4ae871 by Simon Peyton Jones at 2025-05-26T12:14:22+01:00
Improve redundant constraints for instance decls
Addresses #25992, which showed that the default methods
of an instance decl could make GHC fail to report redundant
constraints.
Figuring out how to do this led me to refactor the computation
of redundant constraints. See the entirely rewritten
Note [Tracking redundant constraints]
in GHC.Tc.Solver.Solve
- - - - -
104 changed files:
- compiler/GHC.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- hadrian/src/Flavour.hs
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs
- libraries/ghc-internal/src/GHC/Internal/TypeLits.hs
- libraries/ghc-internal/src/GHC/Internal/TypeNats.hs
- rts/Hash.c
- rts/Hash.h
- rts/Linker.c
- rts/LinkerInternals.h
- rts/PathUtils.c
- rts/PathUtils.h
- rts/linker/Elf.c
- rts/linker/MachO.c
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- + rts/linker/ProddableBlocks.c
- + rts/linker/ProddableBlocks.h
- rts/rts.cabal
- testsuite/tests/callarity/unittest/CallArity1.hs
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/all.T
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- 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
- + testsuite/tests/parser/should_compile/T25900.hs
- + testsuite/tests/parser/should_compile/T25900.stderr
- + testsuite/tests/parser/should_compile/T25900_noext.hs
- + testsuite/tests/parser/should_compile/T25900_noext.stderr
- testsuite/tests/parser/should_compile/all.T
- testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs
- testsuite/tests/patsyn/should_compile/T11959.hs
- testsuite/tests/patsyn/should_compile/T11959.stderr
- testsuite/tests/patsyn/should_compile/T11959Lib.hs
- testsuite/tests/patsyn/should_compile/T13350/boolean/Boolean.hs
- testsuite/tests/patsyn/should_compile/T22521.hs
- testsuite/tests/patsyn/should_compile/T9857.hs
- testsuite/tests/patsyn/should_compile/export.hs
- testsuite/tests/pmcheck/complete_sigs/T25115a.hs
- testsuite/tests/pmcheck/should_compile/T11822.hs
- testsuite/tests/polykinds/T14270.hs
- testsuite/tests/rename/should_compile/T12548.hs
- testsuite/tests/rename/should_fail/T25056.stderr
- testsuite/tests/rename/should_fail/T25056a.hs
- + testsuite/tests/rts/TestProddableBlockSet.c
- testsuite/tests/rts/all.T
- testsuite/tests/simplCore/should_compile/T15186.hs
- testsuite/tests/simplCore/should_compile/T15186A.hs
- + testsuite/tests/typecheck/should_compile/T25992.hs
- + testsuite/tests/typecheck/should_compile/T25992.stderr
- testsuite/tests/typecheck/should_compile/TypeRepCon.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/tcfail097.stderr
- testsuite/tests/warnings/should_compile/DataToTagWarnings.hs
- testsuite/tests/warnings/should_compile/T14794a.hs
- testsuite/tests/warnings/should_compile/T14794a.stderr
- testsuite/tests/warnings/should_compile/T14794b.hs
- testsuite/tests/warnings/should_compile/T14794b.stderr
- testsuite/tests/warnings/should_compile/T14794c.hs
- testsuite/tests/warnings/should_compile/T14794c.stderr
- testsuite/tests/warnings/should_compile/T14794d.hs
- testsuite/tests/warnings/should_compile/T14794d.stderr
- testsuite/tests/warnings/should_compile/T14794e.hs
- testsuite/tests/warnings/should_compile/T14794e.stderr
- testsuite/tests/warnings/should_compile/T14794f.hs
- testsuite/tests/warnings/should_compile/T14794f.stderr
- testsuite/tests/wcompat-warnings/Template.hs
- + testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4cb8b60a22f1a3b7227f5f5153e00f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4cb8b60a22f1a3b7227f5f5153e00f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109a] 3 commits: Revert "Always try rules and inlining before simplifying args"
by Simon Peyton Jones (@simonpj) 26 May '25
by Simon Peyton Jones (@simonpj) 26 May '25
26 May '25
Simon Peyton Jones pushed to branch wip/T23109a at Glasgow Haskell Compiler / GHC
Commits:
acc7c29d by Simon Peyton Jones at 2025-05-26T10:21:37+01:00
Revert "Always try rules and inlining before simplifying args"
This reverts commit 29117fad96e827f1768ca0ac2ba811929ace76f4.
- - - - -
2da3fb2c by Simon Peyton Jones at 2025-05-26T10:21:55+01:00
Revert "Try inlining after simplifying the arguments"
This reverts commit fb2d5dee8f50052bb3cc0bcaec37de7884d631eb.
- - - - -
4d2a8804 by Simon Peyton Jones at 2025-05-26T11:23:49+01:00
Inline top-level used-one things
... until final phase. This makes a difference in LargeRecord, where
we can inline lots of dictionaries
Just before FinalPhase we do a float-out with floatConsts=True, so
we don't want to undo it by inlining them again.
- - - - -
5 changed files:
- 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/Driver/Config/Core/Opt/Simplify.hs
Changes:
=====================================
compiler/GHC/Core/Opt/Simplify.hs
=====================================
@@ -156,7 +156,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts
&& logHasDumpFlag logger Opt_D_dump_simpl_stats) $
logDumpMsg logger
"Simplifier statistics for following pass"
- (vcat [text termination_msg <+> text "after" <+> ppr (it_count-1)
+ (vcat [text termination_msg <+> text "after" <+> ppr it_count
<+> text "iterations",
blankLine,
pprSimplCount counts_out])
@@ -240,8 +240,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts
; read_rule_env = updExternalPackageRules base_rule_env <$> read_eps_rules
; fam_envs = (eps_fam_inst_env eps, fam_inst_env)
- ; iter_mode = mode { sm_first_iter = iteration_no ==1 }
- ; simpl_env = mkSimplEnv iter_mode fam_envs } ;
+ ; simpl_env = mkSimplEnv mode fam_envs } ;
-- Simplify the program
((binds1, rules1), counts1) <-
=====================================
compiler/GHC/Core/Opt/Simplify/Env.hs
=====================================
@@ -272,35 +272,32 @@ seUnfoldingOpts env = sm_uf_opts (seMode env)
-- See Note [The environments of the Simplify pass]
data SimplMode = SimplMode -- See comments in GHC.Core.Opt.Simplify.Monad
- { sm_phase :: !CompilerPhase
- , sm_names :: ![String] -- ^ Name(s) of the phase
- , sm_first_iter :: !Bool -- ^ True <=> first iteration
- -- False <=> second or subsequent iteration
- , sm_rules :: !Bool -- ^ Whether RULES are enabled
- , sm_inline :: !Bool -- ^ Whether inlining is enabled
- , sm_eta_expand :: !Bool -- ^ Whether eta-expansion is enabled
- , sm_cast_swizzle :: !Bool -- ^ Do we swizzle casts past lambdas?
- , sm_uf_opts :: !UnfoldingOpts -- ^ Unfolding options
- , sm_case_case :: !Bool -- ^ Whether case-of-case is enabled
- , sm_pre_inline :: !Bool -- ^ Whether pre-inlining is enabled
- , sm_float_enable :: !FloatEnable -- ^ Whether to enable floating out
+ { sm_phase :: !CompilerPhase
+ , sm_names :: ![String] -- ^ Name(s) of the phase
+ , sm_rules :: !Bool -- ^ Whether RULES are enabled
+ , sm_inline :: !Bool -- ^ Whether inlining is enabled
+ , sm_eta_expand :: !Bool -- ^ Whether eta-expansion is enabled
+ , sm_cast_swizzle :: !Bool -- ^ Do we swizzle casts past lambdas?
+ , sm_uf_opts :: !UnfoldingOpts -- ^ Unfolding options
+ , sm_case_case :: !Bool -- ^ Whether case-of-case is enabled
+ , sm_pre_inline :: !Bool -- ^ Whether pre-inlining is enabled
+ , sm_float_enable :: !FloatEnable -- ^ Whether to enable floating out
, sm_do_eta_reduction :: !Bool
- , sm_arity_opts :: !ArityOpts
- , sm_rule_opts :: !RuleOpts
- , sm_case_folding :: !Bool
- , sm_case_merge :: !Bool
- , sm_co_opt_opts :: !OptCoercionOpts -- ^ Coercion optimiser options
+ , sm_arity_opts :: !ArityOpts
+ , sm_rule_opts :: !RuleOpts
+ , sm_case_folding :: !Bool
+ , sm_case_merge :: !Bool
+ , sm_co_opt_opts :: !OptCoercionOpts -- ^ Coercion optimiser options
}
instance Outputable SimplMode where
ppr (SimplMode { sm_phase = p , sm_names = ss
- , sm_first_iter = fi, sm_rules = r, sm_inline = i
+ , sm_rules = r, sm_inline = i
, sm_cast_swizzle = cs
, sm_eta_expand = eta, sm_case_case = cc })
= text "SimplMode" <+> braces (
sep [ text "Phase =" <+> ppr p <+>
brackets (text (concat $ intersperse "," ss)) <> comma
- , pp_flag fi (text "first-iter") <> comma
, pp_flag i (text "inline") <> comma
, pp_flag r (text "rules") <> comma
, pp_flag eta (text "eta-expand") <> comma
=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -2342,21 +2342,10 @@ simplOutId env fun cont
-- Normal case for (f e1 .. en)
simplOutId env fun cont
- = do { rule_base <- getSimplRules
+ = -- Try rewrite rules: Plan (BEFORE) in Note [When to apply rewrite rules]
+ do { rule_base <- getSimplRules
; let rules_for_me = getRules rule_base fun
- arg_info = mkArgInfo env fun rules_for_me cont
out_args = contOutArgs env cont :: [OutExpr]
-
- -- If we are not in the first iteration, we have already tried rules and inlining
- -- at the end of the previous iteration; no need to repeat that
--- ; if not (sm_first_iter (seMode env))
--- then rebuildCall env arg_info cont
--- else
--- Do this BEFORE so that we can take advantage of single-occ inlines
--- Example: T21839c which takes an extra Simplifier iteration after w/w
--- if you don't do this
-
- -- Try rewrite rules: Plan (BEFORE) in Note [When to apply rewrite rules]
; mb_match <- if not (null rules_for_me) &&
(isClassOpId fun || activeUnfolding (seMode env) fun)
then tryRules env rules_for_me fun out_args
@@ -2368,14 +2357,16 @@ simplOutId env fun cont
-- Try inlining
do { logger <- getLogger
- ; mb_inline <- tryInlining env logger fun (contArgs cont)
+ ; mb_inline <- tryInlining env logger fun cont
; case mb_inline of{
- Just expr -> simplExprF env expr cont ;
+ Just expr -> do { checkedTick (UnfoldingDone fun)
+ ; simplExprF env expr cont } ;
Nothing ->
-- Neither worked, so just rebuild
- rebuildCall env arg_info cont
- } } } }
+ do { let arg_info = mkArgInfo env fun rules_for_me cont
+ ; rebuildCall env arg_info cont
+ } } } } }
---------------------------------------------------------
-- Dealing with a call site
@@ -2447,39 +2438,28 @@ rebuildCall env fun_info
---------- No further useful info, revert to generic rebuild ------------
rebuildCall env (ArgInfo { ai_fun = fun, ai_args = rev_args, ai_rules = rules }) cont
+ | null rules
+ = rebuild env (argInfoExpr fun rev_args) cont
+ | otherwise -- Try rules again: Plan (AFTER) in Note [When to apply rewrite rules]
= do { let args = reverse rev_args
-
- -- Try rules again: Plan (AFTER) in Note [When to apply rewrite rules]
- ; mb_match <- if null rules
- then return Nothing
- else tryRules env rules fun (map argSpecArg args)
- ; case mb_match of {
+ ; mb_match <- tryRules env rules fun (map argSpecArg args)
+ ; case mb_match of
Just (rule_arity, rhs) -> simplExprF env rhs $
- pushSimplifiedArgs env (drop rule_arity args) cont ;
- Nothing ->
-
- do { logger <- getLogger
- ; mb_inline <- tryInlining env logger fun (null args, argSummaries env args, cont)
- ; case mb_inline of
- Just body -> simplExprF env body $
- pushSimplifiedArgs env args cont
- Nothing -> rebuild env (argInfoExpr fun rev_args) cont
- } } }
+ pushSimplifiedArgs env (drop rule_arity args) cont
+ Nothing -> rebuild env (argInfoExpr fun rev_args) cont }
-----------------------------------
-tryInlining :: SimplEnv -> Logger -> OutId
- -> (Bool, [ArgSummary], SimplCont)
- -> SimplM (Maybe OutExpr)
-tryInlining env logger fun (lone_variable, arg_infos, call_cont)
- | Just expr <- callSiteInline env logger fun lone_variable arg_infos interesting_cont
- = do { dump_inline expr call_cont
- ; checkedTick (UnfoldingDone fun)
+tryInlining :: SimplEnv -> Logger -> OutId -> SimplCont -> SimplM (Maybe OutExpr)
+tryInlining env logger var cont
+ | Just expr <- callSiteInline env logger var lone_variable arg_infos interesting_cont
+ = do { dump_inline expr cont
; return (Just expr) }
| otherwise
= return Nothing
where
+ (lone_variable, arg_infos, call_cont) = contArgs cont
interesting_cont = interestingCallContext env call_cont
log_inlining doc
@@ -2490,12 +2470,12 @@ tryInlining env logger fun (lone_variable, arg_infos, call_cont)
dump_inline unfolding cont
| not (logHasDumpFlag logger Opt_D_dump_inlinings) = return ()
| not (logHasDumpFlag logger Opt_D_verbose_core2core)
- = when (isExternalName (idName fun)) $
+ = when (isExternalName (idName var)) $
log_inlining $
- sep [text "Inlining done:", nest 4 (ppr fun)]
+ sep [text "Inlining done:", nest 4 (ppr var)]
| otherwise
= log_inlining $
- sep [text "Inlining done: " <> ppr fun,
+ sep [text "Inlining done: " <> ppr var,
nest 4 (vcat [text "Inlined fn: " <+> nest 2 (ppr unfolding),
text "Cont: " <+> ppr cont])]
=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -24,7 +24,7 @@ module GHC.Core.Opt.Simplify.Utils (
SimplCont(..), DupFlag(..), FromWhat(..), StaticEnv,
isSimplified, contIsStop,
contIsDupable, contResultType, contHoleType, contHoleScaling,
- contIsTrivial, contArgs, contIsRhs, argSummaries,
+ contIsTrivial, contArgs, contIsRhs,
countArgs, contOutArgs, dropContArgs,
mkBoringStop, mkRhsStop, mkLazyArgStop,
interestingCallContext,
@@ -537,11 +537,15 @@ contArgs cont
lone _ = True
go args (ApplyToVal { sc_arg = arg, sc_env = se, sc_cont = k })
- = go (argSummary se arg : args) k
+ = go (is_interesting arg se : args) k
go args (ApplyToTy { sc_cont = k }) = go args k
go args (CastIt { sc_cont = k }) = go args k
go args k = (False, reverse args, k)
+ is_interesting arg se = interestingArg se arg
+ -- Do *not* use short-cutting substitution here
+ -- because we want to get as much IdInfo as possible
+
contOutArgs :: SimplEnv -> SimplCont -> [OutExpr]
-- Get the leading arguments from the `SimplCont`, as /OutExprs/
contOutArgs env cont
@@ -883,15 +887,6 @@ strictArgContext (ArgInfo { ai_encl = encl_rules, ai_discs = discs })
-- Why NonRecursive? Becuase it's a bit like
-- let a = g x in f a
-argSummaries :: SimplEnv -> [ArgSpec] -> [ArgSummary]
-argSummaries env args
- = go args
- where
- env' = zapSubstEnv env -- The args are simplified already
- go [] = []
- go (TyArg {} : args) = go args
- go (ValArg { as_arg = arg } : args) = argSummary env' arg : go args
-
interestingCallContext :: SimplEnv -> SimplCont -> CallCtxt
-- See Note [Interesting call context]
interestingCallContext env cont
@@ -995,9 +990,9 @@ rule for (*) (df d) can fire. To do this
b) we say that a con-like argument (eg (df d)) is interesting
-}
-argSummary :: SimplEnv -> CoreExpr -> ArgSummary
+interestingArg :: SimplEnv -> CoreExpr -> ArgSummary
-- See Note [Interesting arguments]
-argSummary env e = go env 0 e
+interestingArg env e = go env 0 e
where
-- n is # value args to which the expression is applied
go env n (Var v)
@@ -1005,8 +1000,6 @@ argSummary env e = go env 0 e
DoneId v' -> go_var n v'
DoneEx e _ -> go (zapSubstEnv env) n e
ContEx tvs cvs ids e -> go (setSubstEnv env tvs cvs ids) n e
- -- NB: substId looks up in the InScopeSet:
- -- we want to get as much IdInfo as possible
go _ _ (Lit l)
| isLitRubbish l = TrivArg -- Leads to unproductive inlining in WWRec, #20035
@@ -1469,11 +1462,18 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env
one_occ IAmDead = True -- Happens in ((\x.1) v)
one_occ OneOcc{ occ_n_br = 1
- , occ_in_lam = NotInsideLam
- , occ_int_cxt = int_cxt }
- = isNotTopLevel top_lvl -- Get rid of allocation
- || (int_cxt==IsInteresting && idArity bndr > 0) -- Function is applied
- -- || (early_phase && not (isConLikeUnfolding unf)) -- See early_phase
+ , occ_in_lam = NotInsideLam }
+ = isNotTopLevel top_lvl || sePhase env /= FinalPhase
+ -- Inline even top level things if not inside lambda
+ -- Can reduce simplifier iterations, when something is later
+ -- inlining and becomes dead
+ --
+ -- But not in FinalPhase because that's just after we have
+ -- carefully floated out constants to top level
+
+ -- = isNotTopLevel top_lvl -- Get rid of allocation
+ -- || (int_cxt==IsInteresting && idArity bndr > 0) -- Function is applied
+ -- OLD || (early_phase && not (isConLikeUnfolding unf)) -- See early_phase
one_occ OneOcc{ occ_n_br = 1
, occ_in_lam = IsInsideLam
, occ_int_cxt = IsInteresting }
=====================================
compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
=====================================
@@ -60,7 +60,6 @@ initSimplMode :: DynFlags -> CompilerPhase -> String -> SimplMode
initSimplMode dflags phase name = SimplMode
{ sm_names = [name]
, sm_phase = phase
- , sm_first_iter = True
, sm_rules = gopt Opt_EnableRewriteRules dflags
, sm_eta_expand = gopt Opt_DoLambdaEtaExpansion dflags
, sm_cast_swizzle = True
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29117fad96e827f1768ca0ac2ba811…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/29117fad96e827f1768ca0ac2ba811…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/az/ghc-cpp] Require # against left margin for all GHC_CPP directives
by Alan Zimmerman (@alanz) 25 May '25
by Alan Zimmerman (@alanz) 25 May '25
25 May '25
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
32bc5dfb by Alan Zimmerman at 2025-05-25T18:27:52+01:00
Require # against left margin for all GHC_CPP directives
- - - - -
3 changed files:
- compiler/GHC/Parser/Lexer.x
- testsuite/tests/ghc-cpp/GhcCpp01.hs
- testsuite/tests/ghc-cpp/GhcCpp01.stderr
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -328,7 +328,7 @@ $unigraphic / { isSmartQuote } { smart_quote_error }
<bol> {
\n ;
-- Ghc CPP symbols, see https://timsong-cpp.github.io/cppwp/n4140/cpp#1
- ^\ * \# \ * @cppkeyword .* \n / { ifExtensionGhcCppNotComment } { cppToken cpp_prag }
+ ^\# \ * @cppkeyword .* \n / { ifExtensionGhcCppNotComment } { cppToken cpp_prag }
^\# line { begin line_prag1 }
^\# / { followedByDigit } { begin line_prag1 }
@@ -350,7 +350,7 @@ $unigraphic / { isSmartQuote } { smart_quote_error }
-- GhcCppBit is set.
<skipping> {
-- Ghc CPP symbols
- ^\ * \# \ * @cppkeyword .* \n { cppToken cpp_prag }
+ ^\# \ * @cppkeyword .* \n { cppToken cpp_prag }
^.*\n { cppSkip }
}
@@ -361,7 +361,7 @@ $unigraphic / { isSmartQuote } { smart_quote_error }
\{ / { notFollowedBy '-' } { hopefully_open_brace }
-- we might encounter {-# here, but {- has been handled already
\n ;
- ^\ * \# \ * @cppkeyword .* \n / { ifExtension GhcCppBit } { cppToken cpp_prag }
+ ^\# \ * @cppkeyword .* \n / { ifExtension GhcCppBit } { cppToken cpp_prag }
^\# (line)? { begin line_prag1 }
^\#.*\n / { ifExtension GhcCppBit } { cppSkip }
@@ -436,7 +436,7 @@ $unigraphic / { isSmartQuote } { smart_quote_error }
-- This one does not check for GhcCpp being set, we use it to
-- terminate normal pragma processing
- ^\ * \# \ * @cppkeyword .* \n { cppToken cpp_prag }
+ ^\# \ * @cppkeyword .* \n { cppToken cpp_prag }
-- ^\# .*\n { cppSkip }
}
=====================================
testsuite/tests/ghc-cpp/GhcCpp01.hs
=====================================
@@ -3,7 +3,7 @@
module GhcCpp01 where
-- Check leading whitespace on a directive
- # define FOO(A,B) A + B
+# define FOO(A,B) A + B
#define FOO(A,B,C) A + B + C
#if FOO(1,FOO(3,4)) == 8
=====================================
testsuite/tests/ghc-cpp/GhcCpp01.stderr
=====================================
@@ -202,7 +202,7 @@
|module GhcCpp01 where
- |-- Check leading whitespace on a directive
-- | # define FOO(A,B) A + B
+- |# define FOO(A,B) A + B
- |#define FOO(A,B,C) A + B + C
- |#if FOO(1,FOO(3,4)) == 8
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32bc5dfbbd32bcf249ffebe01ac7e74…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32bc5dfbbd32bcf249ffebe01ac7e74…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

25 May '25
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
e14f9dfc by Alan Zimmerman at 2025-05-25T18:15:19+01:00
Tweak testing
- - - - -
3e7ac77b by Alan Zimmerman at 2025-05-25T18:15:35+01:00
Only allow unknown cpp pragmas with # in left margin
- - - - -
2 changed files:
- compiler/GHC/Parser/Lexer.x
- utils/check-cpp/Main.hs
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -333,7 +333,7 @@ $unigraphic / { isSmartQuote } { smart_quote_error }
^\# line { begin line_prag1 }
^\# / { followedByDigit } { begin line_prag1 }
- ^\ *\# \ * $idchar+ .*\n / { ifExtensionGhcCppNotComment } { cppSkip }
+ ^\# \ * $idchar+ .*\n / { ifExtensionGhcCppNotComment } { cppSkip } -- No leading space, otherwise clashes with OverloadedLabels
^\# pragma .* \n / { ifExtensionGhcCppNotComment } { cppSkip } -- GCC 3.3 CPP generated, apparently
^\# \! .* \n / { ifExtensionGhcCppNotComment } { cppSkip } -- #!, for scripts -- gcc
=====================================
utils/check-cpp/Main.hs
=====================================
@@ -147,8 +147,8 @@ getPState dflags includes popts filename str = pstate
, pp_defines = predefinedMacros dflags
, pp_scope = (PpScope True PpNoGroup) :| []
}
- -- pstate = Lexer.initParserState initState popts buf loc
- pstate = Lexer.initPragState initState popts buf loc
+ pstate = Lexer.initParserState initState popts buf loc
+ -- pstate = Lexer.initPragState initState popts buf loc
loc = mkRealSrcLoc (mkFastString filename) 1 1
buf = stringToStringBuffer str
@@ -598,7 +598,7 @@ t20 :: IO ()
t20 = do
dump
[ "{-# LANGUAGE CPP #-}"
- , "#if __GLASGOW_HASKELL__ >= 913"
+ , "#if __GLASGOW_HASKELL__ > 913"
, "{-# LANGUAGE GHC_CPP #-}"
, "#endif"
, ""
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5ad6c90dc6932f48b8316e3637a66…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5ad6c90dc6932f48b8316e3637a66…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/az/ghc-cpp] 136 commits: base: Forward port changelog language from 9.12
by Alan Zimmerman (@alanz) 25 May '25
by Alan Zimmerman (@alanz) 25 May '25
25 May '25
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
e650ec3e by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Forward port changelog language from 9.12
- - - - -
94cd9ca4 by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Fix RestructuredText-isms in changelog
- - - - -
7722232c by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Note strictness changes made in 4.16.0.0
Addresses #25886.
- - - - -
3f4b823c by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Factor out ProddableBlocks machinery
- - - - -
6e23fef2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Improve efficiency of proddable blocks structure
Previously the linker's "proddable blocks" check relied on a simple
linked list of spans. This resulted in extremely poor complexity while
linking objects with lots of small sections (e.g. objects built with
split sections).
Rework the mechanism to instead use a simple interval set implemented
via binary search.
Fixes #26009.
- - - - -
ea74860c by Ben Gamari at 2025-05-23T03:43:28-04:00
testsuite: Add simple functional test for ProddableBlockSet
- - - - -
74c4db46 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Drop check for LOAD_LIBRARY_SEARCH_*_DIRS
The `LOAD_LIBRARY_SEARCH_USER_DIRS` and
`LOAD_LIBRARY_SEARCH_DEFAULT_DIRS` were introduced in Windows Vista and
have been available every since. As we no longer support Windows XP we
can drop this check.
Addresses #26009.
- - - - -
972d81d6 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Clean up code style
- - - - -
8a1073a5 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/Hash: Factor out hashBuffer
This is a useful helper which can be used for non-strings as well.
- - - - -
44f509f2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Fix incorrect use of break in nested for
Previously the happy path of PEi386 used `break` in a double-`for` loop
resulting in redundant calls to `LoadLibraryEx`.
Fixes #26052.
- - - - -
bfb12783 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts: Correctly mark const arguments
- - - - -
08469ff8 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Don't repeatedly load DLLs
Previously every DLL-imported symbol would result in a call to
`LoadLibraryEx`. This ended up constituting over 40% of the runtime of
`ghc --interactive -e 42` on Windows. Avoid this by maintaining a
hash-set of loaded DLL names, skipping the call if we have already
loaded the requested DLL.
Addresses #26009.
- - - - -
823d1ccf by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Expand comment describing ProddableBlockSet
- - - - -
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
b331155d by Alan Zimmerman at 2025-05-24T10:56:53+01:00
GHC-CPP: first rough proof of concept
Processes
#define FOO
#ifdef FOO
x = 1
#endif
Into
[ITcppIgnored [L loc ITcppDefine]
,ITcppIgnored [L loc ITcppIfdef]
,ITvarid "x"
,ITequal
,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1})
,ITcppIgnored [L loc ITcppEndif]
,ITeof]
In time, ITcppIgnored will be pushed into a comment
- - - - -
6a6f8336 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Tidy up before re-visiting the continuation mechanic
- - - - -
43993211 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Switch preprocessor to continuation passing style
Proof of concept, needs tidying up
- - - - -
825a7b84 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Small cleanup
- - - - -
76c63619 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Get rid of some cruft
- - - - -
1d9960a6 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Starting to integrate.
Need to get the pragma recognised and set
- - - - -
ae452cba by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Make cppTokens extend to end of line, and process CPP comments
- - - - -
3b8658cc by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Remove unused ITcppDefined
- - - - -
27e0296e by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Allow spaces between # and keyword for preprocessor directive
- - - - -
46b6623c by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Process CPP continuation lines
They are emited as separate ITcppContinue tokens.
Perhaps the processing should be more like a comment, and keep on
going to the end.
BUT, the last line needs to be slurped as a whole.
- - - - -
55001b63 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Accumulate CPP continuations, process when ready
Can be simplified further, we only need one CPP token
- - - - -
75cd6f5f by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Simplify Lexer interface. Only ITcpp
We transfer directive lines through it, then parse them from scratch
in the preprocessor.
- - - - -
308129ed by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Deal with directive on last line, with no trailing \n
- - - - -
4fbe856b by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Start parsing and processing the directives
- - - - -
1a263713 by Alan Zimmerman at 2025-05-24T10:56:53+01:00
Prepare for processing include files
- - - - -
d731efe8 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Move PpState into PreProcess
And initParserState, initPragState too
- - - - -
0c39f394 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Process nested include files
Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci
session, loading utils/check-cpp/Main.hs
- - - - -
c07b44f4 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Split into separate files
- - - - -
45218048 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Starting on expression parser.
But it hangs. Time for Text.Parsec.Expr
- - - - -
b59adfd0 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Start integrating the ghc-cpp work
From https://github.com/alanz/ghc-cpp
- - - - -
06a7c0ed by Alan Zimmerman at 2025-05-24T10:56:54+01:00
WIP
- - - - -
7002db58 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Fixup after rebase
- - - - -
4900171e by Alan Zimmerman at 2025-05-24T10:56:54+01:00
WIP
- - - - -
49bf7922 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Fixup after rebase, including all tests pass
- - - - -
cbab1612 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Change pragma usage to GHC_CPP from GhcCPP
- - - - -
e7d9a03a by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Some comments
- - - - -
9adedee8 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Reformat
- - - - -
42579ec6 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Delete unused file
- - - - -
3b764ee0 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Rename module Parse to ParsePP
- - - - -
4dd44437 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Clarify naming in the parser
- - - - -
d85d3140 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
WIP. Switching to alex/happy to be able to work in-tree
Since Parsec is not available
- - - - -
a5b5d735 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Layering is now correct
- GHC lexer, emits CPP tokens
- accumulated in Preprocessor state
- Lexed by CPP lexer, CPP command extracted, tokens concated with
spaces (to get rid of token pasting via comments)
- if directive lexed and parsed by CPP lexer/parser, and evaluated
- - - - -
da4102a3 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
First example working
Loading Example1.hs into ghci, getting the right results
```
{-# LANGUAGE GHC_CPP #-}
module Example1 where
y = 3
x =
"hello"
"bye now"
foo = putStrLn x
```
- - - - -
8fe65619 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Rebase, and all tests pass except whitespace for generated parser
- - - - -
60387f1b by Alan Zimmerman at 2025-05-24T10:56:54+01:00
More plumbing. Ready for testing tomorrow.
- - - - -
d4b509eb by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Proress. Renamed module State from Types
And at first blush it seems to handle preprocessor scopes properly.
- - - - -
f0e80e26 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Insert basic GHC version macros into parser
__GLASGOW_HASKELL__
__GLASGOW_HASKELL_FULL_VERSION__
__GLASGOW_HASKELL_PATCHLEVEL1__
__GLASGOW_HASKELL_PATCHLEVEL2__
- - - - -
f141eed9 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Re-sync check-cpp for easy ghci work
- - - - -
a0477115 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Get rid of warnings
- - - - -
9422b43b by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Rework macro processing, in check-cpp
Macros kept at the top level, looked up via name, multiple arity
versions per name can be stored
- - - - -
5062fe5b by Alan Zimmerman at 2025-05-24T10:56:54+01:00
WIP. Can crack arguments for #define
Next step it to crack out args in an expansion
- - - - -
1843a281 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
WIP on arg parsing.
- - - - -
865dde13 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Progress. Still screwing up nested parens.
- - - - -
a5d3e335 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Seems to work, but has redundant code
- - - - -
e6addc9d by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Remove redundant code
- - - - -
26c1d4ea by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Reformat
- - - - -
2de9249e by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Expand args, single pass
Still need to repeat until fixpoint
- - - - -
980b9fa8 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Fixed point expansion
- - - - -
56571b26 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Sync the playground to compiler
- - - - -
5274439e by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Working on dumping the GHC_CPP result
But We need to keep the BufSpan in a comment
- - - - -
d689071b by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Keep BufSpan in queued comments in GHC.Parser.Lexer
- - - - -
ed06be80 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Getting close to being able to print the combined tokens
showing what is in and what is out
- - - - -
930e3c73 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
First implementation of dumpGhcCpp.
Example output
First dumps all macros in the state, then the source, showing which
lines are in and which are out
------------------------------
- |#define FOO(A,B) A + B
- |#define FOO(A,B,C) A + B + C
- |#if FOO(1,FOO(3,4)) == 8
- |-- a comment
|x = 1
- |#else
- |x = 5
- |#endif
- - - - -
43ce53a7 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Clean up a bit
- - - - -
4c7fdd44 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Add -ddump-ghc-cpp option and a test based on it
- - - - -
ba0882cd by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Restore Lexer.x rules, we need them for continuation lines
- - - - -
2dcbdc28 by Alan Zimmerman at 2025-05-24T10:56:54+01:00
Lexer.x: trying to sort out the span for continuations
- We need to match on \n at the end of the line
- We cannot simply back up for it
- - - - -
3ab324c9 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Inserts predefined macros. But does not dump properly
Because the cpp tokens have a trailing newline
- - - - -
6c8d9a66 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Remove unnecessary LExer rules
We *need* the ones that explicitly match to the end of the line.
- - - - -
f01db2c7 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Generate correct span for ITcpp
Dump now works, except we do not render trailing `\` for continuation
lines. This is good enough for use in test output.
- - - - -
aae100a5 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Reduce duplication in lexer
- - - - -
36ecf1de by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Tweaks
- - - - -
e21f91eb by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Insert min_version predefined macros into state
The mechanism now works. Still need to flesh out the full set.
- - - - -
b9ff7298 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Trying my alternative pragma syntax.
It works, but dumpGhcCpp is broken, I suspect from the ITcpp token
span update.
- - - - -
7806b47c by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Pragma extraction now works, with both CPP and GHC_CPP
For the following
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 913
{-# LANGUAGE GHC_CPP #-}
#endif
We will enable GHC_CPP only
- - - - -
0cb5848e by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Remove some tracing
- - - - -
4d9ce4da by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Fix test exes for changes
- - - - -
4c1a8aa6 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
For GHC_CPP tests, normalise config-time-based macros
- - - - -
2dd91346 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
WIP
- - - - -
d5dc2164 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
WIP again. What is wrong?
- - - - -
54f7ef01 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Revert to dynflags for normal not pragma lexing
- - - - -
efde6b0b by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Working on getting check-exact to work properly
- - - - -
0584ec31 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Passes CppCommentPlacement test
- - - - -
26bdd707 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Starting on exact printing with GHC_CPP
While overriding normal CPP
- - - - -
51dbf90c by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Correctly store CPP ignored tokens as comments
By populating the lexeme string in it, based on the bufpos
- - - - -
576d82b9 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
WIP
- - - - -
e2eb9351 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Simplifying
- - - - -
cfa6c9ee by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Update the active state logic
- - - - -
e7b67c4c by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Work the new logic into the mainline code
- - - - -
f4897a8a by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Process `defined` operator
- - - - -
20d71b45 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Manage lexer state while skipping tokens
There is very intricate layout-related state used when lexing. If a
CPP directive blanks out some tokens, store this state when the
blanking starts, and restore it when they are no longer being blanked.
- - - - -
f660cc0f by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Track the last token buffer index, for ITCppIgnored
We need to attach the source being skipped in an ITCppIgnored token.
We cannot simply use its BufSpan as an index into the underlying
StringBuffer as it counts unicode chars, not bytes.
So we update the lexer state to store the starting StringBuffer
location for the last token, and use the already-stored length to
extract the correct portion of the StringBuffer being parsed.
- - - - -
dff1b130 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Process the ! operator in GHC_CPP expressions
- - - - -
0b1a1c8e by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Predefine a constant when GHC_CPP is being used.
- - - - -
1b864cbb by Alan Zimmerman at 2025-05-24T10:56:55+01:00
WIP
- - - - -
a122870f by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Skip lines directly in the lexer when required
- - - - -
c08e5cfe by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Properly manage location when accepting tokens again
- - - - -
5bcb5eaa by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Seems to be working now, for Example9
- - - - -
af10cd3a by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Remove tracing
- - - - -
7eba8335 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Fix parsing '*' in block comments
Instead of replacing them with '-'
- - - - -
c120861f by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Keep the trailing backslash in a ITcpp token
- - - - -
aaf6403f by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Deal with only enabling one section of a group.
A group is an instance of a conditional introduced by
#if/#ifdef/#ifndef,
and ending at the final #endif, including intermediate #elsif sections
- - - - -
4cbc14ce by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Replace remaining identifiers with 0 when evaluating
As per the spec
- - - - -
f2efe0a0 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Snapshot before rebase
- - - - -
23a08af3 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Skip non-processed lines starting with #
- - - - -
070a73ba by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Export generateMacros so we can use it in ghc-exactprint
- - - - -
5961854c by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Fix rebase
- - - - -
45d09b97 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Expose initParserStateWithMacrosString
- - - - -
f68f285b by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Fix buggy lexer cppSkip
It was skipping all lines, not just ones prefixed by #
- - - - -
b675bbdc by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Fix evaluation of && to use the correct operator
- - - - -
0590858e by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Deal with closing #-} at the start of a line
- - - - -
81d303bb by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Add the MIN_VERSION_GLASGOW_HASKELL predefined macro
- - - - -
cac17074 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Include MIN_VERSION_GLASGOW_HASKELL in GhcCpp01.stderr
- - - - -
99c5d435 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Use a strict map for macro defines
- - - - -
09cd7fb3 by Alan Zimmerman at 2025-05-24T10:56:55+01:00
Process TIdentifierLParen
Which only matters at the start of #define
- - - - -
9fd72f0b by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Do not provide TIdentifierLParen paren twice
- - - - -
6ec0fa43 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Handle whitespace between identifier and '(' for directive only
- - - - -
167fb4a8 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Expose some Lexer bitmap manipulation helpers
- - - - -
40d267e3 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Deal with line pragmas as tokens
Blows up for dumpGhcCpp though
- - - - -
e6d4be32 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Allow strings delimited by a single quote too
- - - - -
50f024fd by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Allow leading whitespace on cpp directives
As per https://timsong-cpp.github.io/cppwp/n4140/cpp#1
- - - - -
55406057 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Implement GHC_CPP undef
- - - - -
669e08f4 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Sort out expansion of no-arg macros, in a context with args
And make the expansion bottom out, in the case of recursion
- - - - -
24e61f12 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Fix GhcCpp01 test
The LINE pragma stuff works in ghc-exactprint when specifically
setting flag to emit ITline_pragma tokens
- - - - -
a8ebae85 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Process comments in CPP directives
- - - - -
06888106 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Correctly lex pragmas with finel #-} on a newline
- - - - -
85554b54 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Do not process CPP-style comments
- - - - -
e23844a0 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Allow cpp-style comments when GHC_CPP enabled
- - - - -
1754f279 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Return other pragmas as cpp ignored when GHC_CPP active
- - - - -
f10714b5 by Alan Zimmerman at 2025-05-24T10:56:56+01:00
Fix exactprinting default decl
- - - - -
c5ad6c90 by Alan Zimmerman at 2025-05-25T15:29:59+01:00
Reorganise getOptionsFromFile for use in ghc-exactprint
We want to be able to inject predefined macro definitions into the
parser preprocessor state for when we do a hackage roundtrip.
- - - - -
107 changed files:
- compiler/GHC.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Parser/Monad.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Parser.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Parser.hs-boot
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- + compiler/GHC/Parser/PreProcess.hs
- + compiler/GHC/Parser/PreProcess/Eval.hs
- + compiler/GHC/Parser/PreProcess/Lexer.x
- + compiler/GHC/Parser/PreProcess/Macro.hs
- + compiler/GHC/Parser/PreProcess/ParsePP.hs
- + compiler/GHC/Parser/PreProcess/Parser.y
- + compiler/GHC/Parser/PreProcess/ParserM.hs
- + compiler/GHC/Parser/PreProcess/State.hs
- compiler/GHC/Parser/Utils.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- ghc/GHCi/UI.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/stack.yaml.lock
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- rts/Hash.c
- rts/Hash.h
- rts/Linker.c
- rts/LinkerInternals.h
- rts/PathUtils.c
- rts/PathUtils.h
- rts/linker/Elf.c
- rts/linker/MachO.c
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- + rts/linker/ProddableBlocks.c
- + rts/linker/ProddableBlocks.h
- rts/rts.cabal
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/driver/T4437.hs
- testsuite/tests/ghc-api/T11579.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.stderr
- + testsuite/tests/ghc-cpp/all.T
- 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
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/printer/CppCommentPlacement.hs
- + testsuite/tests/rts/TestProddableBlockSet.c
- testsuite/tests/rts/all.T
- + utils/check-cpp/.ghci
- + utils/check-cpp/.gitignore
- + utils/check-cpp/Eval.hs
- + utils/check-cpp/Example1.hs
- + utils/check-cpp/Example10.hs
- + utils/check-cpp/Example11.hs
- + utils/check-cpp/Example12.hs
- + utils/check-cpp/Example13.hs
- + utils/check-cpp/Example2.hs
- + utils/check-cpp/Example3.hs
- + utils/check-cpp/Example4.hs
- + utils/check-cpp/Example5.hs
- + utils/check-cpp/Example6.hs
- + utils/check-cpp/Example7.hs
- + utils/check-cpp/Example8.hs
- + utils/check-cpp/Example9.hs
- + utils/check-cpp/Lexer.x
- + utils/check-cpp/Macro.hs
- + utils/check-cpp/Main.hs
- + utils/check-cpp/ParsePP.hs
- + utils/check-cpp/ParseSimulate.hs
- + utils/check-cpp/Parser.y
- + utils/check-cpp/ParserM.hs
- + utils/check-cpp/PreProcess.hs
- + utils/check-cpp/README.md
- + utils/check-cpp/State.hs
- + utils/check-cpp/run.sh
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/check-exact/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2eb0e2d66956ecf1531bbab902d5b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2eb0e2d66956ecf1531bbab902d5b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] 34 commits: Refactor mkTopLevImportedEnv out of mkTopLevEnv
by Apoorv Ingle (@ani) 23 May '25
by Apoorv Ingle (@ani) 23 May '25
23 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
e46c6b18 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00
Refactor mkTopLevImportedEnv out of mkTopLevEnv
This makes the code clearer and allows the top-level import context to
be fetched directly from the HomeModInfo through the API (e.g. useful
for the debugger).
- - - - -
0ce0d263 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00
Export sizeOccEnv from GHC.Types.Name.Occurrence
Counts the number of OccNames in an OccEnv
- - - - -
165f98d8 by Simon Peyton Jones at 2025-05-06T09:02:39-04:00
Fix a bad untouchability bug im simplifyInfer
This patch addresses #26004. The root cause was that simplifyInfer
was willing to unify variables "far out". The fix, in
runTcSWithEvBinds', is to initialise the inert set given-eq level with
the current level. See
(TGE6) in Note [Tracking Given equalities]
in GHC.Tc.Solver.InertSet
Two loosely related refactors:
* Refactored approximateWCX to return just the free type
variables of the un-quantified constraints. That avoids duplication
of work (these free vars are needed in simplifyInfer) and makes it
clearer that the constraints themselves are irrelevant.
* A little local refactor of TcSMode, which reduces the number of
parameters to runTcSWithEvBinds
- - - - -
6e67fa08 by Ben Gamari at 2025-05-08T06:21:21-04:00
llvmGen: Fix built-in variable predicate
Previously the predicate to identify LLVM builtin global variables was
checking for `$llvm` rather than `@llvm` as it should.
- - - - -
a9d0a22c by Ben Gamari at 2025-05-08T06:21:22-04:00
llvmGen: Fix linkage of built-in arrays
LLVM now insists that built-in arrays use Appending linkage, not
Internal.
Fixes #25769.
- - - - -
9c6d2b1b by sheaf at 2025-05-08T06:22:11-04:00
Use mkTrAppChecked in ds_ev_typeable
This change avoids violating the invariant of mkTrApp according to which
the argument should not be a fully saturated function type.
This ensures we don't return false negatives for type equality
involving function types.
Fixes #25998
- - - - -
75cadf81 by Ryan Hendrickson at 2025-05-08T06:22:55-04:00
haddock: Preserve indentation in multiline examples
Intended for use with :{ :}, but doesn't look for those characters. Any
consecutive lines with birdtracks will only have initial whitespace
stripped up to the column of the first line.
- - - - -
fee9b351 by Cheng Shao at 2025-05-08T06:23:36-04:00
ci: re-enable chrome for wasm ghci browser tests
Currently only firefox is enabled for wasm ghci browser tests, for
some reason testing with chrome works on my machine but gets stuck on
gitlab instance runners. This patch re-enables testing with chrome by
passing `--no-sandbox`, since chrome sandboxing doesn't work in
containers without `--cap-add=SYS_ADMIN`.
- - - - -
282df905 by Vladislav Zavialov at 2025-05-09T03:18:25-04:00
Take subordinate 'type' specifiers into account
This patch fixes multiple bugs (#22581, #25983, #25984, #25991)
in name resolution of subordinate import lists.
Bug #22581
----------
In subordinate import lists, the use of the `type` namespace specifier
used to be ignored. For example, this import statement was incorrectly
accepted:
import Prelude (Bool(type True))
Now it results in an error message:
<interactive>:2:17: error: [GHC-51433]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported,
but its subordinate item ‘True’ is not in the type namespace.
Bug #25983
----------
In subordinate import lists within a `hiding` clause, non-existent
items led to a poor warning message with -Wdodgy-imports. Consider:
import Prelude hiding (Bool(X))
The warning message for this import statement used to misreport the
cause of the problem:
<interactive>:3:24: warning: [GHC-56449] [-Wdodgy-imports]
In the import of ‘Prelude’:
an item called ‘Bool’ is exported, but it is a type.
Now the warning message is correct:
<interactive>:2:24: warning: [GHC-10237] [-Wdodgy-imports]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported, but it does not export
any constructors or record fields called ‘X’.
Bug #25984
----------
In subordinate import lists within a `hiding` clause, non-existent
items resulted in the entire import declaration being discarded.
For example, this program was incorrectly accepted:
import Prelude hiding (Bool(True,X))
t = True
Now it results in an error message:
<interactive>:2:5: error: [GHC-88464]
Data constructor not in scope: True
Bug #25991
----------
In subordinate import lists, it was not possible to refer to a class
method if there was an associated type of the same name:
module M_helper where
class C a b where
type a # b
(#) :: a -> b -> ()
module M where
import M_helper (C((#)))
This import declaration failed with:
M.hs:2:28: error: [GHC-10237]
In the import of ‘M_helper’:
an item called ‘C’ is exported, but it does not export any children
(constructors, class methods or field names) called ‘#’.
Now it is accepted.
Summary
-------
The changes required to fix these bugs are almost entirely confined to
GHC.Rename.Names. Other than that, there is a new error constructor
BadImportNonTypeSubordinates with error code [GHC-51433].
Test cases:
T22581a T22581b T22581c T22581d
T25983a T25983b T25983c T25983d T25983e T25983f T25983g
T25984a T25984b
T25991a T25991b1 T25991b2
- - - - -
51b0ce8f by Simon Peyton Jones at 2025-05-09T03:19:07-04:00
Slighty improve `dropMisleading`
Fix #26105, by upgrading the (horrible, hacky) `dropMisleading`
function.
This fix makes things a bit better but does not cure the underlying
problem.
- - - - -
7b2d1e6d by Simon Peyton Jones at 2025-05-11T03:24:47-04:00
Refine `noGivenNewtypeReprEqs` to account for quantified constraints
This little MR fixes #26020. We are on the edge of completeness
for newtype equalities (that doesn't change) but this MR makes GHC
a bit more consistent -- and fixes the bug reported.
- - - - -
eaa8093b by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: mark freeJSVal as INLINE
This patch marks `freeJSVal` as `INLINE` for the wasm backend. I
noticed that the `freeJSVal` invocations are not inlined when
inspecting STG/Cmm dumps of downstream libraries that use release
build of the wasm backend. The performance benefit of inlining here is
very modest, but so is the cost anyway; if you are using `freeJSVal`
at all then you care about every potential chance to improve
performance :)
- - - - -
eac196df by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: add zero length fast path for fromJSString
This patch adds a zero length fast path for `fromJSString`; when
marshaling a zero-length `JSString` we don't need to allocate an empty
`ByteArray#` at all.
- - - - -
652cba7e by Peng Fan at 2025-05-14T04:24:35-04:00
Add LoongArch NCG support
Not supported before.
- - - - -
c01f4374 by Lin Runze at 2025-05-14T04:24:35-04:00
ci: Add LoongArch64 cross-compile CI for testing
- - - - -
ce6cf240 by Ben Gamari at 2025-05-14T04:25:18-04:00
rts/linker: Don't fail due to RTLD_NOW
In !12264 we started using the NativeObj machinery introduced some time
ago for loading of shared objects. One of the side-effects of this
change is shared objects are now loaded eagerly (i.e. with `RTLD_NOW`).
This is needed by NativeObj to ensure full visibility of the mappings of
the loaded object, which is in turn needed for safe shared object
unloading.
Unfortunately, this change subtly regressed, causing compilation
failures in some programs. Specifically, shared objects which refer to
undefined symbols (e.g. which may be usually provided by either the
executable image or libraries loaded via `dlopen`) will fail to load
with eager binding. This is problematic as GHC loads all package
dependencies while, e.g., evaluating TemplateHaskell splices. This
results in compilation failures in programs depending upon (but not
using at compile-time) packages with undefined symbol references.
To mitigate this NativeObj now first attempts to load an object via
eager binding, reverting to lazy binding (and disabling unloading) on
failure.
See Note [Don't fail due to RTLD_NOW].
Fixes #25943.
- - - - -
88ee8bb5 by Sylvain Henry at 2025-05-14T04:26:15-04:00
Deprecate GHC.JS.Prim.Internal.Build (#23432)
Deprecated as per CLC proposal 329 (https://github.com/haskell/core-libraries-committee/issues/329)
- - - - -
b4ed465b by Cheng Shao at 2025-05-14T04:26:57-04:00
libffi: update to 3.4.8
Bumps libffi submodule.
- - - - -
a3e71296 by Matthew Pickering at 2025-05-14T04:27:38-04:00
Remove leftover trace
- - - - -
2d0ecdc6 by Cheng Shao at 2025-05-14T04:28:19-04:00
Revert "ci: re-enable chrome for wasm ghci browser tests"
This reverts commit fee9b351fa5a35d5778d1252789eacaaf5663ae8.
Unfortunately the chrome test jobs may still timeout on certain
runners (e.g. OpenCape) for unknown reasons.
- - - - -
3b3a5dec by Ben Gamari at 2025-05-15T16:10:01-04:00
Don't emit unprintable characters when printing Uniques
When faced with an unprintable tag we now instead print the codepoint
number.
Fixes #25989.
(cherry picked from commit e832b1fadee66e8d6dd7b019368974756f8f8c46)
- - - - -
e1ef8974 by Mike Pilgrem at 2025-05-16T16:09:14-04:00
Translate iff in Haddock documentation into everyday English
- - - - -
235f5226 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
- Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed.
- Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx`
- `tcXExpr` is less hacky now
- do not look through HsExpansion applications
- kill OrigPat and remove HsThingRn From VAExpansion
- look through XExpr ExpandedThingRn while inferring type of head
- always set in generated code after stepping inside a ExpandedThingRn
- fixing record update error messages
- remove special case of tcbody from tcLambdaMatches
- wrap last stmt expansion in a HsPar so that the error messages are prettier
- remove special case of dsExpr for ExpandedThingTc
- make EExpand (HsExpr GhcRn) instead of EExpand HsThingRn
- fixing error messages for rebindable
- - - - -
b4ec59e8 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
some progress on tick
- - - - -
87c9b23a by Apoorv Ingle at 2025-05-19T14:25:26-05:00
remove adhoc cases from ticks
- - - - -
de43d1f3 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
fix the case where head of the application chain is an expanded expression and the argument is a type application c.f. T19167.hs
- - - - -
418a83ec by Apoorv Ingle at 2025-05-19T14:25:26-05:00
move setQLInstLevel inside tcInstFun
- - - - -
2e45e697 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
ignore ds warnings originating from gen locations
- - - - -
224d34a8 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
filter expr stmts error msgs
- - - - -
38ca6121 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
exception for AppDo while making error ctxt
- - - - -
e798161a by Apoorv Ingle at 2025-05-19T14:25:26-05:00
moving around things for locations and error ctxts
- - - - -
4e761612 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
popErrCtxt doesn't push contexts and popErrCtxts in the first argument to bind and >> in do expansion statements
- - - - -
549ece3b by Apoorv Ingle at 2025-05-19T14:25:26-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
3a7db680 by Apoorv Ingle at 2025-05-19T14:25:26-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
152 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/Dwarf/Constants.hs
- + compiler/GHC/CmmToAsm/LA64.hs
- + compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- + compiler/GHC/CmmToAsm/LA64/Cond.hs
- + compiler/GHC/CmmToAsm/LA64/Instr.hs
- + compiler/GHC/CmmToAsm/LA64/Ppr.hs
- + compiler/GHC/CmmToAsm/LA64/RegInfo.hs
- + compiler/GHC/CmmToAsm/LA64/Regs.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
- + compiler/GHC/CmmToAsm/Reg/Linear/LA64.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Platform/LoongArch64.hs → compiler/GHC/Platform/LA64.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- + compiler/GHC/Tc/Gen/App.hs-boot
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/explicit_namespaces.rst
- hadrian/bindist/config.mk.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Settings/Builders/RunTest.hs
- libffi-tarballs
- libraries/base/changelog.md
- libraries/base/src/GHC/JS/Prim/Internal/Build.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Maybe.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
- rts/linker/LoadNativeObjPosix.c
- testsuite/tests/deSugar/should_compile/T10662.stderr
- testsuite/tests/deSugar/should_compile/T3263-1.stderr
- testsuite/tests/deSugar/should_compile/T3263-2.stderr
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/driver/RecompExports/RecompExports1.stderr
- testsuite/tests/driver/RecompExports/RecompExports4.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/module/T21826.stderr
- testsuite/tests/module/mod81.stderr
- testsuite/tests/module/mod91.stderr
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- + testsuite/tests/rename/should_compile/T22581c.hs
- + testsuite/tests/rename/should_compile/T22581c_helper.hs
- + testsuite/tests/rename/should_compile/T22581d.script
- + testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25983a.hs
- + testsuite/tests/rename/should_compile/T25983a.stderr
- + testsuite/tests/rename/should_compile/T25983b.hs
- + testsuite/tests/rename/should_compile/T25983b.stderr
- + testsuite/tests/rename/should_compile/T25983c.hs
- + testsuite/tests/rename/should_compile/T25983c.stderr
- + testsuite/tests/rename/should_compile/T25983d.hs
- + testsuite/tests/rename/should_compile/T25983d.stderr
- + testsuite/tests/rename/should_compile/T25983e.hs
- + testsuite/tests/rename/should_compile/T25983e.stderr
- + testsuite/tests/rename/should_compile/T25983f.hs
- + testsuite/tests/rename/should_compile/T25983f.stderr
- + testsuite/tests/rename/should_compile/T25983g.hs
- + testsuite/tests/rename/should_compile/T25983g.stderr
- + testsuite/tests/rename/should_compile/T25984a.hs
- + testsuite/tests/rename/should_compile/T25984a.stderr
- + testsuite/tests/rename/should_compile/T25984a_helper.hs
- + testsuite/tests/rename/should_compile/T25991a.hs
- + testsuite/tests/rename/should_compile/T25991a_helper.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T22581a.hs
- + testsuite/tests/rename/should_fail/T22581a.stderr
- + testsuite/tests/rename/should_fail/T22581a_helper.hs
- + testsuite/tests/rename/should_fail/T22581b.hs
- + testsuite/tests/rename/should_fail/T22581b.stderr
- + testsuite/tests/rename/should_fail/T22581b_helper.hs
- + testsuite/tests/rename/should_fail/T25984b.hs
- + testsuite/tests/rename/should_fail/T25984b.stderr
- + testsuite/tests/rename/should_fail/T25991b1.hs
- + testsuite/tests/rename/should_fail/T25991b1.stderr
- + testsuite/tests/rename/should_fail/T25991b2.hs
- + testsuite/tests/rename/should_fail/T25991b2.stderr
- + testsuite/tests/rename/should_fail/T25991b_helper.hs
- testsuite/tests/rename/should_fail/T9006.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rts/all.T
- testsuite/tests/typecheck/should_compile/T14590.stderr
- + testsuite/tests/typecheck/should_compile/T26020.hs
- + testsuite/tests/typecheck/should_compile/T26020a.hs
- + testsuite/tests/typecheck/should_compile/T26020a_help.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- + testsuite/tests/typecheck/should_fail/T26004.hs
- + testsuite/tests/typecheck/should_fail/T26004.stderr
- + testsuite/tests/typecheck/should_fail/T26015.hs
- + testsuite/tests/typecheck/should_fail/T26015.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7453.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- + testsuite/tests/typecheck/should_run/T25998.hs
- + testsuite/tests/typecheck/should_run/T25998.stdout
- testsuite/tests/typecheck/should_run/all.T
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dc324fdfa9c2844f996f3ee6473bd…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dc324fdfa9c2844f996f3ee6473bd…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][master] base: Expose Backtraces constructor and fields
by Marge Bot (@marge-bot) 23 May '25
by Marge Bot (@marge-bot) 23 May '25
23 May '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
7 changed files:
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.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
=====================================
@@ -22,6 +22,7 @@
* `GHC.TypeNats.Internal`
* `GHC.ExecutionStack.Internal`.
* Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
+ * Expose constructor and field of `Backtraces` from `Control.Exception.Backtrace`, as per [CLC #199](https://github.com/haskell/core-libraries-committee/issues/199#issuecomment-1954662391)
* Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
=====================================
libraries/base/src/Control/Exception/Backtrace.hs
=====================================
@@ -51,7 +51,7 @@ module Control.Exception.Backtrace
, getBacktraceMechanismState
, setBacktraceMechanismState
-- * Collecting backtraces
- , Backtraces
+ , Backtraces(..)
, displayBacktraces
, collectBacktraces
) where
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -9,7 +9,7 @@ module GHC.Internal.Exception.Backtrace
, getBacktraceMechanismState
, setBacktraceMechanismState
-- * Collecting backtraces
- , Backtraces
+ , Backtraces(..)
, displayBacktraces
, collectBacktraces
) where
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = ...
+ data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = ...
+ data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = ...
+ data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -322,7 +322,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = ...
+ data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17db44c5b32fff82ea988fa4f1a233d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17db44c5b32fff82ea988fa4f1a233d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
8 changed files:
- compiler/GHC.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- ghc/GHCi/UI.hs
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -1307,7 +1307,7 @@ typecheckModule pmod = do
minf_instances = fixSafeInstances safe $ instEnvElts $ md_insts details,
minf_iface = Nothing,
minf_safe = safe,
- minf_modBreaks = emptyModBreaks
+ minf_modBreaks = Nothing
}}
-- | Desugar a typechecked module.
@@ -1461,7 +1461,7 @@ data ModuleInfo = ModuleInfo {
minf_instances :: [ClsInst],
minf_iface :: Maybe ModIface,
minf_safe :: SafeHaskellMode,
- minf_modBreaks :: ModBreaks
+ minf_modBreaks :: Maybe ModBreaks
}
-- We don't want HomeModInfo here, because a ModuleInfo applies
-- to package modules too.
@@ -1490,7 +1490,7 @@ getPackageModuleInfo hsc_env mdl
minf_instances = error "getModuleInfo: instances for package module unimplemented",
minf_iface = Just iface,
minf_safe = getSafeMode $ mi_trust iface,
- minf_modBreaks = emptyModBreaks
+ minf_modBreaks = Nothing
}))
availsToGlobalRdrEnv :: HasDebugCallStack => HscEnv -> Module -> [AvailInfo] -> IfGlobalRdrEnv
@@ -1567,7 +1567,7 @@ modInfoIface = minf_iface
modInfoSafe :: ModuleInfo -> SafeHaskellMode
modInfoSafe = minf_safe
-modInfoModBreaks :: ModuleInfo -> ModBreaks
+modInfoModBreaks :: ModuleInfo -> Maybe ModBreaks
modInfoModBreaks = minf_modBreaks
isDictonaryId :: Id -> Bool
=====================================
compiler/GHC/ByteCode/Types.hs
=====================================
@@ -19,7 +19,7 @@ module GHC.ByteCode.Types
, ItblEnv, ItblPtr(..)
, AddrEnv, AddrPtr(..)
, CgBreakInfo(..)
- , ModBreaks (..), BreakIndex, emptyModBreaks
+ , ModBreaks (..), BreakIndex
, CCostCentre
, FlatBag, sizeFlatBag, fromSmallArray, elemsFlatBag
) where
@@ -45,12 +45,11 @@ import Foreign
import Data.Array
import Data.ByteString (ByteString)
import Data.IntMap (IntMap)
-import qualified Data.IntMap as IntMap
import qualified GHC.Exts.Heap as Heap
import GHC.Stack.CCS
import GHC.Cmm.Expr ( GlobalRegSet, emptyRegSet, regSetToList )
import GHC.Iface.Syntax
-import Language.Haskell.Syntax.Module.Name (ModuleName, mkModuleNameFS)
+import Language.Haskell.Syntax.Module.Name (ModuleName)
import GHC.Unit.Types (UnitId(..))
-- -----------------------------------------------------------------------------
@@ -250,7 +249,7 @@ data CCostCentre
-- | All the information about the breakpoints for a module
data ModBreaks
= ModBreaks
- { modBreaks_flags :: ForeignRef BreakArray
+ { modBreaks_flags :: !(ForeignRef BreakArray)
-- ^ The array of flags, one per breakpoint,
-- indicating which breakpoints are enabled.
, modBreaks_locs :: !(Array BreakIndex SrcSpan)
@@ -281,20 +280,6 @@ seqModBreaks ModBreaks{..} =
rnf modBreaks_module `seq`
rnf modBreaks_module_unitid
--- | Construct an empty ModBreaks
-emptyModBreaks :: ModBreaks
-emptyModBreaks = ModBreaks
- { modBreaks_flags = error "ModBreaks.modBreaks_array not initialised"
- -- ToDo: can we avoid this?
- , modBreaks_locs = array (0,-1) []
- , modBreaks_vars = array (0,-1) []
- , modBreaks_decls = array (0,-1) []
- , modBreaks_ccs = array (0,-1) []
- , modBreaks_breakInfo = IntMap.empty
- , modBreaks_module = mkModuleNameFS nilFS
- , modBreaks_module_unitid = UnitId nilFS
- }
-
{-
Note [Field modBreaks_decls]
~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/HsToCore/Breakpoints.hs
=====================================
@@ -18,6 +18,7 @@ import GHC.Utils.Outputable as Outputable
import Data.List (intersperse)
import Data.Array
+import qualified Data.IntMap as IntMap
-- | Initialize memory for breakpoint data that is shared between the bytecode
-- generator and the interpreter.
@@ -38,15 +39,16 @@ mkModBreaks interp mod extendedMixEntries
locsTicks = listArray (0,count-1) [ tick_loc t | t <- entries ]
varsTicks = listArray (0,count-1) [ tick_ids t | t <- entries ]
declsTicks = listArray (0,count-1) [ tick_path t | t <- entries ]
- return $ emptyModBreaks
- { modBreaks_flags = breakArray
- , modBreaks_locs = locsTicks
- , modBreaks_vars = varsTicks
- , modBreaks_decls = declsTicks
- , modBreaks_ccs = ccs
- , modBreaks_module = moduleName mod
- , modBreaks_module_unitid = toUnitId $ moduleUnit mod
- }
+ return $ ModBreaks
+ { modBreaks_flags = breakArray
+ , modBreaks_locs = locsTicks
+ , modBreaks_vars = varsTicks
+ , modBreaks_decls = declsTicks
+ , modBreaks_ccs = ccs
+ , modBreaks_breakInfo = IntMap.empty
+ , modBreaks_module = moduleName mod
+ , modBreaks_module_unitid = toUnitId $ moduleUnit mod
+ }
mkCCSArray
:: Interp -> Module -> Int -> [Tick]
=====================================
compiler/GHC/Runtime/Debugger/Breakpoints.hs
=====================================
@@ -145,15 +145,17 @@ resolveFunctionBreakpoint inp = do
validateBP _ "" (Just _) = pure $ Just $ text "Function name is missing"
validateBP _ fun_str (Just modl) = do
isInterpr <- GHC.moduleIsInterpreted modl
- (_, decls) <- getModBreak modl
mb_err_msg <- case isInterpr of
- False -> pure $ Just $ text "Module" <+> quotes (ppr modl)
- <+> text "is not interpreted"
- True -> case fun_str `elem` (intercalate "." <$> elems decls) of
- False -> pure $ Just $
- text "No breakpoint found for" <+> quotes (text fun_str)
- <+> text "in module" <+> quotes (ppr modl)
- True -> pure Nothing
+ False -> pure $ Just $ text "Module" <+> quotes (ppr modl) <+> text "is not interpreted"
+ True -> do
+ mb_modbreaks <- getModBreak modl
+ let found = case mb_modbreaks of
+ Nothing -> False
+ Just mb -> fun_str `elem` (intercalate "." <$> elems (GHC.modBreaks_decls mb))
+ if found
+ then pure Nothing
+ else pure $ Just $ text "No breakpoint found for" <+> quotes (text fun_str)
+ <+> text "in module" <+> quotes (ppr modl)
pure mb_err_msg
-- | The aim of this function is to find the breakpoints for all the RHSs of
@@ -184,8 +186,7 @@ type TickArray = Array Int [(GHC.BreakIndex,RealSrcSpan)]
makeModuleLineMap :: GhcMonad m => Module -> m (Maybe TickArray)
makeModuleLineMap m = do
mi <- GHC.getModuleInfo m
- return $
- mkTickArray . assocs . GHC.modBreaks_locs . GHC.modInfoModBreaks <$> mi
+ return $ mkTickArray . assocs . GHC.modBreaks_locs <$> (GHC.modInfoModBreaks =<< mi)
where
mkTickArray :: [(BreakIndex, SrcSpan)] -> TickArray
mkTickArray ticks
@@ -195,15 +196,12 @@ makeModuleLineMap m = do
max_line = foldr max 0 [ GHC.srcSpanEndLine sp | (_, RealSrcSpan sp _) <- ticks ]
srcSpanLines pan = [ GHC.srcSpanStartLine pan .. GHC.srcSpanEndLine pan ]
--- | Get the 'modBreaks_locs' and 'modBreaks_decls' of the given 'Module'
+-- | Get the 'ModBreaks' of the given 'Module' when available
getModBreak :: GHC.GhcMonad m
- => Module -> m (Array Int SrcSpan, Array Int [String])
+ => Module -> m (Maybe ModBreaks)
getModBreak m = do
mod_info <- fromMaybe (panic "getModBreak") <$> GHC.getModuleInfo m
- let modBreaks = GHC.modInfoModBreaks mod_info
- let ticks = GHC.modBreaks_locs modBreaks
- let decls = GHC.modBreaks_decls modBreaks
- return (ticks, decls)
+ pure $ GHC.modInfoModBreaks mod_info
--------------------------------------------------------------------------------
-- Getting current breakpoint information
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -522,9 +522,8 @@ result_fs = fsLit "_result"
-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'.
readModBreaks :: HscEnv -> Module -> IO ModBreaks
-readModBreaks hsc_env mod =
- getModBreaks . expectJust <$>
- HUG.lookupHugByModule mod (hsc_HUG hsc_env)
+readModBreaks hsc_env mod = expectJust . getModBreaks . expectJust <$> HUG.lookupHugByModule mod (hsc_HUG hsc_env)
+
bindLocalsAtBreakpoint
:: HscEnv
=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -435,22 +435,24 @@ handleSeqHValueStatus interp unit_env eval_status =
resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
let put x = putStrLn ("*** Ignoring breakpoint " ++ (showSDocUnsafe x))
+ let nothing_case = put $ brackets . ppr $ mkGeneralSrcSpan (fsLit "<unknown>")
case maybe_break of
- Nothing ->
+ Nothing -> nothing_case
-- Nothing case - should not occur!
-- Reason: Setting of flags in libraries/ghci/GHCi/Run.hs:evalOptsSeq
- put $ brackets . ppr $
- mkGeneralSrcSpan (fsLit "<unknown>")
Just break -> do
let bi = evalBreakpointToId break
-- Just case: Stopped at a breakpoint, extract SrcSpan information
-- from the breakpoint.
- breaks_tick <- getModBreaks . expectJust <$>
+ mb_modbreaks <- getModBreaks . expectJust <$>
lookupHugByModule (ibi_tick_mod bi) (ue_home_unit_graph unit_env)
- put $ brackets . ppr $
- (modBreaks_locs breaks_tick) ! ibi_tick_index bi
+ case mb_modbreaks of
+ -- Nothing case - should not occur! We should have the appropriate
+ -- breakpoint information
+ Nothing -> nothing_case
+ Just modbreaks -> put $ brackets . ppr $ (modBreaks_locs modbreaks) ! ibi_tick_index bi
-- resume the seq (:force) processing in the iserv process
withForeignRef resume_ctxt_fhv $ \hval -> do
@@ -737,14 +739,14 @@ fromEvalResult :: EvalResult a -> IO a
fromEvalResult (EvalException e) = throwIO (fromSerializableException e)
fromEvalResult (EvalSuccess a) = return a
-getModBreaks :: HomeModInfo -> ModBreaks
+getModBreaks :: HomeModInfo -> Maybe ModBreaks
getModBreaks hmi
| Just linkable <- homeModInfoByteCode hmi,
-- The linkable may have 'DotO's as well; only consider BCOs. See #20570.
[cbc] <- linkableBCOs linkable
- = fromMaybe emptyModBreaks (bc_breaks cbc)
+ = bc_breaks cbc
| otherwise
- = emptyModBreaks -- probably object code
+ = Nothing -- probably object code
-- | Interpreter uses Profiling way
interpreterProfiled :: Interp -> Bool
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -439,8 +439,8 @@ schemeER_wrk d p rhs = schemeE d 0 p rhs
--
-- If the breakpoint is inlined from another module, look it up in the home
-- package table.
--- If the module doesn't exist there, or its module pointer is null (which means
--- that the 'ModBreaks' value is uninitialized), skip the instruction.
+-- If the module doesn't exist there, or if the 'ModBreaks' value is
+-- uninitialized, skip the instruction (i.e. return Nothing).
break_info ::
HscEnv ->
Module ->
@@ -449,18 +449,11 @@ break_info ::
BcM (Maybe ModBreaks)
break_info hsc_env mod current_mod current_mod_breaks
| mod == current_mod
- = pure $ check_mod_ptr =<< current_mod_breaks
+ = pure current_mod_breaks
| otherwise
= ioToBc (lookupHpt (hsc_HPT hsc_env) (moduleName mod)) >>= \case
- Just hp -> pure $ check_mod_ptr (getModBreaks hp)
+ Just hp -> pure $ getModBreaks hp
Nothing -> pure Nothing
- where
- check_mod_ptr mb
- | mod_ptr <- modBreaks_module mb
- , not $ nullFS $ moduleNameFS mod_ptr
- = Just mb
- | otherwise
- = Nothing
getVarOffSets :: Platform -> StackDepth -> BCEnv -> [Id] -> [Maybe (Id, WordOff)]
getVarOffSets platform depth env = map getOffSet
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -3629,8 +3629,10 @@ completeBreakpoint = wrapCompleter spaces $ \w -> do -- #3000
-- Return all possible bids for a given Module
bidsByModule :: GhciMonad m => [ModuleName] -> Module -> m [String]
bidsByModule nonquals mod = do
- (_, decls) <- getModBreak mod
- let bids = nub $ declPath <$> elems decls
+ mb_decls <- fmap GHC.modBreaks_decls <$> getModBreak mod
+ let bids = case mb_decls of
+ Just decls -> nub $ declPath <$> elems decls
+ Nothing -> []
pure $ case (moduleName mod) `elem` nonquals of
True -> bids
False -> (combineModIdent (showModule mod)) <$> bids
@@ -3656,11 +3658,14 @@ completeBreakpoint = wrapCompleter spaces $ \w -> do -- #3000
-- declarations. See Note [Field modBreaks_decls] in GHC.ByteCode.Types
addNestedDecls :: GhciMonad m => (String, Module) -> m [String]
addNestedDecls (ident, mod) = do
- (_, decls) <- getModBreak mod
- let (mod_str, topLvl, _) = splitIdent ident
- ident_decls = [ elm | elm@(el : _) <- elems decls, el == topLvl ]
- bids = nub $ declPath <$> ident_decls
- pure $ map (combineModIdent mod_str) bids
+ mb_decls <- fmap GHC.modBreaks_decls <$> getModBreak mod
+ case mb_decls of
+ Nothing -> pure []
+ Just decls -> do
+ let (mod_str, topLvl, _) = splitIdent ident
+ ident_decls = [ elm | elm@(el : _) <- elems decls, el == topLvl ]
+ bids = nub $ declPath <$> ident_decls
+ pure $ map (combineModIdent mod_str) bids
completeModule = wrapIdentCompleterMod $ \w -> do
hsc_env <- GHC.getSession
@@ -4066,7 +4071,7 @@ breakById inp = do
case mb_error of
Left sdoc -> printForUser sdoc
Right (mod, mod_info, fun_str) -> do
- let modBreaks = GHC.modInfoModBreaks mod_info
+ let modBreaks = expectJust (GHC.modInfoModBreaks mod_info)
findBreakAndSet mod $ \_ -> findBreakForBind fun_str modBreaks
breakSyntax :: a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9de9e0bc2ac0ad6273fe6ee5960801…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9de9e0bc2ac0ad6273fe6ee5960801…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/romes/step-out] debugger: Implement step-out feature
by Rodrigo Mesquita (@alt-romes) 23 May '25
by Rodrigo Mesquita (@alt-romes) 23 May '25
23 May '25
Rodrigo Mesquita pushed to branch wip/romes/step-out at Glasgow Haskell Compiler / GHC
Commits:
73b258cc by Rodrigo Mesquita at 2025-05-23T17:32:20+01:00
debugger: Implement step-out feature
TODO UPDATE DESCRIPTION
Implements support for stepping-out of a function (aka breaking right after
returning from a function) in the interactive debugger.
It also introduces a GHCi command :stepout to step-out of a function
being debugged in the interpreter. The feature is described as:
Stop at the first breakpoint immediately after returning from the current
function scope.
Known limitations: because a function tail-call does not push a stack
frame, if step-out is used inside of a function that was tail-called,
execution will not be returned to its caller, but rather its caller's
first non-tail caller. On the other hand, it means the debugger
follows the more realistic execution of the program.
In the following example:
.. code-block:: none
f = do
a
b <--- (1) set breakpoint then step in here
c
b = do
...
d <--- (2) step-into this tail call
d = do
...
something <--- (3) step-out here
...
Stepping-out will stop execution at the `c` invokation in `f`, rather than
stopping at `b`.
The key implementation bit is simple:
When step-out is set and the interpreter hits a RETURN instruction,
enable "stop at the immediate next breakpoint" (aka single-step).
See also `Note [Debugger Step-out]` in `rts/Interpreter.c`
Note [Debugger Step-out]
~~~~~~~~~~~~~~~~~~~~~~~~
When the global debugger step-out flag is set (`rts_stop_after_return`),
the interpreter must yield execution right after the first RETURN.
When stepping-out, we simply enable `rts_stop_next_breakpoint` when we hit a
return instruction (in `do_return_pointer` and `do_return_nonpointer`).
The step-out flag is cleared and must be re-enabled explicitly to step-out again.
A limitation of this approach is that stepping-out of a function that was
tail-called will skip its caller since no stack frame is pushed for a tail
call (i.e. a tail call returns directly to its caller's first non-tail caller).
Fixes #26042
- - - - -
32 changed files:
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Driver/Config.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc
- libraries/ghc-heap/tests/parse_tso_flags.hs
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- + rts/Debugger.cmm
- rts/Interpreter.c
- rts/Interpreter.h
- rts/Printer.c
- rts/RtsSymbols.c
- rts/include/rts/Constants.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
- + testsuite/tests/ghci.debugger/scripts/T26042a.hs
- + testsuite/tests/ghci.debugger/scripts/T26042a.script
- + testsuite/tests/ghci.debugger/scripts/T26042a.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042b.hs
- + testsuite/tests/ghci.debugger/scripts/T26042b.script
- + testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042c.hs
- + testsuite/tests/ghci.debugger/scripts/T26042c.script
- + testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73b258ccdb7b2f9c76c407f439f6e7b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73b258ccdb7b2f9c76c407f439f6e7b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0