[Git][ghc/ghc][master] compiler: Fingerprint -fwrite-if-simplified-core
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Jul 12 15:41:55 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core
We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.
Fixes #24656
- - - - -
5 changed files:
- compiler/GHC/Iface/Recomp/Flags.hs
- + testsuite/tests/driver/recomp24656/A.hs
- + testsuite/tests/driver/recomp24656/Makefile
- + testsuite/tests/driver/recomp24656/all.T
- + testsuite/tests/driver/recomp24656/recomp24656.stdout
Changes:
=====================================
compiler/GHC/Iface/Recomp/Flags.hs
=====================================
@@ -83,7 +83,10 @@ fingerprintDynFlags hsc_env this_mod nameio =
-- Other flags which affect code generation
codegen = map (`gopt` dflags) (EnumSet.toList codeGenFlags)
- flags = ((mainis, safeHs, lang, cpp, js, cmm), (paths, prof, ticky, codegen, debugLevel, callerCcFilters))
+ -- Did we include core for all bindings?
+ fat_iface = gopt Opt_WriteIfSimplifiedCore dflags
+
+ flags = ((mainis, safeHs, lang, cpp, js, cmm), (paths, prof, ticky, codegen, debugLevel, callerCcFilters, fat_iface))
in -- pprTrace "flags" (ppr flags) $
computeFingerprint nameio flags
=====================================
testsuite/tests/driver/recomp24656/A.hs
=====================================
@@ -0,0 +1,4 @@
+module A where
+
+foo :: Int
+foo = 1
=====================================
testsuite/tests/driver/recomp24656/Makefile
=====================================
@@ -0,0 +1,12 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+OBJSUFFIX = .o
+
+recomp24656:
+ $(RM) A.hi A$(OBJSUFFIX)
+ '$(TEST_HC)' $(TEST_HC_OPTS) A.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) -fwrite-if-simplified-core A.hs
+ '$(TEST_HC)' $(TEST_HC_OPTS) --show-iface A.hi | grep -A6 "extra decls"
+
=====================================
testsuite/tests/driver/recomp24656/all.T
=====================================
@@ -0,0 +1,2 @@
+test('recomp24656', [extra_files(['A.hs'])],
+ makefile_test, [])
=====================================
testsuite/tests/driver/recomp24656/recomp24656.stdout
=====================================
@@ -0,0 +1,9 @@
+[1 of 1] Compiling A ( A.hs, A.o )
+[1 of 1] Compiling A ( A.hs, A.o ) [Flags changed]
+extra decls:
+ $trModule = GHC.Types.Module $trModule2 $trModule4
+ $trModule1 = "main"#
+ $trModule2 = GHC.Types.TrNameS $trModule1
+ $trModule3 = "A"#
+ $trModule4 = GHC.Types.TrNameS $trModule3
+ foo = GHC.Types.I# 1#
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dddc9dff0547733a10e7f505612ab9df3a7c21b6
--
This project does not include diff previews in email notifications.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dddc9dff0547733a10e7f505612ab9df3a7c21b6
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240712/30d595a9/attachment-0001.html>
More information about the ghc-commits
mailing list