Andreas Klebinger pushed to branch wip/andreask/occ_anal_tuning at Glasgow Haskell Compiler / GHC Commits: 1275d360 by Matthew Pickering at 2025-10-03T06:05:56-04:00 testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests These tests reimplemented the logic from `valid_way` in order to determine what ways to run. It's easier to use this combination of `only_ways` and `extra_ways` to only run in GHCi ways and always run in GHCi ways. - - - - - c06b534b by Matthew Pickering at 2025-10-03T06:06:40-04:00 Rename interpreterBackend to bytecodeBackend This is preparation for creating bytecode files. The "interpreter" is one way in which we can run bytecode objects. It is more accurate to describe that the backend produces bytecode, rather than the means by which the code will eventually run. The "interpreterBackend" binding is left as a deprecated alias. - - - - - 41bdb16f by Andreas Klebinger at 2025-10-06T18:04:34-04:00 Add a perf test for #26425 - - - - - 1da0c700 by Andreas Klebinger at 2025-10-06T18:05:14-04:00 Testsuite: Silence warnings about Wx-partial in concprog001 - - - - - ec22d744 by Andreas Klebinger at 2025-10-07T08:03:44+00:00 Try using a strict env for OccAnal - - - - - 26 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Data/Word64Map/Internal.hs - compiler/GHC/Driver/Backend.hs - compiler/GHC/Driver/Backend/Internal.hs - compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Var/Env.hs - docs/users_guide/extending_ghc.rst - ghc/Main.hs - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/concurrent/prog001/all.T - testsuite/tests/driver/T5313.hs - testsuite/tests/ghc-api/T10052/T10052.hs - testsuite/tests/ghc-api/T8639_api.hs - testsuite/tests/ghc-api/apirecomp001/myghc.hs - testsuite/tests/ghci-wasm/T26431.hs - testsuite/tests/ghci/linking/dyn/T3372.hs - testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T - testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T - testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T - + testsuite/tests/perf/compiler/T26425.hs - testsuite/tests/perf/compiler/all.T Changes: ===================================== compiler/GHC.hs ===================================== @@ -30,7 +30,7 @@ module GHC ( -- * Flags and settings DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt, - ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend, + ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, noBackend, GhcMode(..), GhcLink(..), parseDynamicFlags, parseTargetFiles, getSessionDynFlags, ===================================== compiler/GHC/Core/Opt/OccurAnal.hs ===================================== @@ -10,6 +10,10 @@ -- bad for performance, so I increased the limit to allow it to unbox -- consistently. +-- {-# OPTIONS_GHC -ddump-simpl -ddump-stg -dumpdir dumps -ddump-to-file #-} +-- {-# OPTIONS_GHC -fdistinct-constructor-tables -finfo-table-map #-} +-- {-# OPTIONS_GHC -ticky -ticky-allocd -ticky-LNE #-} + {- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 @@ -984,7 +988,7 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine = -- Analyse the RHS and /then/ the body let -- Analyse the rhs first, generating rhs_uds !(rhs_uds_s, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs - rhs_uds = foldr1 orUDs rhs_uds_s -- NB: orUDs. See (W4) of + rhs_uds = foldl1' orUDs rhs_uds_s -- NB: orUDs. See (W4) of -- Note [Occurrence analysis for join points] -- Now analyse the body, adding the join point @@ -3650,8 +3654,10 @@ data WithTailUsageDetails a = WTUD !TailUsageDetails !a ------------------- -- UsageDetails API -andUDs, orUDs - :: UsageDetails -> UsageDetails -> UsageDetails +-- {-# NOINLINE andUDs #-} +-- {-# NOINLINE orUDs #-} +andUDs:: UsageDetails -> UsageDetails -> UsageDetails +orUDs :: UsageDetails -> UsageDetails -> UsageDetails andUDs = combineUsageDetailsWith andLocalOcc orUDs = combineUsageDetailsWith orLocalOcc @@ -3760,16 +3766,17 @@ restrictFreeVars bndrs fvs = restrictUniqSetToUFM bndrs fvs combineUsageDetailsWith :: (LocalOcc -> LocalOcc -> LocalOcc) -> UsageDetails -> UsageDetails -> UsageDetails {-# INLINE combineUsageDetailsWith #-} +{-# SCC combineUsageDetailsWith #-} combineUsageDetailsWith plus_occ_info uds1@(UD { ud_env = env1, ud_z_many = z_many1, ud_z_in_lam = z_in_lam1, ud_z_tail = z_tail1 }) uds2@(UD { ud_env = env2, ud_z_many = z_many2, ud_z_in_lam = z_in_lam2, ud_z_tail = z_tail2 }) | isEmptyVarEnv env1 = uds2 | isEmptyVarEnv env2 = uds1 | otherwise - = UD { ud_env = plusVarEnv_C plus_occ_info env1 env2 - , ud_z_many = plusVarEnv z_many1 z_many2 - , ud_z_in_lam = plusVarEnv z_in_lam1 z_in_lam2 - , ud_z_tail = plusVarEnv z_tail1 z_tail2 } + = UD { ud_env = {-# SCC ud_env #-} strictPlusVarEnv_C plus_occ_info env1 env2 + , ud_z_many = {-# SCC ud_z_many #-} strictPlusVarEnv z_many1 z_many2 + , ud_z_in_lam = {-# SCC ud_z_in_lam #-} strictPlusVarEnv z_in_lam1 z_in_lam2 + , ud_z_tail = {-# SCC ud_z_tail #-} strictPlusVarEnv z_tail1 z_tail2 } lookupLetOccInfo :: UsageDetails -> Id -> OccInfo -- Don't use locally-generated occ_info for exported (visible-elsewhere) ===================================== compiler/GHC/Data/Word64Map/Internal.hs ===================================== @@ -3,6 +3,7 @@ {-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_GHC -fno-warn-incomplete-uni-patterns #-} +{-# OPTIONS_GHC -ddump-simpl -ddump-stg-final -ddump-to-file -dumpdir dumps #-} ----------------------------------------------------------------------------- ===================================== compiler/GHC/Driver/Backend.hs ===================================== @@ -47,6 +47,7 @@ module GHC.Driver.Backend , llvmBackend , jsBackend , viaCBackend + , bytecodeBackend , interpreterBackend , noBackend , allBackends @@ -252,7 +253,7 @@ instance Show Backend where show = backendDescription -ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend +ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, jsBackend, noBackend :: Backend -- | The native code generator. @@ -310,7 +311,11 @@ viaCBackend = Named ViaC -- (foreign primops). -- -- See "GHC.StgToByteCode" -interpreterBackend = Named Interpreter +bytecodeBackend = Named Bytecode + +{-# DEPRECATED interpreterBackend "Renamed to bytecodeBackend" #-} +interpreterBackend = bytecodeBackend + -- | A dummy back end that generates no code. -- @@ -419,7 +424,7 @@ backendDescription (Named NCG) = "native code generator" backendDescription (Named LLVM) = "LLVM" backendDescription (Named ViaC) = "compiling via C" backendDescription (Named JavaScript) = "compiling to JavaScript" -backendDescription (Named Interpreter) = "byte-code interpreter" +backendDescription (Named Bytecode) = "byte-code interpreter" backendDescription (Named NoBackend) = "no code generated" -- | This flag tells the compiler driver whether the back @@ -431,7 +436,7 @@ backendWritesFiles (Named NCG) = True backendWritesFiles (Named LLVM) = True backendWritesFiles (Named ViaC) = True backendWritesFiles (Named JavaScript) = True -backendWritesFiles (Named Interpreter) = False +backendWritesFiles (Named Bytecode) = False backendWritesFiles (Named NoBackend) = False -- | When the back end does write files, this value tells @@ -442,7 +447,7 @@ backendPipelineOutput (Named NCG) = Persistent backendPipelineOutput (Named LLVM) = Persistent backendPipelineOutput (Named ViaC) = Persistent backendPipelineOutput (Named JavaScript) = Persistent -backendPipelineOutput (Named Interpreter) = NoOutputFile +backendPipelineOutput (Named Bytecode) = NoOutputFile backendPipelineOutput (Named NoBackend) = NoOutputFile -- | This flag tells the driver whether the back end can @@ -453,7 +458,7 @@ backendCanReuseLoadedCode (Named NCG) = False backendCanReuseLoadedCode (Named LLVM) = False backendCanReuseLoadedCode (Named ViaC) = False backendCanReuseLoadedCode (Named JavaScript) = False -backendCanReuseLoadedCode (Named Interpreter) = True +backendCanReuseLoadedCode (Named Bytecode) = True backendCanReuseLoadedCode (Named NoBackend) = False -- | It is is true of every back end except @-fno-code@ @@ -478,7 +483,7 @@ backendGeneratesCode (Named NCG) = True backendGeneratesCode (Named LLVM) = True backendGeneratesCode (Named ViaC) = True backendGeneratesCode (Named JavaScript) = True -backendGeneratesCode (Named Interpreter) = True +backendGeneratesCode (Named Bytecode) = True backendGeneratesCode (Named NoBackend) = False backendGeneratesCodeForHsBoot :: Backend -> Bool @@ -486,7 +491,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True backendGeneratesCodeForHsBoot (Named LLVM) = True backendGeneratesCodeForHsBoot (Named ViaC) = True backendGeneratesCodeForHsBoot (Named JavaScript) = True -backendGeneratesCodeForHsBoot (Named Interpreter) = False +backendGeneratesCodeForHsBoot (Named Bytecode) = False backendGeneratesCodeForHsBoot (Named NoBackend) = False -- | When set, this flag turns on interface writing for @@ -498,7 +503,7 @@ backendSupportsInterfaceWriting (Named NCG) = True backendSupportsInterfaceWriting (Named LLVM) = True backendSupportsInterfaceWriting (Named ViaC) = True backendSupportsInterfaceWriting (Named JavaScript) = True -backendSupportsInterfaceWriting (Named Interpreter) = True +backendSupportsInterfaceWriting (Named Bytecode) = True backendSupportsInterfaceWriting (Named NoBackend) = False -- | When preparing code for this back end, the type @@ -510,7 +515,7 @@ backendRespectsSpecialise (Named NCG) = True backendRespectsSpecialise (Named LLVM) = True backendRespectsSpecialise (Named ViaC) = True backendRespectsSpecialise (Named JavaScript) = True -backendRespectsSpecialise (Named Interpreter) = False +backendRespectsSpecialise (Named Bytecode) = False backendRespectsSpecialise (Named NoBackend) = False -- | This back end wants the `mi_top_env` field of a @@ -522,7 +527,7 @@ backendWantsGlobalBindings (Named LLVM) = False backendWantsGlobalBindings (Named ViaC) = False backendWantsGlobalBindings (Named JavaScript) = False backendWantsGlobalBindings (Named NoBackend) = False -backendWantsGlobalBindings (Named Interpreter) = True +backendWantsGlobalBindings (Named Bytecode) = True -- | The back end targets a technology that implements -- `switch` natively. (For example, LLVM or C.) Therefore @@ -534,7 +539,7 @@ backendHasNativeSwitch (Named NCG) = False backendHasNativeSwitch (Named LLVM) = True backendHasNativeSwitch (Named ViaC) = True backendHasNativeSwitch (Named JavaScript) = True -backendHasNativeSwitch (Named Interpreter) = False +backendHasNativeSwitch (Named Bytecode) = False backendHasNativeSwitch (Named NoBackend) = False -- | As noted in the documentation for @@ -548,7 +553,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives backendPrimitiveImplementation (Named JavaScript) = JSPrimitives backendPrimitiveImplementation (Named ViaC) = GenericPrimitives -backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives +backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives -- | When this value is `IsValid`, the back end is @@ -560,7 +565,7 @@ backendSimdValidity (Named NCG) = IsValid backendSimdValidity (Named LLVM) = IsValid backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] -backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] +backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."] -- | This flag says whether the back end supports large @@ -571,7 +576,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True backendSupportsEmbeddedBlobs (Named LLVM) = False backendSupportsEmbeddedBlobs (Named ViaC) = False backendSupportsEmbeddedBlobs (Named JavaScript) = False -backendSupportsEmbeddedBlobs (Named Interpreter) = False +backendSupportsEmbeddedBlobs (Named Bytecode) = False backendSupportsEmbeddedBlobs (Named NoBackend) = False -- | This flag tells the compiler driver that the back end @@ -586,7 +591,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True backendNeedsPlatformNcgSupport (Named LLVM) = False backendNeedsPlatformNcgSupport (Named ViaC) = False backendNeedsPlatformNcgSupport (Named JavaScript) = False -backendNeedsPlatformNcgSupport (Named Interpreter) = False +backendNeedsPlatformNcgSupport (Named Bytecode) = False backendNeedsPlatformNcgSupport (Named NoBackend) = False -- | This flag is set if the back end can generate code @@ -598,7 +603,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True backendSupportsUnsplitProcPoints (Named LLVM) = False backendSupportsUnsplitProcPoints (Named ViaC) = False backendSupportsUnsplitProcPoints (Named JavaScript) = False -backendSupportsUnsplitProcPoints (Named Interpreter) = False +backendSupportsUnsplitProcPoints (Named Bytecode) = False backendSupportsUnsplitProcPoints (Named NoBackend) = False -- | This flag guides the driver in resolving issues about @@ -616,7 +621,7 @@ backendSwappableWithViaC (Named NCG) = True backendSwappableWithViaC (Named LLVM) = True backendSwappableWithViaC (Named ViaC) = False backendSwappableWithViaC (Named JavaScript) = False -backendSwappableWithViaC (Named Interpreter) = False +backendSwappableWithViaC (Named Bytecode) = False backendSwappableWithViaC (Named NoBackend) = False -- | This flag is true if the back end works *only* with @@ -626,7 +631,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False backendUnregisterisedAbiOnly (Named LLVM) = False backendUnregisterisedAbiOnly (Named ViaC) = True backendUnregisterisedAbiOnly (Named JavaScript) = False -backendUnregisterisedAbiOnly (Named Interpreter) = False +backendUnregisterisedAbiOnly (Named Bytecode) = False backendUnregisterisedAbiOnly (Named NoBackend) = False -- | This flag is set if the back end generates C code in @@ -637,7 +642,7 @@ backendGeneratesHc (Named NCG) = False backendGeneratesHc (Named LLVM) = False backendGeneratesHc (Named ViaC) = True backendGeneratesHc (Named JavaScript) = False -backendGeneratesHc (Named Interpreter) = False +backendGeneratesHc (Named Bytecode) = False backendGeneratesHc (Named NoBackend) = False -- | This flag says whether SPT (static pointer table) @@ -649,7 +654,7 @@ backendSptIsDynamic (Named NCG) = False backendSptIsDynamic (Named LLVM) = False backendSptIsDynamic (Named ViaC) = False backendSptIsDynamic (Named JavaScript) = False -backendSptIsDynamic (Named Interpreter) = True +backendSptIsDynamic (Named Bytecode) = True backendSptIsDynamic (Named NoBackend) = False -- | If this flag is unset, then the driver ignores the flag @-fbreak-points@, @@ -660,7 +665,7 @@ backendSupportsBreakpoints = \case Named LLVM -> False Named ViaC -> False Named JavaScript -> False - Named Interpreter -> True + Named Bytecode -> True Named NoBackend -> False -- | If this flag is set, then the driver forces the @@ -671,7 +676,7 @@ backendForcesOptimization0 (Named NCG) = False backendForcesOptimization0 (Named LLVM) = False backendForcesOptimization0 (Named ViaC) = False backendForcesOptimization0 (Named JavaScript) = False -backendForcesOptimization0 (Named Interpreter) = True +backendForcesOptimization0 (Named Bytecode) = True backendForcesOptimization0 (Named NoBackend) = False -- | I don't understand exactly how this works. But if @@ -683,7 +688,7 @@ backendNeedsFullWays (Named NCG) = False backendNeedsFullWays (Named LLVM) = False backendNeedsFullWays (Named ViaC) = False backendNeedsFullWays (Named JavaScript) = False -backendNeedsFullWays (Named Interpreter) = True +backendNeedsFullWays (Named Bytecode) = True backendNeedsFullWays (Named NoBackend) = False -- | This flag is also special for the interpreter: if a @@ -695,7 +700,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing backendSpecialModuleSource (Named LLVM) = const Nothing backendSpecialModuleSource (Named ViaC) = const Nothing backendSpecialModuleSource (Named JavaScript) = const Nothing -backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing +backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing backendSpecialModuleSource (Named NoBackend) = const (Just "nothing") -- | This flag says whether the back end supports Haskell @@ -707,7 +712,7 @@ backendSupportsHpc (Named NCG) = True backendSupportsHpc (Named LLVM) = True backendSupportsHpc (Named ViaC) = True backendSupportsHpc (Named JavaScript) = False -backendSupportsHpc (Named Interpreter) = False +backendSupportsHpc (Named Bytecode) = False backendSupportsHpc (Named NoBackend) = True -- | This flag says whether the back end supports foreign @@ -718,7 +723,7 @@ backendSupportsCImport (Named NCG) = True backendSupportsCImport (Named LLVM) = True backendSupportsCImport (Named ViaC) = True backendSupportsCImport (Named JavaScript) = True -backendSupportsCImport (Named Interpreter) = True +backendSupportsCImport (Named Bytecode) = True backendSupportsCImport (Named NoBackend) = True -- | This flag says whether the back end supports foreign @@ -728,7 +733,7 @@ backendSupportsCExport (Named NCG) = True backendSupportsCExport (Named LLVM) = True backendSupportsCExport (Named ViaC) = True backendSupportsCExport (Named JavaScript) = True -backendSupportsCExport (Named Interpreter) = False +backendSupportsCExport (Named Bytecode) = False backendSupportsCExport (Named NoBackend) = True -- | When using this back end, it may be necessary or @@ -749,7 +754,7 @@ backendCDefs (Named NCG) = NoCDefs backendCDefs (Named LLVM) = LlvmCDefs backendCDefs (Named ViaC) = NoCDefs backendCDefs (Named JavaScript) = NoCDefs -backendCDefs (Named Interpreter) = NoCDefs +backendCDefs (Named Bytecode) = NoCDefs backendCDefs (Named NoBackend) = NoCDefs -- | This (defunctionalized) function generates code and @@ -768,7 +773,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput backendCodeOutput (Named LLVM) = LlvmCodeOutput backendCodeOutput (Named ViaC) = ViaCCodeOutput backendCodeOutput (Named JavaScript) = JSCodeOutput -backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend" +backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: bytecodeBackend" backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend" backendUseJSLinker :: Backend -> Bool @@ -776,7 +781,7 @@ backendUseJSLinker (Named NCG) = False backendUseJSLinker (Named LLVM) = False backendUseJSLinker (Named ViaC) = False backendUseJSLinker (Named JavaScript) = True -backendUseJSLinker (Named Interpreter) = False +backendUseJSLinker (Named Bytecode) = False backendUseJSLinker (Named NoBackend) = False -- | This (defunctionalized) function tells the compiler @@ -795,7 +800,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline -backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline +backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline -- | Somewhere in the compiler driver, when compiling @@ -809,7 +814,7 @@ backendNormalSuccessorPhase (Named NCG) = As False backendNormalSuccessorPhase (Named LLVM) = LlvmOpt backendNormalSuccessorPhase (Named ViaC) = HCc backendNormalSuccessorPhase (Named JavaScript) = StopLn -backendNormalSuccessorPhase (Named Interpreter) = StopLn +backendNormalSuccessorPhase (Named Bytecode) = StopLn backendNormalSuccessorPhase (Named NoBackend) = StopLn -- | Name of the back end, if any. Used to migrate legacy @@ -820,7 +825,7 @@ backendName (Named NCG) = NCG backendName (Named LLVM) = LLVM backendName (Named ViaC) = ViaC backendName (Named JavaScript) = JavaScript -backendName (Named Interpreter) = Interpreter +backendName (Named Bytecode) = Bytecode backendName (Named NoBackend) = NoBackend @@ -833,7 +838,7 @@ allBackends = [ ncgBackend , llvmBackend , viaCBackend , jsBackend - , interpreterBackend + , bytecodeBackend , noBackend ] ===================================== compiler/GHC/Driver/Backend/Internal.hs ===================================== @@ -28,6 +28,6 @@ data BackendName | LLVM -- ^ Names the LLVM backend. | ViaC -- ^ Names the Via-C backend. | JavaScript -- ^ Names the JS backend. - | Interpreter -- ^ Names the ByteCode interpreter. + | Bytecode -- ^ Names the ByteCode interpreter. | NoBackend -- ^ Names the `-fno-code` backend. deriving (Eq, Show) ===================================== compiler/GHC/Driver/Downsweep.hs ===================================== @@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags)) <*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags)) let new_dflags = case enable_spec of - EnableByteCode -> dflags { backend = interpreterBackend } + EnableByteCode -> dflags { backend = bytecodeBackend } EnableObject -> dflags { backend = defaultBackendOf ms } EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms} let ms' = ms ===================================== compiler/GHC/Driver/Pipeline.hs ===================================== @@ -281,8 +281,8 @@ compileOne' mHscMessage -- was set), force it to generate byte-code. This is NOT transitive and -- only applies to direct targets. | loadAsByteCode - = ( interpreterBackend - , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp + = ( bytecodeBackend + , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp ) | otherwise ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1931,7 +1931,7 @@ dynamic_flags_deps = [ d { ghcLink=NoLink }) >> setBackend noBackend)) , make_ord_flag defFlag "fbyte-code" (noArgM $ \dflags -> do - setBackend interpreterBackend + setBackend bytecodeBackend pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode)) , make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do setBackend $ platformDefaultBackend (targetPlatform dflags) ===================================== compiler/GHC/Types/Unique/FM.hs ===================================== @@ -51,7 +51,9 @@ module GHC.Types.Unique.FM ( delListFromUFM, delListFromUFM_Directly, plusUFM, + strictPlusUFM, plusUFM_C, + strictPlusUFM_C, plusUFM_CD, plusUFM_CD2, mergeUFM, @@ -251,16 +253,24 @@ delListFromUFM_Directly = foldl' delFromUFM_Directly delFromUFM_Directly :: UniqFM key elt -> Unique -> UniqFM key elt delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m) --- Bindings in right argument shadow those in the left +-- | Bindings in right argument shadow those in the left. +-- +-- Unlike containers this union is right-biased for historic reasons. plusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt --- M.union is left-biased, plusUFM should be right-biased. plusUFM (UFM x) (UFM y) = UFM (M.union y x) -- Note (M.union y x), with arguments flipped -- M.union is left-biased, plusUFM should be right-biased. +-- | Right biased +strictPlusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt +strictPlusUFM (UFM x) (UFM y) = UFM (MS.union y x) + plusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y) +strictPlusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt +strictPlusUFM_C f (UFM x) (UFM y) = UFM (MS.unionWith f x y) + -- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the -- combinding function and `d1` resp. `d2` as the default value if -- there is no entry in `m1` reps. `m2`. The domain is the union of ===================================== compiler/GHC/Types/Var/Env.hs ===================================== @@ -12,7 +12,8 @@ module GHC.Types.Var.Env ( elemVarEnv, disjointVarEnv, anyVarEnv, extendVarEnv, extendVarEnv_C, extendVarEnv_Acc, extendVarEnvList, - plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusMaybeVarEnv_C, + strictPlusVarEnv, plusVarEnv, plusVarEnv_C, strictPlusVarEnv_C, + plusVarEnv_CD, plusMaybeVarEnv_C, plusVarEnvList, alterVarEnv, delVarEnvList, delVarEnv, minusVarEnv, @@ -511,6 +512,7 @@ extendVarEnv :: VarEnv a -> Var -> a -> VarEnv a extendVarEnv_C :: (a->a->a) -> VarEnv a -> Var -> a -> VarEnv a extendVarEnv_Acc :: (a->b->b) -> (a->b) -> VarEnv b -> Var -> a -> VarEnv b plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a +strictPlusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a plusVarEnvList :: [VarEnv a] -> VarEnv a extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a varEnvDomain :: VarEnv elt -> UnVarSet @@ -522,6 +524,7 @@ delVarEnvList :: Foldable f => VarEnv a -> f Var -> VarEnv a delVarEnv :: VarEnv a -> Var -> VarEnv a minusVarEnv :: VarEnv a -> VarEnv b -> VarEnv a plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a +strictPlusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a plusMaybeVarEnv_C :: (a -> a -> Maybe a) -> VarEnv a -> VarEnv a -> VarEnv a mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b @@ -548,6 +551,7 @@ extendVarEnv_C = addToUFM_C extendVarEnv_Acc = addToUFM_Acc extendVarEnvList = addListToUFM plusVarEnv_C = plusUFM_C +strictPlusVarEnv_C = strictPlusUFM_C plusVarEnv_CD = plusUFM_CD plusMaybeVarEnv_C = plusMaybeUFM_C delVarEnvList = delListFromUFM @@ -556,6 +560,7 @@ delVarEnvList = delListFromUFM delVarEnv = delFromUFM minusVarEnv = minusUFM plusVarEnv = plusUFM +strictPlusVarEnv = strictPlusUFM plusVarEnvList = plusUFMList -- lookupVarEnv is very hot (in part due to being called by substTyVar), -- if it's not inlined than the mere allocation of the Just constructor causes ===================================== docs/users_guide/extending_ghc.rst ===================================== @@ -1719,7 +1719,7 @@ constructor from version 9.4 with the corresponding value from 9.6: +-----------------+------------------------+ | ``ViaC`` | ``viaCBackend`` | +-----------------+------------------------+ -| ``Interpreter`` | ``interpreterBackend`` | +| ``Interpreter`` | ``bytecodeBackend`` | +-----------------+------------------------+ | ``NoBackend`` | ``noBackend`` | +-----------------+------------------------+ ===================================== ghc/Main.hs ===================================== @@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do let dflt_backend = backend dflags0 (mode, bcknd, link) = case postLoadMode of - DoInteractive -> (CompManager, interpreterBackend, LinkInMemory) - DoEval _ -> (CompManager, interpreterBackend, LinkInMemory) - DoRun -> (CompManager, interpreterBackend, LinkInMemory) + DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory) + DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory) + DoRun -> (CompManager, bytecodeBackend, LinkInMemory) DoMake -> (CompManager, dflt_backend, LinkBinary) DoBackpack -> (CompManager, dflt_backend, LinkBinary) DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary) ===================================== testsuite/driver/testglobals.py ===================================== @@ -136,9 +136,12 @@ class TestConfig: # Do we have interpreter support? self.have_interp = False + # Do we have external interpreter support? + self.have_ext_interp = False + # Are we cross-compiling? self.cross = False - + # Does the RTS linker only support loading shared libraries? self.interp_force_dyn = False ===================================== testsuite/driver/testlib.py ===================================== @@ -549,10 +549,12 @@ only_ghci = only_ways([WayName('ghci'), WayName('ghci-opt')]) # ----- def valid_way( way: WayName ) -> bool: - if way in {'ghci', 'ghci-opt', 'ghci-ext'}: + if way in {'ghci', 'ghci-opt'}: return config.have_RTS_linker - if way == 'ghci-ext-prof': - return config.have_RTS_linker and config.have_profiling + if way in {'ghci-ext'}: + return config.have_ext_interp + if way in {'ghci-ext-prof'}: + return config.have_ext_interp and config.have_profiling return True def extra_ways( ways: List[WayName] ): ===================================== testsuite/tests/concurrent/prog001/all.T ===================================== @@ -16,4 +16,4 @@ test('concprog001', [extra_files(['Arithmetic.hs', 'Converter.hs', 'Mult.hs', 'S when(fast(), skip), only_ways(['threaded2']), fragile(16604), run_timeout_multiplier(2)], - multimod_compile_and_run, ['Mult', '']) + multimod_compile_and_run, ['Mult', '-Wno-x-partial']) ===================================== testsuite/tests/driver/T5313.hs ===================================== @@ -7,7 +7,7 @@ main = do -- begin initialize df0 <- GHC.getSessionDynFlags let df1 = df0{GHC.ghcMode = GHC.CompManager, - GHC.backend = GHC.interpreterBackend, + GHC.backend = GHC.bytecodeBackend, GHC.ghcLink = GHC.LinkInMemory, GHC.verbosity = 0} _ <- GHC.setSessionDynFlags df1 ===================================== testsuite/tests/ghc-api/T10052/T10052.hs ===================================== @@ -24,7 +24,7 @@ runGhc' args act = do logger <- getLogger (dflags1, _leftover, _warns) <- parseDynamicFlags logger dflags0 flags let dflags2 = dflags1 { - backend = interpreterBackend + backend = bytecodeBackend , ghcLink = LinkInMemory , verbosity = 1 } ===================================== testsuite/tests/ghc-api/T8639_api.hs ===================================== @@ -11,7 +11,7 @@ main = do { [libdir] <- getArgs ; runGhc (Just libdir) $ do flags <- getSessionDynFlags - setSessionDynFlags (flags{ backend = interpreterBackend, ghcLink = LinkInMemory}) + setSessionDynFlags (flags{ backend = bytecodeBackend, ghcLink = LinkInMemory}) target <- guessTarget "T8639_api_a.hs" Nothing Nothing setTargets [target] load LoadAllTargets ===================================== testsuite/tests/ghc-api/apirecomp001/myghc.hs ===================================== @@ -37,7 +37,7 @@ main = do prn "target nothing: ok" dflags <- getSessionDynFlags - setSessionDynFlags $ dflags { backend = interpreterBackend } + setSessionDynFlags $ dflags { backend = bytecodeBackend } ok <- load LoadAllTargets when (failed ok) $ error "Couldn't load A.hs in interpreted mode" prn "target interpreted: ok" ===================================== testsuite/tests/ghci-wasm/T26431.hs ===================================== @@ -16,7 +16,7 @@ main = do let dflags1 = dflags0 { ghcMode = CompManager, - backend = interpreterBackend, + backend = bytecodeBackend, ghcLink = LinkInMemory } logger <- getLogger ===================================== testsuite/tests/ghci/linking/dyn/T3372.hs ===================================== @@ -44,7 +44,7 @@ newGhcServer = do (libdir:_) <- getArgs where ghc action libdir = GHC.runGhc (Just libdir) (init >> action) init = do df <- GHC.getSessionDynFlags GHC.setSessionDynFlags df{GHC.ghcMode = GHC.CompManager, - GHC.backend = GHC.interpreterBackend, + GHC.backend = GHC.bytecodeBackend, GHC.ghcLink = GHC.LinkInMemory, GHC.verbosity = 0} ===================================== testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T ===================================== @@ -2,9 +2,8 @@ test('PackedDataCon', [ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']), req_interp, req_bco, - extra_ways(['ghci']), - when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])), - when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof'])) + extra_ways(ghci_ways), + only_ways(ghci_ways), ], compile_and_run, [''] ===================================== testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T ===================================== @@ -2,9 +2,8 @@ test('UnboxedTuples', [ extra_files(['Obj.hs', 'ByteCode.hs', 'Common.hs-incl']), req_interp, req_bco, - extra_ways(['ghci']), - when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])), - when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof'])) + only_ways(ghci_ways), + extra_ways(ghci_ways), ], compile_and_run, [''] ===================================== testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T ===================================== @@ -2,9 +2,8 @@ test('UnliftedDataTypeInterp', [ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']), req_interp, req_bco, - extra_ways(['ghci']), - when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])), - when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof'])) + only_ways(ghci_ways), + extra_ways(ghci_ways), ], compile_and_run, [''] ===================================== testsuite/tests/perf/compiler/T26425.hs ===================================== @@ -0,0 +1,664 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Reproducer (strToInt) where + +import qualified Data.Text as T + +{- This program results in a nested chain of join points and cases which tests + primarily OccAnal and Unfolding performance. +-} + +strToInt :: T.Text -> Maybe Int +strToInt txt = case txt of + "0" -> Just 0 + "1" -> Just 1 + "2" -> Just 2 + "3" -> Just 3 + "4" -> Just 4 + "5" -> Just 5 + "6" -> Just 6 + "7" -> Just 7 + "8" -> Just 8 + "9" -> Just 9 + "10" -> Just 10 + "11" -> Just 11 + "12" -> Just 12 + "13" -> Just 13 + "14" -> Just 14 + "15" -> Just 15 + "16" -> Just 16 + "17" -> Just 17 + "18" -> Just 18 + "19" -> Just 19 + "20" -> Just 20 + "21" -> Just 21 + "22" -> Just 22 + "23" -> Just 23 + "24" -> Just 24 + "25" -> Just 25 + "26" -> Just 26 + "27" -> Just 27 + "28" -> Just 28 + "29" -> Just 29 + "30" -> Just 30 + "31" -> Just 31 + "32" -> Just 32 + "33" -> Just 33 + "34" -> Just 34 + "35" -> Just 35 + "36" -> Just 36 + "37" -> Just 37 + "38" -> Just 38 + "39" -> Just 39 + "40" -> Just 40 + "41" -> Just 41 + "42" -> Just 42 + "43" -> Just 43 + "44" -> Just 44 + "45" -> Just 45 + "46" -> Just 46 + "47" -> Just 47 + "48" -> Just 48 + "49" -> Just 49 + "50" -> Just 50 + "51" -> Just 51 + "52" -> Just 52 + "53" -> Just 53 + "54" -> Just 54 + "55" -> Just 55 + "56" -> Just 56 + "57" -> Just 57 + "58" -> Just 58 + "59" -> Just 59 + "60" -> Just 60 + "61" -> Just 61 + "62" -> Just 62 + "63" -> Just 63 + "64" -> Just 64 + "65" -> Just 65 + "66" -> Just 66 + "67" -> Just 67 + "68" -> Just 68 + "69" -> Just 69 + "70" -> Just 70 + "71" -> Just 71 + "72" -> Just 72 + "73" -> Just 73 + "74" -> Just 74 + "75" -> Just 75 + "76" -> Just 76 + "77" -> Just 77 + "78" -> Just 78 + "79" -> Just 79 + "80" -> Just 80 + "81" -> Just 81 + "82" -> Just 82 + "83" -> Just 83 + "84" -> Just 84 + "85" -> Just 85 + "86" -> Just 86 + "87" -> Just 87 + "88" -> Just 88 + "89" -> Just 89 + "90" -> Just 90 + "91" -> Just 91 + "92" -> Just 92 + "93" -> Just 93 + "94" -> Just 94 + "95" -> Just 95 + "96" -> Just 96 + "97" -> Just 97 + "98" -> Just 98 + "99" -> Just 99 + "100" -> Just 100 + "101" -> Just 101 + "102" -> Just 102 + "103" -> Just 103 + "104" -> Just 104 + "105" -> Just 105 + "106" -> Just 106 + "107" -> Just 107 + "108" -> Just 108 + "109" -> Just 109 + "110" -> Just 110 + "111" -> Just 111 + "112" -> Just 112 + "113" -> Just 113 + "114" -> Just 114 + "115" -> Just 115 + "116" -> Just 116 + "117" -> Just 117 + "118" -> Just 118 + "119" -> Just 119 + "120" -> Just 120 + "121" -> Just 121 + "122" -> Just 122 + "123" -> Just 123 + "124" -> Just 124 + "125" -> Just 125 + "126" -> Just 126 + "127" -> Just 127 + "128" -> Just 128 + "129" -> Just 129 + "130" -> Just 130 + "131" -> Just 131 + "132" -> Just 132 + "133" -> Just 133 + "134" -> Just 134 + "135" -> Just 135 + "136" -> Just 136 + "137" -> Just 137 + "138" -> Just 138 + "139" -> Just 139 + "140" -> Just 140 + "141" -> Just 141 + "142" -> Just 142 + "143" -> Just 143 + "144" -> Just 144 + "145" -> Just 145 + "146" -> Just 146 + "147" -> Just 147 + "148" -> Just 148 + "149" -> Just 149 + "150" -> Just 150 + "151" -> Just 151 + "152" -> Just 152 + "153" -> Just 153 + "154" -> Just 154 + "155" -> Just 155 + "156" -> Just 156 + "157" -> Just 157 + "158" -> Just 158 + "159" -> Just 159 + "160" -> Just 160 + "161" -> Just 161 + "162" -> Just 162 + "163" -> Just 163 + "164" -> Just 164 + "165" -> Just 165 + "166" -> Just 166 + "167" -> Just 167 + "168" -> Just 168 + "169" -> Just 169 + "170" -> Just 170 + "171" -> Just 171 + "172" -> Just 172 + "173" -> Just 173 + "174" -> Just 174 + "175" -> Just 175 + "176" -> Just 176 + "177" -> Just 177 + "178" -> Just 178 + "179" -> Just 179 + "180" -> Just 180 + "181" -> Just 181 + "182" -> Just 182 + "183" -> Just 183 + "184" -> Just 184 + "185" -> Just 185 + "186" -> Just 186 + "187" -> Just 187 + "188" -> Just 188 + "189" -> Just 189 + "190" -> Just 190 + "191" -> Just 191 + "192" -> Just 192 + "193" -> Just 193 + "194" -> Just 194 + "195" -> Just 195 + "196" -> Just 196 + "197" -> Just 197 + "198" -> Just 198 + "199" -> Just 199 + "200" -> Just 200 + "201" -> Just 201 + "202" -> Just 202 + "203" -> Just 203 + "204" -> Just 204 + "205" -> Just 205 + "206" -> Just 206 + "207" -> Just 207 + "208" -> Just 208 + "209" -> Just 209 + "210" -> Just 210 + "211" -> Just 211 + "212" -> Just 212 + "213" -> Just 213 + "214" -> Just 214 + "215" -> Just 215 + "216" -> Just 216 + "217" -> Just 217 + "218" -> Just 218 + "219" -> Just 219 + "220" -> Just 220 + "221" -> Just 221 + "222" -> Just 222 + "223" -> Just 223 + "224" -> Just 224 + "225" -> Just 225 + "226" -> Just 226 + "227" -> Just 227 + "228" -> Just 228 + "229" -> Just 229 + "230" -> Just 230 + "231" -> Just 231 + "232" -> Just 232 + "233" -> Just 233 + "234" -> Just 234 + "235" -> Just 235 + "236" -> Just 236 + "237" -> Just 237 + "238" -> Just 238 + "239" -> Just 239 + "240" -> Just 240 + "241" -> Just 241 + "242" -> Just 242 + "243" -> Just 243 + "244" -> Just 244 + "245" -> Just 245 + "246" -> Just 246 + "247" -> Just 247 + "248" -> Just 248 + "249" -> Just 249 + "250" -> Just 250 + "251" -> Just 251 + "252" -> Just 252 + "253" -> Just 253 + "254" -> Just 254 + "255" -> Just 255 + "256" -> Just 256 + "257" -> Just 257 + "258" -> Just 258 + "259" -> Just 259 + "260" -> Just 260 + "261" -> Just 261 + "262" -> Just 262 + "263" -> Just 263 + "264" -> Just 264 + "265" -> Just 265 + "266" -> Just 266 + "267" -> Just 267 + "268" -> Just 268 + "269" -> Just 269 + "270" -> Just 270 + "271" -> Just 271 + "272" -> Just 272 + "273" -> Just 273 + "274" -> Just 274 + "275" -> Just 275 + "276" -> Just 276 + "277" -> Just 277 + "278" -> Just 278 + "279" -> Just 279 + "280" -> Just 280 + "281" -> Just 281 + "282" -> Just 282 + "283" -> Just 283 + "284" -> Just 284 + "285" -> Just 285 + "286" -> Just 286 + "287" -> Just 287 + "288" -> Just 288 + "289" -> Just 289 + "290" -> Just 290 + "291" -> Just 291 + "292" -> Just 292 + "293" -> Just 293 + "294" -> Just 294 + "295" -> Just 295 + "296" -> Just 296 + "297" -> Just 297 + "298" -> Just 298 + "299" -> Just 299 + "300" -> Just 300 + "301" -> Just 301 + "302" -> Just 302 + "303" -> Just 303 + "304" -> Just 304 + "305" -> Just 305 + "306" -> Just 306 + "307" -> Just 307 + "308" -> Just 308 + "309" -> Just 309 + "310" -> Just 310 + "311" -> Just 311 + "312" -> Just 312 + "313" -> Just 313 + "314" -> Just 314 + "315" -> Just 315 + "316" -> Just 316 + "317" -> Just 317 + "318" -> Just 318 + "319" -> Just 319 + "320" -> Just 320 + "321" -> Just 321 + "322" -> Just 322 + "323" -> Just 323 + "324" -> Just 324 + "325" -> Just 325 + "326" -> Just 326 + "327" -> Just 327 + "328" -> Just 328 + "329" -> Just 329 + "330" -> Just 330 + "331" -> Just 331 + "332" -> Just 332 + "333" -> Just 333 + "334" -> Just 334 + "335" -> Just 335 + "336" -> Just 336 + "337" -> Just 337 + "338" -> Just 338 + "339" -> Just 339 + "340" -> Just 340 + "341" -> Just 341 + "342" -> Just 342 + "343" -> Just 343 + "344" -> Just 344 + "345" -> Just 345 + "346" -> Just 346 + "347" -> Just 347 + "348" -> Just 348 + "349" -> Just 349 + "350" -> Just 350 + "351" -> Just 351 + "352" -> Just 352 + "353" -> Just 353 + "354" -> Just 354 + "355" -> Just 355 + "356" -> Just 356 + "357" -> Just 357 + "358" -> Just 358 + "359" -> Just 359 + "360" -> Just 360 + "361" -> Just 361 + "362" -> Just 362 + "363" -> Just 363 + "364" -> Just 364 + "365" -> Just 365 + "366" -> Just 366 + "367" -> Just 367 + "368" -> Just 368 + "369" -> Just 369 + "370" -> Just 370 + "371" -> Just 371 + "372" -> Just 372 + "373" -> Just 373 + "374" -> Just 374 + "375" -> Just 375 + "376" -> Just 376 + "377" -> Just 377 + "378" -> Just 378 + "379" -> Just 379 + "380" -> Just 380 + "381" -> Just 381 + "382" -> Just 382 + "383" -> Just 383 + "384" -> Just 384 + "385" -> Just 385 + "386" -> Just 386 + "387" -> Just 387 + "388" -> Just 388 + "389" -> Just 389 + "390" -> Just 390 + "391" -> Just 391 + "392" -> Just 392 + "393" -> Just 393 + "394" -> Just 394 + "395" -> Just 395 + "396" -> Just 396 + "397" -> Just 397 + "398" -> Just 398 + "399" -> Just 399 + "400" -> Just 400 + "401" -> Just 401 + "402" -> Just 402 + "403" -> Just 403 + "404" -> Just 404 + "405" -> Just 405 + "406" -> Just 406 + "407" -> Just 407 + "408" -> Just 408 + "409" -> Just 409 + "410" -> Just 410 + "411" -> Just 411 + "412" -> Just 412 + "413" -> Just 413 + "414" -> Just 414 + "415" -> Just 415 + "416" -> Just 416 + "417" -> Just 417 + "418" -> Just 418 + "419" -> Just 419 + "420" -> Just 420 + "421" -> Just 421 + "422" -> Just 422 + "423" -> Just 423 + "424" -> Just 424 + "425" -> Just 425 + "426" -> Just 426 + "427" -> Just 427 + "428" -> Just 428 + "429" -> Just 429 + "430" -> Just 430 + "431" -> Just 431 + "432" -> Just 432 + "433" -> Just 433 + "434" -> Just 434 + "435" -> Just 435 + "436" -> Just 436 + "437" -> Just 437 + "438" -> Just 438 + "439" -> Just 439 + "440" -> Just 440 + "441" -> Just 441 + "442" -> Just 442 + "443" -> Just 443 + "444" -> Just 444 + "445" -> Just 445 + "446" -> Just 446 + "447" -> Just 447 + "448" -> Just 448 + "449" -> Just 449 + "450" -> Just 450 + "451" -> Just 451 + "452" -> Just 452 + "453" -> Just 453 + "454" -> Just 454 + "455" -> Just 455 + "456" -> Just 456 + "457" -> Just 457 + "458" -> Just 458 + "459" -> Just 459 + "460" -> Just 460 + "461" -> Just 461 + "462" -> Just 462 + "463" -> Just 463 + "464" -> Just 464 + "465" -> Just 465 + "466" -> Just 466 + "467" -> Just 467 + "468" -> Just 468 + "469" -> Just 469 + "470" -> Just 470 + "471" -> Just 471 + "472" -> Just 472 + "473" -> Just 473 + "474" -> Just 474 + "475" -> Just 475 + "476" -> Just 476 + "477" -> Just 477 + "478" -> Just 478 + "479" -> Just 479 + "480" -> Just 480 + "481" -> Just 481 + "482" -> Just 482 + "483" -> Just 483 + "484" -> Just 484 + "485" -> Just 485 + "486" -> Just 486 + "487" -> Just 487 + "488" -> Just 488 + "489" -> Just 489 + "490" -> Just 490 + "491" -> Just 491 + "492" -> Just 492 + "493" -> Just 493 + "494" -> Just 494 + "495" -> Just 495 + "496" -> Just 496 + "497" -> Just 497 + "498" -> Just 498 + "499" -> Just 499 + "500" -> Just 500 + "501" -> Just 501 + "502" -> Just 502 + "503" -> Just 503 + "504" -> Just 504 + "505" -> Just 505 + "506" -> Just 506 + "507" -> Just 507 + "508" -> Just 508 + "509" -> Just 509 + "510" -> Just 510 + "511" -> Just 511 + "512" -> Just 512 + "513" -> Just 513 + "514" -> Just 514 + "515" -> Just 515 + "516" -> Just 516 + "517" -> Just 517 + "518" -> Just 518 + "519" -> Just 519 + "520" -> Just 520 + "521" -> Just 521 + "522" -> Just 522 + "523" -> Just 523 + "524" -> Just 524 + "525" -> Just 525 + "526" -> Just 526 + "527" -> Just 527 + "528" -> Just 528 + "529" -> Just 529 + "530" -> Just 530 + "531" -> Just 531 + "532" -> Just 532 + "533" -> Just 533 + "534" -> Just 534 + "535" -> Just 535 + "536" -> Just 536 + "537" -> Just 537 + "538" -> Just 538 + "539" -> Just 539 + "540" -> Just 540 + "541" -> Just 541 + "542" -> Just 542 + "543" -> Just 543 + "544" -> Just 544 + "545" -> Just 545 + "546" -> Just 546 + "547" -> Just 547 + "548" -> Just 548 + "549" -> Just 549 + "550" -> Just 550 + "551" -> Just 551 + "552" -> Just 552 + "553" -> Just 553 + "554" -> Just 554 + "555" -> Just 555 + "556" -> Just 556 + "557" -> Just 557 + "558" -> Just 558 + "559" -> Just 559 + "560" -> Just 560 + "561" -> Just 561 + "562" -> Just 562 + "563" -> Just 563 + "564" -> Just 564 + "565" -> Just 565 + "566" -> Just 566 + "567" -> Just 567 + "568" -> Just 568 + "569" -> Just 569 + "570" -> Just 570 + "571" -> Just 571 + "572" -> Just 572 + "573" -> Just 573 + "574" -> Just 574 + "575" -> Just 575 + "576" -> Just 576 + "577" -> Just 577 + "578" -> Just 578 + "579" -> Just 579 + "580" -> Just 580 + "581" -> Just 581 + "582" -> Just 582 + "583" -> Just 583 + "584" -> Just 584 + "585" -> Just 585 + "586" -> Just 586 + "587" -> Just 587 + "588" -> Just 588 + "589" -> Just 589 + "590" -> Just 590 + "591" -> Just 591 + "592" -> Just 592 + "593" -> Just 593 + "594" -> Just 594 + "595" -> Just 595 + "596" -> Just 596 + "597" -> Just 597 + "598" -> Just 598 + "599" -> Just 599 + "600" -> Just 600 + "601" -> Just 601 + "602" -> Just 602 + "603" -> Just 603 + "604" -> Just 604 + "605" -> Just 605 + "606" -> Just 606 + "607" -> Just 607 + "608" -> Just 608 + "609" -> Just 609 + "610" -> Just 610 + "611" -> Just 611 + "612" -> Just 612 + "613" -> Just 613 + "614" -> Just 614 + "615" -> Just 615 + "616" -> Just 616 + "617" -> Just 617 + "618" -> Just 618 + "619" -> Just 619 + "620" -> Just 620 + "621" -> Just 621 + "622" -> Just 622 + "623" -> Just 623 + "624" -> Just 624 + "625" -> Just 625 + "626" -> Just 626 + "627" -> Just 627 + "628" -> Just 628 + "629" -> Just 629 + "630" -> Just 630 + "631" -> Just 631 + "632" -> Just 632 + "633" -> Just 633 + "634" -> Just 634 + "635" -> Just 635 + "636" -> Just 636 + "637" -> Just 637 + "638" -> Just 638 + "639" -> Just 639 + "640" -> Just 640 + "641" -> Just 641 + "642" -> Just 642 + "643" -> Just 643 + "644" -> Just 644 + "645" -> Just 645 + "646" -> Just 646 + "647" -> Just 647 + "648" -> Just 648 + "649" -> Just 649 + "650" -> Just 650 + _ -> Nothing ===================================== testsuite/tests/perf/compiler/all.T ===================================== @@ -792,3 +792,8 @@ test('interpreter_steplocal', ], ghci_script, ['interpreter_steplocal.script']) + +test ('T26425', + [ collect_compiler_stats('all',5) ], + compile, + ['-O']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6db54184feb8064e90a3f64934cd16d... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6db54184feb8064e90a3f64934cd16d... You're receiving this email because of your account on gitlab.haskell.org.