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
-
7250fc0c
by Matthew Pickering at 2025-04-22T16:24:04-04:00
-
d2dc89b4
by Matthew Pickering at 2025-04-22T16:24:04-04:00
-
90ee5634
by Simon Peyton Jones at 2025-04-23T08:58:22+01:00
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:
... | ... | @@ -69,7 +69,6 @@ import GHC.Cmm.MachOp ( FMASign(..) ) |
69 | 69 | import GHC.Cmm.Type ( Width(..) )
|
70 | 70 | |
71 | 71 | import GHC.Data.FastString
|
72 | -import GHC.Data.Maybe ( orElse )
|
|
73 | 72 | |
74 | 73 | import GHC.Utils.Outputable
|
75 | 74 | import GHC.Utils.Misc
|
... | ... | @@ -1997,6 +1996,14 @@ because we don't expect the user to call tagToEnum# at all; we merely |
1997 | 1996 | generate calls in derived instances of Enum. So we compromise: a
|
1998 | 1997 | rewrite rule rewrites a bad instance of tagToEnum# to an error call,
|
1999 | 1998 | and emits a warning.
|
1999 | + |
|
2000 | +We also do something similar if we can see that the argument of tagToEnum is out
|
|
2001 | +of bounds, e.g. `tagToEnum# 99# :: Bool`.
|
|
2002 | +Replacing this with an error expression is better for two reasons:
|
|
2003 | +* It allow us to eliminate more dead code in cases like `case tagToEnum# 99# :: Bool of ...`
|
|
2004 | +* Should we actually end up executing the relevant code at runtime the user will
|
|
2005 | + see a meaningful error message, instead of a segfault or incorrect result.
|
|
2006 | +See #25976.
|
|
2000 | 2007 | -}
|
2001 | 2008 | |
2002 | 2009 | tagToEnumRule :: RuleM CoreExpr
|
... | ... | @@ -2008,9 +2015,13 @@ tagToEnumRule = do |
2008 | 2015 | Just (tycon, tc_args) | isEnumerationTyCon tycon -> do
|
2009 | 2016 | let tag = fromInteger i
|
2010 | 2017 | correct_tag dc = (dataConTagZ dc) == tag
|
2011 | - (dc:rest) <- return $ filter correct_tag (tyConDataCons_maybe tycon `orElse` [])
|
|
2012 | - massert (null rest)
|
|
2013 | - return $ mkTyApps (Var (dataConWorkId dc)) tc_args
|
|
2018 | + Just dataCons <- pure $ tyConDataCons_maybe tycon
|
|
2019 | + case filter correct_tag dataCons of
|
|
2020 | + (dc:rest) -> do
|
|
2021 | + massert (null rest)
|
|
2022 | + pure $ mkTyApps (Var (dataConWorkId dc)) tc_args
|
|
2023 | + -- Literal is out of range, e.g. tagToEnum @Bool #4
|
|
2024 | + [] -> pure $ mkImpossibleExpr ty "tagToEnum: Argument out of range"
|
|
2014 | 2025 | |
2015 | 2026 | -- See Note [tagToEnum#]
|
2016 | 2027 | _ -> warnPprTrace True "tagToEnum# on non-enumeration type" (ppr ty) $
|
... | ... | @@ -947,6 +947,71 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do |
947 | 947 | hostFullWays
|
948 | 948 | in dflags_c
|
949 | 949 | |
950 | +{- Note [-fno-code mode]
|
|
951 | +~~~~~~~~~~~~~~~~~~~~~~~~
|
|
952 | +GHC offers the flag -fno-code for the purpose of parsing and typechecking a
|
|
953 | +program without generating object files. This is intended to be used by tooling
|
|
954 | +and IDEs to provide quick feedback on any parser or type errors as cheaply as
|
|
955 | +possible.
|
|
956 | + |
|
957 | +When GHC is invoked with -fno-code, no object files or linked output will be
|
|
958 | +generated. As many errors and warnings as possible will be generated, as if
|
|
959 | +-fno-code had not been passed. The session DynFlags will have
|
|
960 | +backend == NoBackend.
|
|
961 | + |
|
962 | +-fwrite-interface
|
|
963 | +~~~~~~~~~~~~~~~~
|
|
964 | +Whether interface files are generated in -fno-code mode is controlled by the
|
|
965 | +-fwrite-interface flag. The -fwrite-interface flag is a no-op if -fno-code is
|
|
966 | +not also passed. Recompilation avoidance requires interface files, so passing
|
|
967 | +-fno-code without -fwrite-interface should be avoided. If -fno-code were
|
|
968 | +re-implemented today, there would be no need for -fwrite-interface as it
|
|
969 | +would considered always on; this behaviour is as it is for backwards compatibility.
|
|
970 | + |
|
971 | +================================================================
|
|
972 | +IN SUMMARY: ALWAYS PASS -fno-code AND -fwrite-interface TOGETHER
|
|
973 | +================================================================
|
|
974 | + |
|
975 | +Template Haskell
|
|
976 | +~~~~~~~~~~~~~~~~
|
|
977 | +A module using Template Haskell may invoke an imported function from inside a
|
|
978 | +splice. This will cause the type-checker to attempt to execute that code, which
|
|
979 | +would fail if no object files had been generated. See #8025. To rectify this,
|
|
980 | +during the downsweep we patch the DynFlags in the ModSummary of any home module
|
|
981 | +that is imported by a module that uses Template Haskell to generate object
|
|
982 | +code.
|
|
983 | + |
|
984 | +The flavour of the generated code depends on whether `-fprefer-byte-code` is enabled
|
|
985 | +or not in the module which needs the code generation. If the module requires byte-code then
|
|
986 | +dependencies will generate byte-code, otherwise they will generate object files.
|
|
987 | +In the case where some modules require byte-code and some object files, both are
|
|
988 | +generated by enabling `-fbyte-code-and-object-code`, the test "fat015" tests these
|
|
989 | +configurations.
|
|
990 | + |
|
991 | +The object files (and interface files if -fwrite-interface is disabled) produced
|
|
992 | +for Template Haskell are written to temporary files.
|
|
993 | + |
|
994 | +Note that since Template Haskell can run arbitrary IO actions, -fno-code mode
|
|
995 | +is no more secure than running without it.
|
|
996 | + |
|
997 | +Potential TODOS:
|
|
998 | +~~~~~
|
|
999 | +* Remove -fwrite-interface and have interface files always written in -fno-code
|
|
1000 | + mode
|
|
1001 | +* Both .o and .dyn_o files are generated for template haskell, but we only need
|
|
1002 | + .dyn_o. Fix it.
|
|
1003 | +* In make mode, a message like
|
|
1004 | + Compiling A (A.hs, /tmp/ghc_123.o)
|
|
1005 | + is shown if downsweep enabled object code generation for A. Perhaps we should
|
|
1006 | + show "nothing" or "temporary object file" instead. Note that one
|
|
1007 | + can currently use -keep-tmp-files and inspect the generated file with the
|
|
1008 | + current behaviour.
|
|
1009 | +* Offer a -no-codedir command line option, and write what were temporary
|
|
1010 | + object files there. This would speed up recompilation.
|
|
1011 | +* Use existing object files (if they are up to date) instead of always
|
|
1012 | + generating temporary ones.
|
|
1013 | +-}
|
|
1014 | + |
|
950 | 1015 | -- | Populate the Downsweep cache with the root modules.
|
951 | 1016 | mkRootMap
|
952 | 1017 | :: [ModuleNodeInfo]
|
... | ... | @@ -1246,70 +1246,6 @@ addSptEntries hsc_env mlinkable = |
1246 | 1246 | , spt <- bc_spt_entries bco
|
1247 | 1247 | ]
|
1248 | 1248 | |
1249 | -{- Note [-fno-code mode]
|
|
1250 | -~~~~~~~~~~~~~~~~~~~~~~~~
|
|
1251 | -GHC offers the flag -fno-code for the purpose of parsing and typechecking a
|
|
1252 | -program without generating object files. This is intended to be used by tooling
|
|
1253 | -and IDEs to provide quick feedback on any parser or type errors as cheaply as
|
|
1254 | -possible.
|
|
1255 | - |
|
1256 | -When GHC is invoked with -fno-code no object files or linked output will be
|
|
1257 | -generated. As many errors and warnings as possible will be generated, as if
|
|
1258 | --fno-code had not been passed. The session DynFlags will have
|
|
1259 | -backend == NoBackend.
|
|
1260 | - |
|
1261 | --fwrite-interface
|
|
1262 | -~~~~~~~~~~~~~~~~
|
|
1263 | -Whether interface files are generated in -fno-code mode is controlled by the
|
|
1264 | --fwrite-interface flag. The -fwrite-interface flag is a no-op if -fno-code is
|
|
1265 | -not also passed. Recompilation avoidance requires interface files, so passing
|
|
1266 | --fno-code without -fwrite-interface should be avoided. If -fno-code were
|
|
1267 | -re-implemented today, -fwrite-interface would be discarded and it would be
|
|
1268 | -considered always on; this behaviour is as it is for backwards compatibility.
|
|
1269 | - |
|
1270 | -================================================================
|
|
1271 | -IN SUMMARY: ALWAYS PASS -fno-code AND -fwrite-interface TOGETHER
|
|
1272 | -================================================================
|
|
1273 | - |
|
1274 | -Template Haskell
|
|
1275 | -~~~~~~~~~~~~~~~~
|
|
1276 | -A module using template haskell may invoke an imported function from inside a
|
|
1277 | -splice. This will cause the type-checker to attempt to execute that code, which
|
|
1278 | -would fail if no object files had been generated. See #8025. To rectify this,
|
|
1279 | -during the downsweep we patch the DynFlags in the ModSummary of any home module
|
|
1280 | -that is imported by a module that uses template haskell, to generate object
|
|
1281 | -code.
|
|
1282 | - |
|
1283 | -The flavour of the generated code depends on whether `-fprefer-byte-code` is enabled
|
|
1284 | -or not in the module which needs the code generation. If the module requires byte-code then
|
|
1285 | -dependencies will generate byte-code, otherwise they will generate object files.
|
|
1286 | -In the case where some modules require byte-code and some object files, both are
|
|
1287 | -generated by enabling `-fbyte-code-and-object-code`, the test "fat015" tests these
|
|
1288 | -configurations.
|
|
1289 | - |
|
1290 | -The object files (and interface files if -fwrite-interface is disabled) produced
|
|
1291 | -for template haskell are written to temporary files.
|
|
1292 | - |
|
1293 | -Note that since template haskell can run arbitrary IO actions, -fno-code mode
|
|
1294 | -is no more secure than running without it.
|
|
1295 | - |
|
1296 | -Potential TODOS:
|
|
1297 | -~~~~~
|
|
1298 | -* Remove -fwrite-interface and have interface files always written in -fno-code
|
|
1299 | - mode
|
|
1300 | -* Both .o and .dyn_o files are generated for template haskell, but we only need
|
|
1301 | - .dyn_o. Fix it.
|
|
1302 | -* In make mode, a message like
|
|
1303 | - Compiling A (A.hs, /tmp/ghc_123.o)
|
|
1304 | - is shown if downsweep enabled object code generation for A. Perhaps we should
|
|
1305 | - show "nothing" or "temporary object file" instead. Note that one
|
|
1306 | - can currently use -keep-tmp-files and inspect the generated file with the
|
|
1307 | - current behaviour.
|
|
1308 | -* Offer a -no-codedir command line option, and write what were temporary
|
|
1309 | - object files there. This would speed up recompilation.
|
|
1310 | -* Use existing object files (if they are up to date) instead of always
|
|
1311 | - generating temporary ones.
|
|
1312 | --}
|
|
1313 | 1249 | |
1314 | 1250 | -- Note [When source is considered modified]
|
1315 | 1251 | -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
1 | +{-# LANGUAGE GADTs #-}
|
|
2 | +module T23298 where
|
|
3 | + |
|
4 | +import Data.Kind (Type)
|
|
5 | + |
|
6 | +type HList :: Type -> Type
|
|
7 | +data HList a where
|
|
8 | + HCons :: HList x -> HList (Maybe x)
|
|
9 | + |
|
10 | +eq :: HList a -> Bool
|
|
11 | +eq x = case x of
|
|
12 | + HCons ms -> True
|
|
13 | + |
|
14 | +go (HCons x) = go x
|
|
15 | + |
|
16 | +{- go :: HList alpha -> beta
|
|
17 | + |
|
18 | +Under HCons
|
|
19 | + [G] alpha ~ Maybe x
|
|
20 | + [W] HList x ~ HList alpha
|
|
21 | +==>
|
|
22 | + [W] x ~ alpha
|
|
23 | +==>
|
|
24 | + [W] x ~ Maybe x
|
|
25 | +-} |
1 | + T23298.hs:14:16: error: [GHC-25897]
|
|
2 | + • Couldn't match type ‘x’ with ‘Maybe x’
|
|
3 | + Expected: HList x -> t
|
|
4 | + Actual: HList a -> t
|
|
5 | + ‘x’ is a rigid type variable bound by
|
|
6 | + a pattern with constructor:
|
|
7 | + HCons :: forall x. HList x -> HList (Maybe x),
|
|
8 | + in an equation for ‘go’
|
|
9 | + at T23298.hs:14:5-11
|
|
10 | + • In the expression: go x
|
|
11 | + In an equation for ‘go’: go (HCons x) = go x
|
|
12 | + • Relevant bindings include x :: HList x (bound at T23298.hs:14:11) |
... | ... | @@ -131,3 +131,4 @@ test('T19847a', normalise_version('base'), compile, ['-ddump-types']) |
131 | 131 | test('T19847b', normal, compile, [''])
|
132 | 132 | test('T23022', normal, compile, ['-dcore-lint'])
|
133 | 133 | test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test?
|
134 | +test('T23298', normal, compile_fail, ['']) |
1 | +{-# LANGUAGE MagicHash #-}
|
|
2 | + |
|
3 | +module T25976 where
|
|
4 | + |
|
5 | +import GHC.PrimOps (tagToEnum#)
|
|
6 | + |
|
7 | +-- Spoiler - it's all dead code since tagToEnum 3# is undefined
|
|
8 | +main = case (tagToEnum# 4# :: Bool) of
|
|
9 | + True -> print "Dead Code"
|
|
10 | + False -> print "Dead Code" |
... | ... | @@ -541,3 +541,5 @@ test('T25883', normal, compile_grep_core, ['']) |
541 | 541 | test('T25883b', normal, compile_grep_core, [''])
|
542 | 542 | test('T25883c', normal, compile_grep_core, [''])
|
543 | 543 | 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 ="'])
|
544 | + |
|
545 | +test('T25976', [grep_errmsg('Dead Code')], compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds']) |