[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Move -fno-code note into Downsweep module

Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 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 - - - - - cd848c75 by Matthew Pickering at 2025-04-23T12:18:00-04:00 ghci: Use loadInterfaceForModule rather than loadSrcInterface in mkTopLevEnv loadSrcInterface takes a user given `ModuleName` and resolves it to the module which needs to be loaded (taking into account module renaming/visibility etc). loadInterfaceForModule takes a specific module and loads it. The modules in `ImpDeclSpec` have already been resolved to the actual module to get the information from during renaming. Therefore we just need to fetch the precise interface from disk (and not attempt to rename it again). Fixes #25951 - - - - - df8442ae by Simon Peyton Jones at 2025-04-23T12:18:01-04:00 Test for #23298 - - - - - 10 changed files: - compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Runtime/Eval.hs - + testsuite/tests/gadt/T23298.hs - + testsuite/tests/gadt/T23298.stderr - testsuite/tests/gadt/all.T - + testsuite/tests/ghci/scripts/GhciPackageRename.hs - + testsuite/tests/ghci/scripts/GhciPackageRename.script - + testsuite/tests/ghci/scripts/GhciPackageRename.stdout - testsuite/tests/ghci/scripts/all.T Changes: ===================================== 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] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -78,7 +78,7 @@ import GHC.Core.Type hiding( typeKind ) import qualified GHC.Core.Type as Type import GHC.Iface.Env ( newInteractiveBinder ) -import GHC.Iface.Load ( loadSrcInterface ) +import GHC.Iface.Load ( loadInterfaceForModule ) import GHC.Tc.Utils.TcType import GHC.Tc.Types.Constraint import GHC.Tc.Types.Origin @@ -843,7 +843,7 @@ mkTopLevEnv hsc_env modl $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv) $ forM imports $ \iface_import -> do let ImpUserSpec spec details = tcIfaceImport iface_import - iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec) + iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec) pure $ case details of ImpUserAll -> importsFromIface hsc_env iface spec Nothing ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns) ===================================== 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/ghci/scripts/GhciPackageRename.hs ===================================== @@ -0,0 +1,4 @@ +module GhciPackageRename where + +foo :: Map k v +foo = empty \ No newline at end of file ===================================== testsuite/tests/ghci/scripts/GhciPackageRename.script ===================================== @@ -0,0 +1,6 @@ +:l GhciPackageRename.hs +-- Test that Data.Map is available as Prelude +:t fromList + +-- Test using a Map function +fromList [(1,"a"), (2,"b")] \ No newline at end of file ===================================== testsuite/tests/ghci/scripts/GhciPackageRename.stdout ===================================== @@ -0,0 +1,3 @@ +fromList + :: ghc-internal:GHC.Internal.Classes.Ord k => [(k, a)] -> Map k a +fromList [(1,"a"),(2,"b")] ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -386,3 +386,9 @@ test('T13869', extra_files(['T13869a.hs', 'T13869b.hs']), ghci_script, ['T13869. test('ListTuplePunsPpr', normal, ghci_script, ['ListTuplePunsPpr.script']) test('ListTuplePunsPprNoAbbrevTuple', [expect_broken(23135), limit_stdout_lines(13)], ghci_script, ['ListTuplePunsPprNoAbbrevTuple.script']) test('T24459', normal, ghci_script, ['T24459.script']) + +# Test package renaming in GHCi session +test('GhciPackageRename', + [extra_hc_opts("-hide-all-packages -package 'containers (Data.Map as Prelude)'")], + ghci_script, + ['GhciPackageRename.script']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e09173636dc453b10cf8949f96cf2b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e09173636dc453b10cf8949f96cf2b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)