[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Allow disabling builtin rules (#20298)
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 5ae89054 by Sylvain Henry at 2025-09-24T17:07:00-04:00 Allow disabling builtin rules (#20298) Add a way to disable built-in rules programmatically and with a debug flag. I also took the opportunity to add a debug flag to disable bignum rules, which was only possible programmatically (e.g. in a plugin). - - - - - 135242ca by Rodrigo Mesquita at 2025-09-24T17:07:44-04:00 Don't use build CFLAGS and friends as target settings In the GHC in tree configure, `CFLAGS`, `CXXFLAGS`, and similar tool configuration flags apply to the BUILD phase of the compiler, i.e. to the tools run to compile GHC itself. Notably, they should /not/ be carried over to the Target settings, i.e. these flags should /not/ apply to the tool which GHC invokes at runtime. Fixes #25637 - - - - - 575cdf21 by Brandon Chinn at 2025-09-24T20:14:01-04:00 Fix tabs in string gaps (#26415) Tabs in string gaps were broken in bb030d0d because previously, string gaps were manually parsed, but now it's lexed by the usual Alex grammar and post-processed after successful lexing. It broke because of a discrepancy between GHC's lexer grammar and the Haskell Report. The Haskell Report includes tabs in whitechar: whitechar → newline | vertab | space | tab | uniWhite $whitechar used to include tabs until 18 years ago, when it was removed in order to exclude tabs from $white_no_nl in order to warn on tabs: 6e202120. In this MR, I'm adding \t back into $whitechar, and explicitly excluding \t from the $white_no_nl+ rule ignoring all whitespace in source code, which more accurately colocates the "ignore all whitespace except tabs, which is handled in the next line" logic. As a side effect of this MR, tabs are now allowed in pragmas; currently, a pragma written as {-# \t LANGUAGE ... #-} is interpreted as the tab character being the pragma name, and GHC warns "Unrecognized pragma". With this change, tabs are ignored as whitespace, which more closely matches the Report anyway. - - - - - 3348ba40 by Cheng Shao at 2025-09-24T20:14:02-04:00 wasm: remove the --no-turbo-fast-api-calls hack from dynamic linker shebang This patch removes the `--no-turbo-fast-api-calls` hack from the dyld script shebang; it was used to workaround v8 fast call coredumps in nodejs and no longer needed, and comes with a performance penalty, hence the removal. - - - - - 23 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Rules/Config.hs - compiler/GHC/Driver/Config/Core/Rules.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/Lexer/String.x - configure.ac - docs/users_guide/debugging.rst - m4/fp_setup_windows_toolchain.m4 - m4/ghc_toolchain.m4 - + testsuite/tests/codeGen/should_compile/T20298a.hs - + testsuite/tests/codeGen/should_compile/T20298a.stderr - + testsuite/tests/codeGen/should_compile/T20298b.hs - + testsuite/tests/codeGen/should_compile/T20298b.stderr - + testsuite/tests/codeGen/should_compile/T20298c.hs - + testsuite/tests/codeGen/should_compile/T20298c.stderr - testsuite/tests/codeGen/should_compile/all.T - + testsuite/tests/parser/should_run/T26415.hs - + testsuite/tests/parser/should_run/T26415.stdout - testsuite/tests/parser/should_run/all.T - utils/jsffi/dyld.mjs Changes: ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -2173,6 +2173,43 @@ builtinRules -- there is no benefit to inlining these yet, despite this, GHC produces -- unfoldings for this regardless since the floated list entries look small. + + +{- Note [Built-in bignum rules] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We have some built-in rules for operations on bignum types (Integer, Natural, +BigNat). These rules implement the same kind of constant folding as we have for +Int#/Word#/etc. primops. See builtinBignumRules. + +These rules are built-in because they can't be expressed as regular rules for +now. The reason is that due to the let-can-float invariant (see Note [Core +let-can-float invariant] in GHC.Core), GHC is too conservative with some bignum +operations and they don't match rules. For example: + + case integerAdd 1 x of r { _ -> integerAdd 1 r } + +doesn't constant-fold into `integerAdd 2 x` with a regular rule. That's because +GHC never floats in `integerAdd 1 x` to form `integerAdd 1 (integerAdd 1 x)` +because of the let-can-float invariant (it doesn't know if `integerAdd` +terminates). + +In the built-in rule for `integerAdd` we can access the unfolding of `r` and we +can perform the appropriate substitution. + +To support constant-folding, Bignum operations are not allowed to inline. As a +consequence, some codes that would benefit from inlining of bignum operations +don't. An idea to fix this was to only have built-in rules for BigNat# +operations and to allow Integer and Natural operations to inline. However these +operations are often too big to inline and we end up with broken +constant-folding and still no inlining. This issue is tracked in #20361 + +Bignum built-in rules can be disabled independently of other built-in rules by +passing the -dno-bignum-rules flag or programmatically with the `roBignumRules` field of +RuleOpts. + +-} + +-- | Built-in bignum rules (see Note [Built-in bignum rules]) builtinBignumRules :: [CoreRule] builtinBignumRules = [ -- conversions ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -65,6 +65,7 @@ import GHC.Core.Map.Expr ( eqCoreExpr ) import GHC.Core.Opt.Arity( etaExpandToJoinPointRule ) import GHC.Core.Make ( mkCoreLams ) import GHC.Core.Opt.OccurAnal( occurAnalyseExpr ) +import GHC.Core.Rules.Config (roBuiltinRules) import GHC.Tc.Utils.TcType ( tcSplitTyConApp_maybe ) import GHC.Builtin.Types ( anyTypeOfKind ) @@ -708,10 +709,8 @@ matchRule :: HasDebugCallStack matchRule opts rule_env _is_active fn args _rough_args (BuiltinRule { ru_try = match_fn }) --- Built-in rules can't be switched off, it seems - = case match_fn opts rule_env fn args of - Nothing -> Nothing - Just expr -> Just expr + | not (roBuiltinRules opts) = Nothing + | otherwise = match_fn opts rule_env fn args matchRule _ rule_env is_active _ args rough_args (Rule { ru_name = rule_name, ru_act = act, ru_rough = tpl_tops ===================================== compiler/GHC/Core/Rules/Config.hs ===================================== @@ -14,6 +14,10 @@ data RuleOpts = RuleOpts , roExcessRationalPrecision :: !Bool -- ^ Cut down precision of Rational values to that of Float/Double if disabled , roBignumRules :: !Bool - -- ^ Enable rules for bignums + -- ^ Enable built-in bignum rules (requires roBuiltinRules to be True too) + -- + -- See Note [Built-in bignum rules] in GHC.Core.Opt.ConstantFold + , roBuiltinRules :: !Bool + -- ^ Enable or disable all builtin rules (including bignum rules) } ===================================== compiler/GHC/Driver/Config/Core/Rules.hs ===================================== @@ -15,5 +15,6 @@ initRuleOpts dflags = RuleOpts { roPlatform = targetPlatform dflags , roNumConstantFolding = gopt Opt_NumConstantFolding dflags , roExcessRationalPrecision = gopt Opt_ExcessPrecision dflags - , roBignumRules = True + , roBignumRules = not (gopt Opt_NoBignumRules dflags) + , roBuiltinRules = not (gopt Opt_NoBuiltinRules dflags) } ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -592,6 +592,8 @@ data GeneralFlag | Opt_NoLlvmMangler -- hidden flag | Opt_FastLlvm -- hidden flag | Opt_NoTypeableBinds + | Opt_NoBuiltinRules + | Opt_NoBignumRules | Opt_DistinctConstructorTables | Opt_InfoTableMap @@ -973,6 +975,8 @@ codeGenFlags = EnumSet.fromList , Opt_ExposeAllUnfoldings , Opt_ExposeOverloadedUnfoldings , Opt_NoTypeableBinds + , Opt_NoBuiltinRules + , Opt_NoBignumRules , Opt_ObjectDeterminism , Opt_Haddock ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1660,6 +1660,10 @@ dynamic_flags_deps = [ (NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag , make_ord_flag defGhcFlag "dno-typeable-binds" (NoArg (setGeneralFlag Opt_NoTypeableBinds)) + , make_ord_flag defGhcFlag "dno-builtin-rules" + (NoArg (setGeneralFlag Opt_NoBuiltinRules)) + , make_ord_flag defGhcFlag "dno-bignum-rules" + (NoArg (setGeneralFlag Opt_NoBignumRules)) , make_ord_flag defGhcFlag "ddump-debug" (setDumpFlag Opt_D_dump_debug) , make_dep_flag defGhcFlag "ddump-json" ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -145,7 +145,7 @@ import GHC.Parser.String $unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex]. $nl = [\n\r\f] $space = [\ $unispace] -$whitechar = [$nl \v $space] +$whitechar = [$nl \t \v $space] $white_no_nl = $whitechar # \n -- TODO #8424 $tab = \t @@ -248,7 +248,7 @@ haskell :- -- Alex "Rules" -- everywhere: skip whitespace -$white_no_nl+ ; +($white_no_nl # \t)+ ; $tab { warnTab } -- Everywhere: deal with nested comments. We explicitly rule out ===================================== compiler/GHC/Parser/Lexer/String.x ===================================== @@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic) $unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex]. $nl = [\n\r\f] $space = [\ $unispace] -$whitechar = [$nl \v $space] +$whitechar = [$nl \t \v $space] $tab = \t $ascdigit = 0-9 ===================================== configure.ac ===================================== @@ -43,12 +43,6 @@ dnl interprets build/host/target and how this interacts with $CC tests test -n "$target_alias" && ac_tool_prefix=$target_alias- dnl ---------------------------------------------------------- -dnl ** Store USER specified environment variables to pass them on to -dnl ** ghc-toolchain (in m4/ghc-toolchain.m4) -USER_CFLAGS="$CFLAGS" -USER_LDFLAGS="$LDFLAGS" -USER_LIBS="$LIBS" -USER_CXXFLAGS="$CXXFLAGS" dnl The lower-level/not user-facing environment variables that may still be set dnl by developers such as in ghc-wasm-meta USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2" ===================================== docs/users_guide/debugging.rst ===================================== @@ -1225,6 +1225,18 @@ Other compiler will panic if you try to use Typeable instances of things that you built with this flag. +.. ghc-flag:: -dno-builtin-rules + :shortdesc: Disable all built-in rewrite rules + :type: dynamic + + This disables all the built-in rewrite rules. Mostly useful for debugging. + +.. ghc-flag:: -dno-bignum-rules + :shortdesc: Disable bignum built-in rewrite rules + :type: dynamic + + This disables bignum built-in rewrite rules. Mostly useful for debugging. + .. ghc-flag:: -dtag-inference-checks :shortdesc: Affirm tag inference results are correct at runtime. :type: dynamic ===================================== m4/fp_setup_windows_toolchain.m4 ===================================== @@ -146,11 +146,11 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[ dnl We override the USER_* flags here since the user delegated dnl configuration to the bundled windows toolchain, and these are the dnl options required by the bundled windows toolchain. - USER_CFLAGS="$CFLAGS" USER_CPP_ARGS="$CONF_CPP_OPTS_STAGE2" - USER_CXXFLAGS="$CXXFLAGS" USER_HS_CPP_ARGS="$HaskellCPPArgs" - USER_LDFLAGS="$CONF_GCC_LINKER_OPTS_STAGE2" + USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2" + USER_CONF_CXX_OPTS_STAGE2="$CONF_CXX_OPTS_STAGE2" + USER_CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2" USER_JS_CPP_ARGS="$JavaScriptCPPArgs" USER_CMM_CPP_ARGS="$CmmCPPArgs" ]) ===================================== m4/ghc_toolchain.m4 ===================================== @@ -8,18 +8,6 @@ AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG], done ]) -dnl $1 argument name -dnl $2 first variable to try -dnl $3 variable to add if the first variable is empty -AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG_CHOOSE], -[ - if test -z "$2"; then - ADD_GHC_TOOLCHAIN_ARG([$1],[$3]) - else - ADD_GHC_TOOLCHAIN_ARG([$1],[$2]) - fi -]) - AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG], [ if test "$2" = "YES"; then @@ -123,10 +111,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], ENABLE_GHC_TOOLCHAIN_ARG([dwarf-unwind], [$enable_dwarf_unwind]) dnl We store USER_* variants of all user-specified flags to pass them over to ghc-toolchain. - ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-opt], [$USER_CONF_CC_OPTS_STAGE2], [$USER_CFLAGS]) - ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-link-opt], [$USER_CONF_GCC_LINKER_OPTS_STAGE2], [$USER_LDFLAGS]) - ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_LIBS]) - ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cxx-opt], [$USER_CONF_CXX_OPTS_STAGE2], [$USER_CXXFLAGS]) + ADD_GHC_TOOLCHAIN_ARG([cc-opt], [$USER_CONF_CC_OPTS_STAGE2]) + ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_CONF_GCC_LINKER_OPTS_STAGE2]) + ADD_GHC_TOOLCHAIN_ARG([cxx-opt], [$USER_CONF_CXX_OPTS_STAGE2]) ADD_GHC_TOOLCHAIN_ARG([cpp-opt], [$USER_CPP_ARGS]) ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$USER_HS_CPP_ARGS]) ADD_GHC_TOOLCHAIN_ARG([js-cpp-opt], [$USER_JS_CPP_ARGS]) ===================================== testsuite/tests/codeGen/should_compile/T20298a.hs ===================================== @@ -0,0 +1,4 @@ +module T20298a where + +foo :: Integer +foo = 10 + 20 ===================================== testsuite/tests/codeGen/should_compile/T20298a.stderr ===================================== @@ -0,0 +1,9 @@ + +==================== Tidy Core ==================== +Result size of Tidy Core + = {terms: 3, types: 1, coercions: 0, joins: 0/0} + +foo = IS 30# + + + ===================================== testsuite/tests/codeGen/should_compile/T20298b.hs ===================================== @@ -0,0 +1,4 @@ +module T20298b where + +foo :: Integer +foo = 10 + 20 ===================================== testsuite/tests/codeGen/should_compile/T20298b.stderr ===================================== @@ -0,0 +1,13 @@ + +==================== Tidy Core ==================== +Result size of Tidy Core + = {terms: 10, types: 3, coercions: 0, joins: 0/0} + +foo2 = IS 10# + +foo1 = IS 20# + +foo = integerAdd foo2 foo1 + + + ===================================== testsuite/tests/codeGen/should_compile/T20298c.hs ===================================== @@ -0,0 +1,4 @@ +module T20298c where + +foo :: Integer +foo = 10 + 20 ===================================== testsuite/tests/codeGen/should_compile/T20298c.stderr ===================================== @@ -0,0 +1,13 @@ + +==================== Tidy Core ==================== +Result size of Tidy Core + = {terms: 11, types: 4, coercions: 0, joins: 0/0} + +foo2 = IS 10# + +foo1 = IS 20# + +foo = + $fNumInteger foo2 foo1 + + + ===================================== testsuite/tests/codeGen/should_compile/all.T ===================================== @@ -145,3 +145,7 @@ test('T25166', [req_cmm], makefile_test, []) test('T25177', normal, compile, ['-O2 -dno-typeable-binds -ddump-simpl -dsuppress-all -dsuppress-uniques -v0']) test('T16351', normal, compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques']) + +test('T20298a', normal, compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques']) +test('T20298b', normal, compile, ['-O2 -dno-bignum-rules -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques']) +test('T20298c', normal, compile, ['-O2 -dno-builtin-rules -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques']) ===================================== testsuite/tests/parser/should_run/T26415.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE MultilineStrings #-} + +main :: IO () +main = do + -- The below strings contain the characters ['\\', '\t', '\\'] + print "\ \" + print """\ \""" ===================================== testsuite/tests/parser/should_run/T26415.stdout ===================================== @@ -0,0 +1,2 @@ +"" +"" ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil test('RecordDotSyntax5', normal, compile_and_run, ['']) test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script']) test('T25937', normal, compile_and_run, ['']) +test('T26415', normal, compile_and_run, ['']) # Multiline strings test('MultilineStrings', normal, compile_and_run, ['']) ===================================== utils/jsffi/dyld.mjs ===================================== @@ -1,4 +1,4 @@ -#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation +#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --wasm-lazy-validation // Note [The Wasm Dynamic Linker] // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/807f5c863ecdcafa4335523cf3600a9... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/807f5c863ecdcafa4335523cf3600a9... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)