[Git][ghc/ghc][wip/andreask/fold_tag_to_enum] Simplifier: Constant fold invald tagToEnum# calls to bottom expr.

Andreas Klebinger pushed to branch wip/andreask/fold_tag_to_enum at Glasgow Haskell Compiler / GHC Commits: c53726a5 by Andreas Klebinger at 2025-04-21T13:29:28+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 - - - - - 3 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - + 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,13 @@ 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. -} tagToEnumRule :: RuleM CoreExpr @@ -2008,9 +2014,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) $ ===================================== 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" \ No newline at end of file ===================================== 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/-/commit/c53726a5cb85254102b22a766b4e1300... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c53726a5cb85254102b22a766b4e1300... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Andreas Klebinger (@AndreasK)