
Simon Peyton Jones pushed to branch wip/T23298-test at Glasgow Haskell Compiler / GHC Commits: 2e204269 by Andreas Klebinger at 2025-04-22T12:20:41+02:00 Simplifier: Constant fold invald tagToEnum# calls to bottom expr. When applying tagToEnum# to a out-of-range value it's best to simply constant fold it to a bottom expression. That potentially allows more dead code elimination and makes debugging easier. Fixes #25976 - - - - - 7250fc0c by Matthew Pickering at 2025-04-22T16:24:04-04:00 Move -fno-code note into Downsweep module This note was left behind when all the code which referred to it was moved into the GHC.Driver.Downsweep module - - - - - d2dc89b4 by Matthew Pickering at 2025-04-22T16:24:04-04:00 Apply editing notes to Note [-fno-code mode] suggested by sheaf These notes were suggested in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14241 - - - - - 90ee5634 by Simon Peyton Jones at 2025-04-23T08:58:22+01:00 Test for #23298 - - - - - 8 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/Make.hs - + testsuite/tests/gadt/T23298.hs - + testsuite/tests/gadt/T23298.stderr - testsuite/tests/gadt/all.T - + testsuite/tests/simplCore/should_compile/T25976.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -69,7 +69,6 @@ import GHC.Cmm.MachOp ( FMASign(..) ) import GHC.Cmm.Type ( Width(..) ) import GHC.Data.FastString -import GHC.Data.Maybe ( orElse ) import GHC.Utils.Outputable import GHC.Utils.Misc @@ -1997,6 +1996,14 @@ because we don't expect the user to call tagToEnum# at all; we merely generate calls in derived instances of Enum. So we compromise: a rewrite rule rewrites a bad instance of tagToEnum# to an error call, and emits a warning. + +We also do something similar if we can see that the argument of tagToEnum is out +of bounds, e.g. `tagToEnum# 99# :: Bool`. +Replacing this with an error expression is better for two reasons: +* It allow us to eliminate more dead code in cases like `case tagToEnum# 99# :: Bool of ...` +* Should we actually end up executing the relevant code at runtime the user will + see a meaningful error message, instead of a segfault or incorrect result. +See #25976. -} tagToEnumRule :: RuleM CoreExpr @@ -2008,9 +2015,13 @@ tagToEnumRule = do Just (tycon, tc_args) | isEnumerationTyCon tycon -> do let tag = fromInteger i correct_tag dc = (dataConTagZ dc) == tag - (dc:rest) <- return $ filter correct_tag (tyConDataCons_maybe tycon `orElse` []) - massert (null rest) - return $ mkTyApps (Var (dataConWorkId dc)) tc_args + Just dataCons <- pure $ tyConDataCons_maybe tycon + case filter correct_tag dataCons of + (dc:rest) -> do + massert (null rest) + pure $ mkTyApps (Var (dataConWorkId dc)) tc_args + -- Literal is out of range, e.g. tagToEnum @Bool #4 + [] -> pure $ mkImpossibleExpr ty "tagToEnum: Argument out of range" -- See Note [tagToEnum#] _ -> warnPprTrace True "tagToEnum# on non-enumeration type" (ppr ty) $ ===================================== compiler/GHC/Driver/Downsweep.hs ===================================== @@ -947,6 +947,71 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do hostFullWays in dflags_c +{- Note [-fno-code mode] +~~~~~~~~~~~~~~~~~~~~~~~~ +GHC offers the flag -fno-code for the purpose of parsing and typechecking a +program without generating object files. This is intended to be used by tooling +and IDEs to provide quick feedback on any parser or type errors as cheaply as +possible. + +When GHC is invoked with -fno-code, no object files or linked output will be +generated. As many errors and warnings as possible will be generated, as if +-fno-code had not been passed. The session DynFlags will have +backend == NoBackend. + +-fwrite-interface +~~~~~~~~~~~~~~~~ +Whether interface files are generated in -fno-code mode is controlled by the +-fwrite-interface flag. The -fwrite-interface flag is a no-op if -fno-code is +not also passed. Recompilation avoidance requires interface files, so passing +-fno-code without -fwrite-interface should be avoided. If -fno-code were +re-implemented today, there would be no need for -fwrite-interface as it +would considered always on; this behaviour is as it is for backwards compatibility. + +================================================================ +IN SUMMARY: ALWAYS PASS -fno-code AND -fwrite-interface TOGETHER +================================================================ + +Template Haskell +~~~~~~~~~~~~~~~~ +A module using Template Haskell may invoke an imported function from inside a +splice. This will cause the type-checker to attempt to execute that code, which +would fail if no object files had been generated. See #8025. To rectify this, +during the downsweep we patch the DynFlags in the ModSummary of any home module +that is imported by a module that uses Template Haskell to generate object +code. + +The flavour of the generated code depends on whether `-fprefer-byte-code` is enabled +or not in the module which needs the code generation. If the module requires byte-code then +dependencies will generate byte-code, otherwise they will generate object files. +In the case where some modules require byte-code and some object files, both are +generated by enabling `-fbyte-code-and-object-code`, the test "fat015" tests these +configurations. + +The object files (and interface files if -fwrite-interface is disabled) produced +for Template Haskell are written to temporary files. + +Note that since Template Haskell can run arbitrary IO actions, -fno-code mode +is no more secure than running without it. + +Potential TODOS: +~~~~~ +* Remove -fwrite-interface and have interface files always written in -fno-code + mode +* Both .o and .dyn_o files are generated for template haskell, but we only need + .dyn_o. Fix it. +* In make mode, a message like + Compiling A (A.hs, /tmp/ghc_123.o) + is shown if downsweep enabled object code generation for A. Perhaps we should + show "nothing" or "temporary object file" instead. Note that one + can currently use -keep-tmp-files and inspect the generated file with the + current behaviour. +* Offer a -no-codedir command line option, and write what were temporary + object files there. This would speed up recompilation. +* Use existing object files (if they are up to date) instead of always + generating temporary ones. +-} + -- | Populate the Downsweep cache with the root modules. mkRootMap :: [ModuleNodeInfo] ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -1246,70 +1246,6 @@ addSptEntries hsc_env mlinkable = , spt <- bc_spt_entries bco ] -{- Note [-fno-code mode] -~~~~~~~~~~~~~~~~~~~~~~~~ -GHC offers the flag -fno-code for the purpose of parsing and typechecking a -program without generating object files. This is intended to be used by tooling -and IDEs to provide quick feedback on any parser or type errors as cheaply as -possible. - -When GHC is invoked with -fno-code no object files or linked output will be -generated. As many errors and warnings as possible will be generated, as if --fno-code had not been passed. The session DynFlags will have -backend == NoBackend. - --fwrite-interface -~~~~~~~~~~~~~~~~ -Whether interface files are generated in -fno-code mode is controlled by the --fwrite-interface flag. The -fwrite-interface flag is a no-op if -fno-code is -not also passed. Recompilation avoidance requires interface files, so passing --fno-code without -fwrite-interface should be avoided. If -fno-code were -re-implemented today, -fwrite-interface would be discarded and it would be -considered always on; this behaviour is as it is for backwards compatibility. - -================================================================ -IN SUMMARY: ALWAYS PASS -fno-code AND -fwrite-interface TOGETHER -================================================================ - -Template Haskell -~~~~~~~~~~~~~~~~ -A module using template haskell may invoke an imported function from inside a -splice. This will cause the type-checker to attempt to execute that code, which -would fail if no object files had been generated. See #8025. To rectify this, -during the downsweep we patch the DynFlags in the ModSummary of any home module -that is imported by a module that uses template haskell, to generate object -code. - -The flavour of the generated code depends on whether `-fprefer-byte-code` is enabled -or not in the module which needs the code generation. If the module requires byte-code then -dependencies will generate byte-code, otherwise they will generate object files. -In the case where some modules require byte-code and some object files, both are -generated by enabling `-fbyte-code-and-object-code`, the test "fat015" tests these -configurations. - -The object files (and interface files if -fwrite-interface is disabled) produced -for template haskell are written to temporary files. - -Note that since template haskell can run arbitrary IO actions, -fno-code mode -is no more secure than running without it. - -Potential TODOS: -~~~~~ -* Remove -fwrite-interface and have interface files always written in -fno-code - mode -* Both .o and .dyn_o files are generated for template haskell, but we only need - .dyn_o. Fix it. -* In make mode, a message like - Compiling A (A.hs, /tmp/ghc_123.o) - is shown if downsweep enabled object code generation for A. Perhaps we should - show "nothing" or "temporary object file" instead. Note that one - can currently use -keep-tmp-files and inspect the generated file with the - current behaviour. -* Offer a -no-codedir command line option, and write what were temporary - object files there. This would speed up recompilation. -* Use existing object files (if they are up to date) instead of always - generating temporary ones. --} -- Note [When source is considered modified] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== testsuite/tests/gadt/T23298.hs ===================================== @@ -0,0 +1,25 @@ +{-# LANGUAGE GADTs #-} +module T23298 where + +import Data.Kind (Type) + +type HList :: Type -> Type +data HList a where + HCons :: HList x -> HList (Maybe x) + +eq :: HList a -> Bool +eq x = case x of + HCons ms -> True + +go (HCons x) = go x + +{- go :: HList alpha -> beta + +Under HCons + [G] alpha ~ Maybe x + [W] HList x ~ HList alpha +==> + [W] x ~ alpha +==> + [W] x ~ Maybe x +-} ===================================== testsuite/tests/gadt/T23298.stderr ===================================== @@ -0,0 +1,12 @@ + T23298.hs:14:16: error: [GHC-25897] + • Couldn't match type ‘x’ with ‘Maybe x’ + Expected: HList x -> t + Actual: HList a -> t + ‘x’ is a rigid type variable bound by + a pattern with constructor: + HCons :: forall x. HList x -> HList (Maybe x), + in an equation for ‘go’ + at T23298.hs:14:5-11 + • In the expression: go x + In an equation for ‘go’: go (HCons x) = go x + • Relevant bindings include x :: HList x (bound at T23298.hs:14:11) ===================================== testsuite/tests/gadt/all.T ===================================== @@ -131,3 +131,4 @@ test('T19847a', normalise_version('base'), compile, ['-ddump-types']) test('T19847b', normal, compile, ['']) test('T23022', normal, compile, ['-dcore-lint']) test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test? +test('T23298', normal, compile_fail, ['']) ===================================== testsuite/tests/simplCore/should_compile/T25976.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE MagicHash #-} + +module T25976 where + +import GHC.PrimOps (tagToEnum#) + +-- Spoiler - it's all dead code since tagToEnum 3# is undefined +main = case (tagToEnum# 4# :: Bool) of + True -> print "Dead Code" + False -> print "Dead Code" ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -541,3 +541,5 @@ test('T25883', normal, compile_grep_core, ['']) test('T25883b', normal, compile_grep_core, ['']) test('T25883c', normal, compile_grep_core, ['']) test('T25883d', [extra_files(['T25883d_import.hs'])], multimod_compile_filter, ['T25883d', '-O -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques', r'grep -e "y ="']) + +test('T25976', [grep_errmsg('Dead Code')], compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fd9a3da0a21c8d09a3ddf8865880b8... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fd9a3da0a21c8d09a3ddf8865880b8... You're receiving this email because of your account on gitlab.haskell.org.