Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC

Commits:

23 changed files:

Changes:

  • compiler/GHC/Core/Opt/ConstantFold.hs
    ... ... @@ -2173,6 +2173,43 @@ builtinRules
    2173 2173
     -- there is no benefit to inlining these yet, despite this, GHC produces
    
    2174 2174
     -- unfoldings for this regardless since the floated list entries look small.
    
    2175 2175
     
    
    2176
    +
    
    2177
    +
    
    2178
    +{- Note [Built-in bignum rules]
    
    2179
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    2180
    +We have some built-in rules for operations on bignum types (Integer, Natural,
    
    2181
    +BigNat). These rules implement the same kind of constant folding as we have for
    
    2182
    +Int#/Word#/etc. primops. See builtinBignumRules.
    
    2183
    +
    
    2184
    +These rules are built-in because they can't be expressed as regular rules for
    
    2185
    +now. The reason is that due to the let-can-float invariant (see Note [Core
    
    2186
    +let-can-float invariant] in GHC.Core), GHC is too conservative with some bignum
    
    2187
    +operations and they don't match rules. For example:
    
    2188
    +
    
    2189
    +  case integerAdd 1 x of r { _ -> integerAdd 1 r }
    
    2190
    +
    
    2191
    +doesn't constant-fold into `integerAdd 2 x` with a regular rule. That's because
    
    2192
    +GHC never floats in `integerAdd 1 x` to form `integerAdd 1 (integerAdd 1 x)`
    
    2193
    +because of the let-can-float invariant (it doesn't know if `integerAdd`
    
    2194
    +terminates).
    
    2195
    +
    
    2196
    +In the built-in rule for `integerAdd` we can access the unfolding of `r` and we
    
    2197
    +can perform the appropriate substitution.
    
    2198
    +
    
    2199
    +To support constant-folding, Bignum operations are not allowed to inline. As a
    
    2200
    +consequence, some codes that would benefit from inlining of bignum operations
    
    2201
    +don't. An idea to fix this was to only have built-in rules for BigNat#
    
    2202
    +operations and to allow Integer and Natural operations to inline. However these
    
    2203
    +operations are often too big to inline and we end up with broken
    
    2204
    +constant-folding and still no inlining. This issue is tracked in #20361
    
    2205
    +
    
    2206
    +Bignum built-in rules can be disabled independently of other built-in rules by
    
    2207
    +passing the -dno-bignum-rules flag or programmatically with the `roBignumRules` field of
    
    2208
    +RuleOpts.
    
    2209
    +
    
    2210
    +-}
    
    2211
    +
    
    2212
    +-- | Built-in bignum rules (see Note [Built-in bignum rules])
    
    2176 2213
     builtinBignumRules :: [CoreRule]
    
    2177 2214
     builtinBignumRules =
    
    2178 2215
       [ -- conversions
    

  • compiler/GHC/Core/Rules.hs
    ... ... @@ -65,6 +65,7 @@ import GHC.Core.Map.Expr ( eqCoreExpr )
    65 65
     import GHC.Core.Opt.Arity( etaExpandToJoinPointRule )
    
    66 66
     import GHC.Core.Make     ( mkCoreLams )
    
    67 67
     import GHC.Core.Opt.OccurAnal( occurAnalyseExpr )
    
    68
    +import GHC.Core.Rules.Config (roBuiltinRules)
    
    68 69
     
    
    69 70
     import GHC.Tc.Utils.TcType  ( tcSplitTyConApp_maybe )
    
    70 71
     import GHC.Builtin.Types    ( anyTypeOfKind )
    
    ... ... @@ -708,10 +709,8 @@ matchRule :: HasDebugCallStack
    708 709
     
    
    709 710
     matchRule opts rule_env _is_active fn args _rough_args
    
    710 711
               (BuiltinRule { ru_try = match_fn })
    
    711
    --- Built-in rules can't be switched off, it seems
    
    712
    -  = case match_fn opts rule_env fn args of
    
    713
    -        Nothing   -> Nothing
    
    714
    -        Just expr -> Just expr
    
    712
    +  | not (roBuiltinRules opts) = Nothing
    
    713
    +  | otherwise                 = match_fn opts rule_env fn args
    
    715 714
     
    
    716 715
     matchRule _ rule_env is_active _ args rough_args
    
    717 716
               (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
    14 14
        , roExcessRationalPrecision :: !Bool
    
    15 15
          -- ^ Cut down precision of Rational values to that of Float/Double if disabled
    
    16 16
        , roBignumRules             :: !Bool
    
    17
    -     -- ^ Enable rules for bignums
    
    17
    +     -- ^ Enable built-in bignum rules (requires roBuiltinRules to be True too)
    
    18
    +     --
    
    19
    +     -- See Note [Built-in bignum rules] in GHC.Core.Opt.ConstantFold
    
    20
    +   , roBuiltinRules            :: !Bool
    
    21
    +     -- ^ Enable or disable all builtin rules (including bignum rules)
    
    18 22
        }
    
    19 23
     

  • compiler/GHC/Driver/Config/Core/Rules.hs
    ... ... @@ -15,5 +15,6 @@ initRuleOpts dflags = RuleOpts
    15 15
       { roPlatform                = targetPlatform dflags
    
    16 16
       , roNumConstantFolding      = gopt Opt_NumConstantFolding dflags
    
    17 17
       , roExcessRationalPrecision = gopt Opt_ExcessPrecision dflags
    
    18
    -  , roBignumRules             = True
    
    18
    +  , roBignumRules             = not (gopt Opt_NoBignumRules dflags)
    
    19
    +  , roBuiltinRules            = not (gopt Opt_NoBuiltinRules dflags)
    
    19 20
       }

  • compiler/GHC/Driver/Flags.hs
    ... ... @@ -592,6 +592,8 @@ data GeneralFlag
    592 592
        | Opt_NoLlvmMangler                  -- hidden flag
    
    593 593
        | Opt_FastLlvm                       -- hidden flag
    
    594 594
        | Opt_NoTypeableBinds
    
    595
    +   | Opt_NoBuiltinRules
    
    596
    +   | Opt_NoBignumRules
    
    595 597
     
    
    596 598
        | Opt_DistinctConstructorTables
    
    597 599
        | Opt_InfoTableMap
    
    ... ... @@ -973,6 +975,8 @@ codeGenFlags = EnumSet.fromList
    973 975
        , Opt_ExposeAllUnfoldings
    
    974 976
        , Opt_ExposeOverloadedUnfoldings
    
    975 977
        , Opt_NoTypeableBinds
    
    978
    +   , Opt_NoBuiltinRules
    
    979
    +   , Opt_NoBignumRules
    
    976 980
        , Opt_ObjectDeterminism
    
    977 981
        , Opt_Haddock
    
    978 982
     
    

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -1660,6 +1660,10 @@ dynamic_flags_deps = [
    1660 1660
             (NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag
    
    1661 1661
       , make_ord_flag defGhcFlag "dno-typeable-binds"
    
    1662 1662
             (NoArg (setGeneralFlag Opt_NoTypeableBinds))
    
    1663
    +  , make_ord_flag defGhcFlag "dno-builtin-rules"
    
    1664
    +        (NoArg (setGeneralFlag Opt_NoBuiltinRules))
    
    1665
    +  , make_ord_flag defGhcFlag "dno-bignum-rules"
    
    1666
    +        (NoArg (setGeneralFlag Opt_NoBignumRules))
    
    1663 1667
       , make_ord_flag defGhcFlag "ddump-debug"
    
    1664 1668
             (setDumpFlag Opt_D_dump_debug)
    
    1665 1669
       , make_dep_flag defGhcFlag "ddump-json"
    

  • compiler/GHC/Parser/Lexer.x
    ... ... @@ -145,7 +145,7 @@ import GHC.Parser.String
    145 145
     $unispace    = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
    
    146 146
     $nl          = [\n\r\f]
    
    147 147
     $space       = [\ $unispace]
    
    148
    -$whitechar   = [$nl \v $space]
    
    148
    +$whitechar   = [$nl \t \v $space]
    
    149 149
     $white_no_nl = $whitechar # \n -- TODO #8424
    
    150 150
     $tab         = \t
    
    151 151
     
    
    ... ... @@ -248,7 +248,7 @@ haskell :-
    248 248
     -- Alex "Rules"
    
    249 249
     
    
    250 250
     -- everywhere: skip whitespace
    
    251
    -$white_no_nl+ ;
    
    251
    +($white_no_nl # \t)+ ;
    
    252 252
     $tab          { warnTab }
    
    253 253
     
    
    254 254
     -- Everywhere: deal with nested comments.  We explicitly rule out
    

  • compiler/GHC/Parser/Lexer/String.x
    ... ... @@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
    25 25
     $unispace    = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
    
    26 26
     $nl          = [\n\r\f]
    
    27 27
     $space       = [\ $unispace]
    
    28
    -$whitechar   = [$nl \v $space]
    
    28
    +$whitechar   = [$nl \t \v $space]
    
    29 29
     $tab         = \t
    
    30 30
     
    
    31 31
     $ascdigit  = 0-9
    

  • configure.ac
    ... ... @@ -43,12 +43,6 @@ dnl interprets build/host/target and how this interacts with $CC tests
    43 43
     test -n "$target_alias" && ac_tool_prefix=$target_alias-
    
    44 44
     
    
    45 45
     dnl ----------------------------------------------------------
    
    46
    -dnl ** Store USER specified environment variables to pass them on to
    
    47
    -dnl ** ghc-toolchain (in m4/ghc-toolchain.m4)
    
    48
    -USER_CFLAGS="$CFLAGS"
    
    49
    -USER_LDFLAGS="$LDFLAGS"
    
    50
    -USER_LIBS="$LIBS"
    
    51
    -USER_CXXFLAGS="$CXXFLAGS"
    
    52 46
     dnl The lower-level/not user-facing environment variables that may still be set
    
    53 47
     dnl by developers such as in ghc-wasm-meta
    
    54 48
     USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2"
    

  • docs/users_guide/debugging.rst
    ... ... @@ -1225,6 +1225,18 @@ Other
    1225 1225
         compiler will panic if you try to use Typeable instances of things that you
    
    1226 1226
         built with this flag.
    
    1227 1227
     
    
    1228
    +.. ghc-flag:: -dno-builtin-rules
    
    1229
    +    :shortdesc: Disable all built-in rewrite rules
    
    1230
    +    :type: dynamic
    
    1231
    +
    
    1232
    +    This disables all the built-in rewrite rules. Mostly useful for debugging.
    
    1233
    +
    
    1234
    +.. ghc-flag:: -dno-bignum-rules
    
    1235
    +    :shortdesc: Disable bignum built-in rewrite rules
    
    1236
    +    :type: dynamic
    
    1237
    +
    
    1238
    +    This disables bignum built-in rewrite rules. Mostly useful for debugging.
    
    1239
    +
    
    1228 1240
     .. ghc-flag:: -dtag-inference-checks
    
    1229 1241
         :shortdesc: Affirm tag inference results are correct at runtime.
    
    1230 1242
         :type: dynamic
    

  • m4/fp_setup_windows_toolchain.m4
    ... ... @@ -146,11 +146,11 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
    146 146
         dnl We override the USER_* flags here since the user delegated
    
    147 147
         dnl configuration to the bundled windows toolchain, and these are the
    
    148 148
         dnl options required by the bundled windows toolchain.
    
    149
    -    USER_CFLAGS="$CFLAGS"
    
    150 149
         USER_CPP_ARGS="$CONF_CPP_OPTS_STAGE2"
    
    151
    -    USER_CXXFLAGS="$CXXFLAGS"
    
    152 150
         USER_HS_CPP_ARGS="$HaskellCPPArgs"
    
    153
    -    USER_LDFLAGS="$CONF_GCC_LINKER_OPTS_STAGE2"
    
    151
    +    USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2"
    
    152
    +    USER_CONF_CXX_OPTS_STAGE2="$CONF_CXX_OPTS_STAGE2"
    
    153
    +    USER_CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2"
    
    154 154
         USER_JS_CPP_ARGS="$JavaScriptCPPArgs"
    
    155 155
         USER_CMM_CPP_ARGS="$CmmCPPArgs"
    
    156 156
     ])

  • m4/ghc_toolchain.m4
    ... ... @@ -8,18 +8,6 @@ AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG],
    8 8
         done
    
    9 9
     ])
    
    10 10
     
    
    11
    -dnl $1 argument name
    
    12
    -dnl $2 first variable to try
    
    13
    -dnl $3 variable to add if the first variable is empty
    
    14
    -AC_DEFUN([ADD_GHC_TOOLCHAIN_ARG_CHOOSE],
    
    15
    -[
    
    16
    -    if test -z "$2"; then
    
    17
    -        ADD_GHC_TOOLCHAIN_ARG([$1],[$3])
    
    18
    -    else
    
    19
    -        ADD_GHC_TOOLCHAIN_ARG([$1],[$2])
    
    20
    -    fi
    
    21
    -])
    
    22
    -
    
    23 11
     AC_DEFUN([ENABLE_GHC_TOOLCHAIN_ARG],
    
    24 12
     [
    
    25 13
         if test "$2" = "YES"; then
    
    ... ... @@ -123,10 +111,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
    123 111
         ENABLE_GHC_TOOLCHAIN_ARG([dwarf-unwind], [$enable_dwarf_unwind])
    
    124 112
     
    
    125 113
         dnl We store USER_* variants of all user-specified flags to pass them over to ghc-toolchain.
    
    126
    -    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-opt], [$USER_CONF_CC_OPTS_STAGE2], [$USER_CFLAGS])
    
    127
    -    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-link-opt], [$USER_CONF_GCC_LINKER_OPTS_STAGE2], [$USER_LDFLAGS])
    
    128
    -    ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_LIBS])
    
    129
    -    ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cxx-opt], [$USER_CONF_CXX_OPTS_STAGE2], [$USER_CXXFLAGS])
    
    114
    +    ADD_GHC_TOOLCHAIN_ARG([cc-opt], [$USER_CONF_CC_OPTS_STAGE2])
    
    115
    +    ADD_GHC_TOOLCHAIN_ARG([cc-link-opt], [$USER_CONF_GCC_LINKER_OPTS_STAGE2])
    
    116
    +    ADD_GHC_TOOLCHAIN_ARG([cxx-opt], [$USER_CONF_CXX_OPTS_STAGE2])
    
    130 117
         ADD_GHC_TOOLCHAIN_ARG([cpp-opt], [$USER_CPP_ARGS])
    
    131 118
         ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$USER_HS_CPP_ARGS])
    
    132 119
         ADD_GHC_TOOLCHAIN_ARG([js-cpp-opt], [$USER_JS_CPP_ARGS])
    

  • testsuite/tests/codeGen/should_compile/T20298a.hs
    1
    +module T20298a where
    
    2
    +
    
    3
    +foo :: Integer
    
    4
    +foo = 10 + 20

  • testsuite/tests/codeGen/should_compile/T20298a.stderr
    1
    +
    
    2
    +==================== Tidy Core ====================
    
    3
    +Result size of Tidy Core
    
    4
    +  = {terms: 3, types: 1, coercions: 0, joins: 0/0}
    
    5
    +
    
    6
    +foo = IS 30#
    
    7
    +
    
    8
    +
    
    9
    +

  • testsuite/tests/codeGen/should_compile/T20298b.hs
    1
    +module T20298b where
    
    2
    +
    
    3
    +foo :: Integer
    
    4
    +foo = 10 + 20

  • testsuite/tests/codeGen/should_compile/T20298b.stderr
    1
    +
    
    2
    +==================== Tidy Core ====================
    
    3
    +Result size of Tidy Core
    
    4
    +  = {terms: 10, types: 3, coercions: 0, joins: 0/0}
    
    5
    +
    
    6
    +foo2 = IS 10#
    
    7
    +
    
    8
    +foo1 = IS 20#
    
    9
    +
    
    10
    +foo = integerAdd foo2 foo1
    
    11
    +
    
    12
    +
    
    13
    +

  • testsuite/tests/codeGen/should_compile/T20298c.hs
    1
    +module T20298c where
    
    2
    +
    
    3
    +foo :: Integer
    
    4
    +foo = 10 + 20

  • testsuite/tests/codeGen/should_compile/T20298c.stderr
    1
    +
    
    2
    +==================== Tidy Core ====================
    
    3
    +Result size of Tidy Core
    
    4
    +  = {terms: 11, types: 4, coercions: 0, joins: 0/0}
    
    5
    +
    
    6
    +foo2 = IS 10#
    
    7
    +
    
    8
    +foo1 = IS 20#
    
    9
    +
    
    10
    +foo = + $fNumInteger foo2 foo1
    
    11
    +
    
    12
    +
    
    13
    +

  • testsuite/tests/codeGen/should_compile/all.T
    ... ... @@ -145,3 +145,7 @@ test('T25166', [req_cmm], makefile_test, [])
    145 145
     test('T25177', normal, compile, ['-O2 -dno-typeable-binds -ddump-simpl -dsuppress-all -dsuppress-uniques -v0'])
    
    146 146
     
    
    147 147
     test('T16351', normal, compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques'])
    
    148
    +
    
    149
    +test('T20298a', normal, compile, ['-O2 -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques'])
    
    150
    +test('T20298b', normal, compile, ['-O2 -dno-bignum-rules -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques'])
    
    151
    +test('T20298c', normal, compile, ['-O2 -dno-builtin-rules -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques'])

  • testsuite/tests/parser/should_run/T26415.hs
    1
    +{-# LANGUAGE MultilineStrings #-}
    
    2
    +
    
    3
    +main :: IO ()
    
    4
    +main = do
    
    5
    +  -- The below strings contain the characters ['\\', '\t', '\\']
    
    6
    +  print "\	\"
    
    7
    +  print """\	\"""

  • testsuite/tests/parser/should_run/T26415.stdout
    1
    +""
    
    2
    +""

  • testsuite/tests/parser/should_run/all.T
    ... ... @@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
    27 27
     test('RecordDotSyntax5', normal, compile_and_run, [''])
    
    28 28
     test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
    
    29 29
     test('T25937', normal, compile_and_run, [''])
    
    30
    +test('T26415', normal, compile_and_run, [''])
    
    30 31
     
    
    31 32
     # Multiline strings
    
    32 33
     test('MultilineStrings', normal, compile_and_run, [''])
    

  • utils/jsffi/dyld.mjs
    1
    -#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --no-turbo-fast-api-calls --wasm-lazy-validation
    
    1
    +#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --max-old-space-size=65536 --wasm-lazy-validation
    
    2 2
     
    
    3 3
     // Note [The Wasm Dynamic Linker]
    
    4 4
     // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~