[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: 912f2e9f by Andreas Klebinger at 2025-04-19T13:43:14+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 ===================================== @@ -2008,9 +2008,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 ===================================== @@ -535,3 +535,4 @@ test('T25197', [req_th, extra_files(["T25197_TH.hs"]), only_ways(['optasm'])], m test('T25389', normal, compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds']) test('T24359a', normal, compile, ['-O -ddump-rules']) test('T25713', [grep_errmsg('W:::')], compile, ['-O -ddump-simpl']) +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/912f2e9f2cf73bba7c56484db4e465c4... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/912f2e9f2cf73bba7c56484db4e465c4... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Andreas Klebinger (@AndreasK)