
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Refactor handling of imported COMPLETE pragmas
by Marge Bot (@marge-bot) 28 May '25
by Marge Bot (@marge-bot) 28 May '25
28 May '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b08c08ae by soulomoon at 2025-05-28T01:57:23+08:00
Refactor handling of imported COMPLETE pragmas
from the HPT
Previously, we imported COMPLETE pragmas from all modules in the Home
Package Table (HPT) during type checking. However, since !13675, there
may be non-below modules in the HPT from the dependency tree that we do
not want to import COMPLETE pragmas from. This refactor changes the way
we handle COMPLETE pragmas from the HPT to only import them from modules
that are "below" the current module in the HPT.
- Add hugCompleteSigsBelow to filter COMPLETE pragmas from "below"
modules in the HPT, mirroring hugRulesBelow.
- Move responsibility for calling hugCompleteSigsBelow to tcRnImports,
storing the result in the new tcg_complete_match_env field of TcGblEnv.
- Update getCompleteMatchesTcM to use tcg_complete_match_env.
This refactor only affects how COMPLETE pragmas are imported from the
HPT, imports from external packages are unchanged.
- - - - -
fef1a930 by Hécate Kleidukos at 2025-05-28T14:48:20-04:00
Expose all of Backtraces' internals for ghc-internal
Closes #26049
- - - - -
8 changed files:
- compiler/GHC/Driver/Env.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Utils/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
Changes:
=====================================
compiler/GHC/Driver/Env.hs
=====================================
@@ -33,6 +33,7 @@ module GHC.Driver.Env
, hugRulesBelow
, hugInstancesBelow
, hugAnnsBelow
+ , hugCompleteSigsBelow
-- * Legacy API
, hscUpdateHPT
@@ -79,6 +80,7 @@ import GHC.Utils.Logger
import GHC.Core.Rules
import GHC.Types.Annotations
+import GHC.Types.CompleteMatch
import GHC.Core.InstEnv
import GHC.Core.FamInstEnv
import GHC.Builtin.Names
@@ -228,6 +230,12 @@ hugAnnsBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO AnnEnv
hugAnnsBelow hsc uid mn = foldr (flip extendAnnEnvList) emptyAnnEnv <$>
hugSomeThingsBelowUs (md_anns . hm_details) False hsc uid mn
+-- | Find all COMPLETE pragmas in modules that are in the transitive closure of the
+-- given module.
+hugCompleteSigsBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO CompleteMatches
+hugCompleteSigsBelow hsc uid mn = foldr (++) [] <$>
+ hugSomeThingsBelowUs (md_complete_matches . hm_details) False hsc uid mn
+
-- | Find instances visible from the given set of imports
hugInstancesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO (InstEnv, [FamInst])
hugInstancesBelow hsc_env uid mnwib = do
=====================================
compiler/GHC/HsToCore/Monad.hs
=====================================
@@ -266,9 +266,12 @@ mkDsEnvsFromTcGbl hsc_env msg_var tcg_env
ptc = initPromotionTickContext (hsc_dflags hsc_env)
-- re-use existing next_wrapper_num to ensure uniqueness
next_wrapper_num_var = tcg_next_wrapper_num tcg_env
+ tcg_comp_env = tcg_complete_match_env tcg_env
; ds_complete_matches <-
liftIO $ unsafeInterleaveIO $
+ -- Note [Lazily loading COMPLETE pragmas]
+ -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- This call to 'unsafeInterleaveIO' ensures we only do this work
-- when we need to look at the COMPLETE pragmas, avoiding doing work
-- when we don't need them.
@@ -276,7 +279,7 @@ mkDsEnvsFromTcGbl hsc_env msg_var tcg_env
-- Relevant test case: MultiLayerModulesTH_Make, which regresses
-- in allocations by ~5% if we don't do this.
traverse (lookupCompleteMatch type_env hsc_env) =<<
- localAndImportedCompleteMatches (tcg_complete_matches tcg_env) (hsc_unit_env hsc_env) eps
+ localAndImportedCompleteMatches tcg_comp_env eps
; return $ mkDsEnvs unit_env this_mod rdr_env type_env fam_inst_env ptc
msg_var cc_st_var next_wrapper_num_var ds_complete_matches
}
@@ -334,7 +337,7 @@ initDsWithModGuts hsc_env (ModGuts { mg_module = this_mod, mg_binds = binds
bindsToIds (Rec binds) = map fst binds
ids = concatMap bindsToIds binds
; ds_complete_matches <- traverse (lookupCompleteMatch type_env hsc_env) =<<
- localAndImportedCompleteMatches local_complete_matches (hsc_unit_env hsc_env) eps
+ localAndImportedCompleteMatches local_complete_matches eps
; let
envs = mkDsEnvs unit_env this_mod rdr_env type_env
fam_inst_env ptc msg_var cc_st_var
=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -338,7 +338,8 @@ rnValBindsRHS ctxt (ValBinds _ mbinds sigs)
-- Update the TcGblEnv with renamed COMPLETE pragmas from the current
-- module, for pattern irrefutability checking in do notation.
; let localCompletePrags = localCompletePragmas sigs'
- ; updGblEnv (\gblEnv -> gblEnv { tcg_complete_matches = tcg_complete_matches gblEnv ++ localCompletePrags}) $
+ ; updGblEnv (\gblEnv -> gblEnv { tcg_complete_matches = tcg_complete_matches gblEnv ++ localCompletePrags
+ , tcg_complete_match_env = tcg_complete_match_env gblEnv ++ localCompletePrags }) $
do { binds_w_dus <- mapM (rnLBind (mkScopedTvFn sigs')) mbinds
; let !(anal_binds, anal_dus) = depAnalBinds binds_w_dus
@@ -956,7 +957,8 @@ rnMethodBinds is_cls_decl cls ktv_names binds sigs
-- Update the TcGblEnv with renamed COMPLETE pragmas from the current
-- module, for pattern irrefutability checking in do notation.
- ; updGblEnv (\gblEnv -> gblEnv { tcg_complete_matches = tcg_complete_matches gblEnv ++ localCompletePrags}) $
+ ; updGblEnv (\gblEnv -> gblEnv { tcg_complete_matches = tcg_complete_matches gblEnv ++ localCompletePrags
+ , tcg_complete_match_env = tcg_complete_match_env gblEnv ++ localCompletePrags}) $
do {
-- Rename the bindings RHSs. Again there's an issue about whether the
-- type variables from the class/instance head are in scope.
=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -222,7 +222,8 @@ rnSrcDecls group@(HsGroup { hs_valds = val_decls,
last_tcg_env0 <- getGblEnv ;
let { last_tcg_env =
last_tcg_env0
- { tcg_complete_matches = tcg_complete_matches last_tcg_env0 ++ localCompletePragmas sigs' }
+ { tcg_complete_matches = tcg_complete_matches last_tcg_env0 ++ localCompletePragmas sigs'
+ , tcg_complete_match_env = tcg_complete_match_env last_tcg_env0 ++ localCompletePragmas sigs'}
} ;
-- (I) Compute the results and return
let {rn_group = HsGroup { hs_ext = noExtField,
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -51,6 +51,7 @@ import GHC.Driver.Env
import GHC.Driver.Plugins
import GHC.Driver.DynFlags
import GHC.Driver.Config.Diagnostic
+import GHC.IO.Unsafe ( unsafeInterleaveIO )
import GHC.Tc.Errors.Hole.Plugin ( HoleFitPluginR (..) )
import GHC.Tc.Errors.Types
@@ -483,6 +484,12 @@ tcRnImports hsc_env import_decls
; (home_insts, home_fam_insts) <- liftIO $
hugInstancesBelow hsc_env unitId mnwib
+ -- We use 'unsafeInterleaveIO' to avoid redundant memory allocations
+ -- See Note [Lazily loading COMPLETE pragmas] from GHC.HsToCore.Monad
+ -- and see https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14274#note_620545
+ ; completeSigsBelow <- liftIO $ unsafeInterleaveIO $
+ hugCompleteSigsBelow hsc_env unitId mnwib
+
-- Record boot-file info in the EPS, so that it's
-- visible to loadHiBootInterface in tcRnSrcDecls,
-- and any other incrementally-performed imports
@@ -495,6 +502,8 @@ tcRnImports hsc_env import_decls
gbl {
tcg_rdr_env = tcg_rdr_env gbl `plusGlobalRdrEnv` rdr_env,
tcg_imports = tcg_imports gbl `plusImportAvails` imports,
+ tcg_complete_match_env = tcg_complete_match_env gbl ++
+ completeSigsBelow,
tcg_import_decls = imp_user_spec,
tcg_rn_imports = rn_imports,
tcg_default = foldMap subsume tc_defaults,
=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -507,6 +507,9 @@ data TcGblEnv
tcg_fam_inst_env :: !FamInstEnv, -- ^ Ditto for family instances
-- NB. BangPattern is to fix a leak, see #15111
tcg_ann_env :: AnnEnv, -- ^ And for annotations
+ tcg_complete_match_env :: CompleteMatches,
+ -- ^ The complete matches for all /home-package/ modules;
+ -- Includes the complete matches in tcg_complete_matches
-- Now a bunch of things about this module that are simply
-- accumulated, but never consulted until the end.
@@ -689,9 +692,10 @@ data TcGblEnv
-- ^ Wanted constraints of static forms.
-- See Note [Constraints in static forms].
tcg_complete_matches :: !CompleteMatches,
+ -- ^ Complete matches defined in this module.
- -- ^ Tracking indices for cost centre annotations
tcg_cc_st :: TcRef CostCentreState,
+ -- ^ Tracking indices for cost centre annotations
tcg_next_wrapper_num :: TcRef (ModuleEnv Int)
-- ^ See Note [Generating fresh names for FFI wrappers]
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -328,6 +328,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
tcg_inst_env = emptyInstEnv,
tcg_fam_inst_env = emptyFamInstEnv,
tcg_ann_env = emptyAnnEnv,
+ tcg_complete_match_env = [],
tcg_th_used = th_var,
tcg_th_needed_deps = th_needed_deps_var,
tcg_exports = [],
@@ -2425,15 +2426,14 @@ liftZonkM (ZonkM f) =
getCompleteMatchesTcM :: TcM CompleteMatches
getCompleteMatchesTcM
= do { hsc_env <- getTopEnv
- ; tcg_env <- getGblEnv
; eps <- liftIO $ hscEPS hsc_env
- ; liftIO $ localAndImportedCompleteMatches (tcg_complete_matches tcg_env) (hsc_unit_env hsc_env) eps
+ ; tcg_env <- getGblEnv
+ ; let tcg_comps = tcg_complete_match_env tcg_env
+ ; liftIO $ localAndImportedCompleteMatches tcg_comps eps
}
-localAndImportedCompleteMatches :: CompleteMatches -> UnitEnv -> ExternalPackageState -> IO CompleteMatches
-localAndImportedCompleteMatches tcg_comps unit_env eps = do
- hugCSigs <- hugCompleteSigs unit_env
+localAndImportedCompleteMatches :: CompleteMatches -> ExternalPackageState -> IO CompleteMatches
+localAndImportedCompleteMatches tcg_comps eps = do
return $
- tcg_comps -- from the current module
- ++ hugCSigs -- from the home package
- ++ eps_complete_matches eps -- from imports
+ tcg_comps -- from the current modulea and from the home package
+ ++ eps_complete_matches eps -- from external packages
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -3,16 +3,7 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
-module GHC.Internal.Exception.Backtrace
- ( -- * Backtrace mechanisms
- BacktraceMechanism(..)
- , getBacktraceMechanismState
- , setBacktraceMechanismState
- -- * Collecting backtraces
- , Backtraces(..)
- , displayBacktraces
- , collectBacktraces
- ) where
+module GHC.Internal.Exception.Backtrace where
import GHC.Internal.Base
import GHC.Internal.Data.OldList
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2191cb339d30232d4728de53452bd2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2191cb339d30232d4728de53452bd2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Remove emptyModBreaks
by Marge Bot (@marge-bot) 28 May '25
by Marge Bot (@marge-bot) 28 May '25
28 May '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
1fc75735 by fendor at 2025-05-28T12:31:46+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
646aa874 by fendor at 2025-05-28T12:31:46+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
2191cb33 by Hécate Kleidukos at 2025-05-28T09:26:59-04:00
Expose all of Backtraces' internals for ghc-internal
Closes #26049
- - - - -
142 changed files:
- compiler/GHC.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- testsuite/driver/testlib.py
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/quasiquotation/T7918.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f422b3c7fe7dd68c62b2d692509e9b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f422b3c7fe7dd68c62b2d692509e9b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/ghci-multiple-home-units] 2 commits: Make GHCi commands compatible with multiple home units
by Hannes Siebenhandl (@fendor) 28 May '25
by Hannes Siebenhandl (@fendor) 28 May '25
28 May '25
Hannes Siebenhandl pushed to branch wip/fendor/ghci-multiple-home-units at Glasgow Haskell Compiler / GHC
Commits:
1fc75735 by fendor at 2025-05-28T12:31:46+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
646aa874 by fendor at 2025-05-28T12:31:46+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
131 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- testsuite/driver/testlib.py
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/quasiquotation/T7918.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f04951f931ba257116d68ba4b3d48d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f04951f931ba257116d68ba4b3d48d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/ghci-multiple-home-units] 2 commits: Make GHCi commands compatible with multiple home units
by Hannes Siebenhandl (@fendor) 28 May '25
by Hannes Siebenhandl (@fendor) 28 May '25
28 May '25
Hannes Siebenhandl pushed to branch wip/fendor/ghci-multiple-home-units at Glasgow Haskell Compiler / GHC
Commits:
83ee6e79 by fendor at 2025-05-28T12:28:34+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
f04951f9 by fendor at 2025-05-28T12:28:34+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
131 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- testsuite/driver/testlib.py
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/quasiquotation/T7918.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c85f3af2c2fc3fe537ceb3a43056f3…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c85f3af2c2fc3fe537ceb3a43056f3…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/ghci-multiple-home-units] 22 commits: Interpreter: Add limited support for direct primop evaluation.
by Hannes Siebenhandl (@fendor) 28 May '25
by Hannes Siebenhandl (@fendor) 28 May '25
28 May '25
Hannes Siebenhandl pushed to branch wip/fendor/ghci-multiple-home-units at Glasgow Haskell Compiler / GHC
Commits:
202b201c by Andreas Klebinger at 2025-05-21T10:16:14-04:00
Interpreter: Add limited support for direct primop evaluation.
This commit adds support for a number of primops directly
to the interpreter. This avoids the indirection of going
through the primop wrapper for those primops speeding interpretation
of optimized code up massively.
Code involving IntSet runs about 25% faster with optimized core and these
changes. For core without breakpoints it's even more pronouced and I
saw reductions in runtime by up to 50%.
Running GHC itself in the interpreter was sped up by ~15% through this
change.
Additionally this comment does a few other related changes:
testsuite:
* Run foundation test in ghci and ghci-opt ways to test these
primops.
* Vastly expand the foundation test to cover all basic primops
by comparing result with the result of calling the wrapper.
Interpreter:
* When pushing arguments for interpreted primops extend each argument to
at least word with when pushing. This avoids some issues with big
endian. We can revisit this if it causes performance issues.
* Restructure the stack chunk check logic. There are now macros for
read accesses which might cross stack chunk boundries and macros which
omit the checks which are used when we statically know we access an
address in the current stack chunk.
- - - - -
67a177b4 by sheaf at 2025-05-21T10:17:04-04:00
QuickLook: do a shape test before unifying
This commit ensures we do a shape test before unifying. This ensures
we don't try to unify a TyVarTv with a non-tyvar, e.g.
alpha[tyv] := Int
On the way, we refactor simpleUnifyCheck:
1. Move the checkTopShape check into simpleUnifyCheck
2. Refactors simpleUnifyCheck to return a value of the new type
SimpleUnifyResult type. Now, simpleUnifyCheck returns "can unify",
"cannot unify" or "dunno" (with "cannot unify" being the new result
it can return). Now:
- touchabilityTest is included; it it fails we return "cannot unify"
- checkTopShape now returns "cannot unify" instead of "dunno" upon failure
3. Move the call to simpleUnifyCheck out of checkTouchableTyVarEq.
After that, checkTouchableTyVarEq becames a simple call to
checkTyEqRhs, so we inline it.
This allows the logic in canEqCanLHSFinish_try_unification to be simplified.
In particular, we now avoid calling 'checkTopShape' twice.
Two further changes suggested by Simon were also implemented:
- In canEqCanLHSFinish, if checkTyEqRhs returns PuFail with
'do_not_prevent_rewriting', we now **continue with this constraint**.
This allows us to use the constraint for rewriting.
- checkTyEqRhs now has a top-level check to avoid flattening a tyfam app
in a top-level equality of the form alpha ~ F tys, as this is
going around in circles. This simplifies the implementation without
any change in behaviour.
Fixes #25950
Fixes #26030
- - - - -
4020972c by sheaf at 2025-05-21T10:17:04-04:00
FixedRuntimeRepError: omit unhelpful explanation
This commit tweaks the FixedRuntimeRepError case of pprTcSolverReportMsg,
to avoid including an explanation which refers to a type variable that
appears nowhere else.
For example, the old error message could look like the following:
The pattern binding does not have a fixed runtime representation.
Its type is:
T :: TYPE R
Cannot unify ‘R’ with the type variable ‘c0’
because the former is not a concrete ‘RuntimeRep’.
With this commit, we now omit the last two lines, because the concrete
type variable (here 'c0') does not appear in the type displayed to the
user (here 'T :: TYPE R').
- - - - -
6d058a69 by Andrea Bedini at 2025-05-21T16:00:51-04:00
Don't fail when ghcversion.h can't be found (#26018)
If ghcversion.h can't be found, don't try to include it. This happens
when there is no rts package in the package db and when -ghcversion-file
argument isn't passed.
Co-authored-by: Syvlain Henry <sylvain(a)haskus.fr>
- - - - -
b1212fbf by Vladislav Zavialov at 2025-05-21T16:01:33-04:00
Implement -Wpattern-namespace-specifier (#25900)
In accordance with GHC Proposal #581 "Namespace-specified imports",
section 2.3 "Deprecate use of pattern in import/export lists", the
`pattern` namespace specifier is now deprecated.
Test cases: T25900 T25900_noext
- - - - -
e650ec3e by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Forward port changelog language from 9.12
- - - - -
94cd9ca4 by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Fix RestructuredText-isms in changelog
- - - - -
7722232c by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Note strictness changes made in 4.16.0.0
Addresses #25886.
- - - - -
3f4b823c by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Factor out ProddableBlocks machinery
- - - - -
6e23fef2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Improve efficiency of proddable blocks structure
Previously the linker's "proddable blocks" check relied on a simple
linked list of spans. This resulted in extremely poor complexity while
linking objects with lots of small sections (e.g. objects built with
split sections).
Rework the mechanism to instead use a simple interval set implemented
via binary search.
Fixes #26009.
- - - - -
ea74860c by Ben Gamari at 2025-05-23T03:43:28-04:00
testsuite: Add simple functional test for ProddableBlockSet
- - - - -
74c4db46 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Drop check for LOAD_LIBRARY_SEARCH_*_DIRS
The `LOAD_LIBRARY_SEARCH_USER_DIRS` and
`LOAD_LIBRARY_SEARCH_DEFAULT_DIRS` were introduced in Windows Vista and
have been available every since. As we no longer support Windows XP we
can drop this check.
Addresses #26009.
- - - - -
972d81d6 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Clean up code style
- - - - -
8a1073a5 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/Hash: Factor out hashBuffer
This is a useful helper which can be used for non-strings as well.
- - - - -
44f509f2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Fix incorrect use of break in nested for
Previously the happy path of PEi386 used `break` in a double-`for` loop
resulting in redundant calls to `LoadLibraryEx`.
Fixes #26052.
- - - - -
bfb12783 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts: Correctly mark const arguments
- - - - -
08469ff8 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Don't repeatedly load DLLs
Previously every DLL-imported symbol would result in a call to
`LoadLibraryEx`. This ended up constituting over 40% of the runtime of
`ghc --interactive -e 42` on Windows. Avoid this by maintaining a
hash-set of loaded DLL names, skipping the call if we have already
loaded the requested DLL.
Addresses #26009.
- - - - -
823d1ccf by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Expand comment describing ProddableBlockSet
- - - - -
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
d551aa1e by fendor at 2025-05-28T10:44:52+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
c85f3af2 by fendor at 2025-05-28T10:49:21+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
245 changed files:
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- hadrian/src/Flavour.hs
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs
- libraries/ghc-internal/src/GHC/Internal/TypeLits.hs
- libraries/ghc-internal/src/GHC/Internal/TypeNats.hs
- rts/Disassembler.c
- rts/Hash.c
- rts/Hash.h
- rts/Interpreter.c
- rts/Linker.c
- rts/LinkerInternals.h
- rts/PathUtils.c
- rts/PathUtils.h
- rts/include/rts/Bytecodes.h
- rts/linker/Elf.c
- rts/linker/MachO.c
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- + rts/linker/ProddableBlocks.c
- + rts/linker/ProddableBlocks.h
- rts/rts.cabal
- testsuite/driver/testlib.py
- testsuite/tests/callarity/unittest/CallArity1.hs
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/all.T
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- + testsuite/tests/ghci/all.T
- + testsuite/tests/ghci/ghci-mem-primops.hs
- + testsuite/tests/ghci/ghci-mem-primops.script
- + testsuite/tests/ghci/ghci-mem-primops.stdout
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- + testsuite/tests/parser/should_compile/T25900.hs
- + testsuite/tests/parser/should_compile/T25900.stderr
- + testsuite/tests/parser/should_compile/T25900_noext.hs
- + testsuite/tests/parser/should_compile/T25900_noext.stderr
- testsuite/tests/parser/should_compile/all.T
- testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs
- testsuite/tests/patsyn/should_compile/T11959.hs
- testsuite/tests/patsyn/should_compile/T11959.stderr
- testsuite/tests/patsyn/should_compile/T11959Lib.hs
- testsuite/tests/patsyn/should_compile/T13350/boolean/Boolean.hs
- testsuite/tests/patsyn/should_compile/T22521.hs
- testsuite/tests/patsyn/should_compile/T9857.hs
- testsuite/tests/patsyn/should_compile/export.hs
- testsuite/tests/pmcheck/complete_sigs/T25115a.hs
- testsuite/tests/pmcheck/should_compile/T11822.hs
- testsuite/tests/polykinds/T14270.hs
- testsuite/tests/quasiquotation/T7918.hs
- testsuite/tests/rename/should_compile/T12548.hs
- testsuite/tests/rename/should_fail/T25056.stderr
- testsuite/tests/rename/should_fail/T25056a.hs
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T23903.stderr
- + testsuite/tests/rts/TestProddableBlockSet.c
- testsuite/tests/rts/all.T
- testsuite/tests/simplCore/should_compile/T15186.hs
- testsuite/tests/simplCore/should_compile/T15186A.hs
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- + testsuite/tests/typecheck/should_compile/T26030.hs
- testsuite/tests/typecheck/should_compile/TypeRepCon.hs
- testsuite/tests/typecheck/should_compile/all.T
- + testsuite/tests/typecheck/should_fail/T25950.hs
- + testsuite/tests/typecheck/should_fail/T25950.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/warnings/should_compile/DataToTagWarnings.hs
- testsuite/tests/warnings/should_compile/T14794a.hs
- testsuite/tests/warnings/should_compile/T14794a.stderr
- testsuite/tests/warnings/should_compile/T14794b.hs
- testsuite/tests/warnings/should_compile/T14794b.stderr
- testsuite/tests/warnings/should_compile/T14794c.hs
- testsuite/tests/warnings/should_compile/T14794c.stderr
- testsuite/tests/warnings/should_compile/T14794d.hs
- testsuite/tests/warnings/should_compile/T14794d.stderr
- testsuite/tests/warnings/should_compile/T14794e.hs
- testsuite/tests/warnings/should_compile/T14794e.stderr
- testsuite/tests/warnings/should_compile/T14794f.hs
- testsuite/tests/warnings/should_compile/T14794f.stderr
- testsuite/tests/wcompat-warnings/Template.hs
- + testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1feabf08cafcd5b77985e1b57f7b2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1feabf08cafcd5b77985e1b57f7b2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/romes/step-out] More fixes and improvements; it now works but behaviour is not finished
by Rodrigo Mesquita (@alt-romes) 27 May '25
by Rodrigo Mesquita (@alt-romes) 27 May '25
27 May '25
Rodrigo Mesquita pushed to branch wip/romes/step-out at Glasgow Haskell Compiler / GHC
Commits:
f7d2b30a by Rodrigo Mesquita at 2025-05-27T17:22:35+01:00
More fixes and improvements; it now works but behaviour is not finished
- - - - -
8 changed files:
- compiler/GHC/Driver/Config.hs
- compiler/GHC/Runtime/Eval/Types.hs
- ghc/GHCi/UI.hs
- libraries/ghci/GHCi/Run.hs
- rts/Debugger.cmm
- rts/Interpreter.c
- rts/StgMiscClosures.cmm
- utils/deriveConstants/Main.hs
Changes:
=====================================
compiler/GHC/Driver/Config.hs
=====================================
@@ -33,7 +33,7 @@ initSimpleOpts dflags = SimpleOpts
data EvalStep
-- | ... at every breakpoint tick
= EvalStepSingle
- -- | ... after every return stmt
+ -- | ... after any return stmt
| EvalStepOut
-- | ... only on explicit breakpoints
| EvalStepNone
=====================================
compiler/GHC/Runtime/Eval/Types.hs
=====================================
@@ -47,7 +47,7 @@ data SingleStep
-- | :step [expr]
| SingleStep
- -- | :stepout [expr]
+ -- | :stepout
| StepOut
-- | :steplocal [expr]
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -247,7 +247,7 @@ ghciCommands = map mkCmd [
("sprint", keepGoing sprintCmd, completeExpression),
("step", keepGoing stepCmd, completeIdentifier),
("steplocal", keepGoing stepLocalCmd, completeIdentifier),
- ("stepout", keepGoing stepOutCmd, completeIdentifier),
+ ("stepout", keepGoing stepOutCmd, noCompletion),
("stepmodule",keepGoing stepModuleCmd, completeIdentifier),
("type", keepGoingMulti' typeOfExpr, completeExpression),
("trace", keepGoing traceCmd, completeExpression),
@@ -3796,10 +3796,7 @@ stepCmd arg = withSandboxOnly ":step" $ step arg
step expression = runStmt expression GHC.SingleStep >> return ()
stepOutCmd :: GhciMonad m => String -> m ()
-stepOutCmd arg = withSandboxOnly ":stepout" $ step arg
- where
- step [] = doContinue GHC.StepOut
- step expression = stepCmd expression
+stepOutCmd _ = withSandboxOnly ":stepout" $ doContinue GHC.StepOut
stepLocalCmd :: GhciMonad m => String -> m ()
stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -202,7 +202,7 @@ doSeq ref = do
resumeSeq :: RemoteRef (ResumeContext ()) -> IO (EvalStatus ())
resumeSeq hvref = do
ResumeContext{..} <- localRef hvref
- withBreakAction evalOptsSeq resumeBreakMVar resumeStatusMVar $
+ withBreakAction evalOptsSeq resumeBreakMVar resumeStatusMVar (Just resumeThreadId) $
mask_ $ do
putMVar resumeBreakMVar () -- this awakens the stopped thread...
redirectInterrupts resumeThreadId $ takeMVar resumeStatusMVar
@@ -231,7 +231,7 @@ sandboxIO opts io = do
-- We are running in uninterruptibleMask
breakMVar <- newEmptyMVar
statusMVar <- newEmptyMVar
- withBreakAction opts breakMVar statusMVar $ do
+ withBreakAction opts breakMVar statusMVar Nothing $ do
let runIt = measureAlloc $ tryEval $ rethrow opts $ clearCCS io
if useSandboxThread opts
then do
@@ -326,8 +326,8 @@ tryEval io = do
-- resets everything when the computation has stopped running. This
-- is a not-very-good way to ensure that only the interactive
-- evaluation should generate breakpoints.
-withBreakAction :: EvalOpts -> MVar () -> MVar (EvalStatus b) -> IO a -> IO a
-withBreakAction opts breakMVar statusMVar act
+withBreakAction :: EvalOpts -> MVar () -> MVar (EvalStatus b) -> Maybe ThreadId {-^ If resuming, the current threadId -} -> IO a -> IO a
+withBreakAction opts breakMVar statusMVar mtid act
= bracket setBreakAction resetBreakAction (\_ -> act)
where
setBreakAction = do
@@ -336,8 +336,10 @@ withBreakAction opts breakMVar statusMVar act
when (breakOnException opts) $ poke exceptionFlag 1
when (singleStep opts) rts_enableStopNextBreakpointAll
when (stepOut opts) $ do
- ThreadId tid <- myThreadId
- rts_enableStopAfterReturn tid
+ case mtid of
+ Nothing -> rts_enableStopNextBreakpointAll -- just enable single-step when no thread is stopped
+ Just (ThreadId tid) -> do
+ rts_enableStopAfterReturn tid
return stablePtr
-- Breaking on exceptions is not enabled by default, since it
-- might be a bit surprising. The exception flag is turned off
@@ -369,10 +371,9 @@ withBreakAction opts breakMVar statusMVar act
poke breakPointIOAction noBreakStablePtr
poke exceptionFlag 0
rts_disableStopNextBreakpointAll
-
- ThreadId tid <- myThreadId
- rts_disableStopAfterReturn tid
-
+ case mtid of
+ Just (ThreadId tid) -> rts_disableStopAfterReturn tid
+ _ -> pure ()
freeStablePtr stablePtr
resumeStmt
@@ -380,7 +381,7 @@ resumeStmt
-> IO (EvalStatus [HValueRef])
resumeStmt opts hvref = do
ResumeContext{..} <- localRef hvref
- withBreakAction opts resumeBreakMVar resumeStatusMVar $
+ withBreakAction opts resumeBreakMVar resumeStatusMVar (Just resumeThreadId) $
mask_ $ do
putMVar resumeBreakMVar () -- this awakens the stopped thread...
redirectInterrupts resumeThreadId $ takeMVar resumeStatusMVar
=====================================
rts/Debugger.cmm
=====================================
@@ -29,8 +29,8 @@ import CLOSURE stg_stop_after_ret_frame_info;
*
* See Note [Debugger: Step-out] for details.
*/
-INFO_TABLE_RET (stg_stop_after_ret_frame, RET_SMALL)
- return (/* no return values */)
+INFO_TABLE_RET (stg_stop_after_ret_frame, RET_SMALL, W_ info_ptr)
+ /* no args => explicit stack */
{
/* We've entered a stg_stop_after_ret_frame, thus we want to stop at the next
@@ -40,7 +40,12 @@ INFO_TABLE_RET (stg_stop_after_ret_frame, RET_SMALL)
StgTSO_flags(CurrentTSO) =
%lobits32( TO_W_(StgTSO_flags(CurrentTSO)) | TSO_STOP_NEXT_BREAKPOINT );
-
/* After enabling the single step mode, execution is resumed by returning
- * to the frame this one intercepted. */
+ * to the frame this one intercepted.
+ *
+ * Note: Arguments passed to the frame we intercepted must be propagated,
+ * and the floating point registers untouched! See Note [Frames intercepting frames].
+ */
+ Sp = Sp + SIZEOF_StgStopAfterRetFrame;
+ jump %ENTRY_CODE(Sp(0)) GP_ARG_REGS; // NB. all GP arg regs live!
}
=====================================
rts/Interpreter.c
=====================================
@@ -562,7 +562,7 @@ interpretBCO (Capability* cap)
if (cap->r.rCurrentTSO->flags & TSO_STOP_AFTER_RETURN) {
StgPtr frame;
- frame = cap->r.rCurrentTSO->stackobj->sp;
+ frame = Sp;
// Insert the stg_stop_after_ret_frame after the first frame that is NOT a
// case continuation BCO.
@@ -573,18 +573,23 @@ interpretBCO (Capability* cap)
while (*frame == (W_)&stg_CASE_CONT_BCO_info) {
frame += stack_frame_sizeW((StgClosure *)frame);
}
- // New frame goes right after the first non-case-cont frame
+ // New frame goes /right after the first/ non-case-cont frame
frame += stack_frame_sizeW((StgClosure *)frame);
// TODO: Handle stack bottom edge case!? if frame == STACK BOTTOM...
// Make space for the new frame
+ memmove((W_*)Sp - sizeofW(StgStopAfterRetFrame), Sp, (uint8_t*)frame - (uint8_t*)Sp);
Sp_subW(sizeofW(StgStopAfterRetFrame));
- memmove(frame-sizeof(StgStopAfterRetFrame), frame, (uint8_t*)cap->r.rCurrentTSO->stackobj->sp - (uint8_t*)frame);
+
+ // Point to newly opened space
+ frame -= sizeofW(StgStopAfterRetFrame);
// Then write it.
((StgStopAfterRetFrame*)frame)->header.info = &stg_stop_after_ret_frame_info;
+ // TODO: Write profiling info if needed
+
// Frame was pushed, mark as done to not do it again
cap->r.rCurrentTSO->flags &= ~TSO_STOP_AFTER_RETURN;
}
@@ -640,7 +645,6 @@ interpretBCO (Capability* cap)
//
// [1] An StgBCO's info table pointer may also be stg_CASE_CONT_BCO_info.
// See Note [Case continuation BCOs].
- //
else if (SpW(0) == (W_)&stg_apply_interp_info) {
obj = UNTAG_CLOSURE((StgClosure *)ReadSpW(1));
Sp_addW(2);
=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -53,21 +53,12 @@ INFO_TABLE_RET (stg_orig_thunk_info_frame, RET_SMALL,
{
/*
-
!!!!!!!!!!!!!!!!!
!!! IMPORTANT !!!
!!!!!!!!!!!!!!!!!
The body of this function MUST NOT use any floating-point
- or vector registers. DO NOT add any e.g. debug printing logic that
- has any chance whatsoever of using floating-point or vector registers.
- If you DO want to edit the function in such a way that it may use
- vector registers, you will need to define multiple different copies
- of this function, as we do e.g. for stg_stack_underflow_frame
- (see Jumps.h).
-
- See Note [realArgRegsCover] in GHC.Cmm.CallConv for more details.
-
+ or vector registers. See Note [Frames intercepting frames].
*/
unwind Sp = W_[Sp + SIZEOF_StgOrigThunkInfoFrame];
@@ -75,6 +66,30 @@ INFO_TABLE_RET (stg_orig_thunk_info_frame, RET_SMALL,
jump %ENTRY_CODE(Sp(0)) GP_ARG_REGS; // NB. all GP arg regs live!
}
+/*
+Note [Frames intercepting frames]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+A frame which "intercepts" the following frame (to do additional work or
+manipulate the stack, such as `stg_orig_thunk_info_frame` or
+`stg_stop_after_ret_frame`) must take care to passthrough all the registers and
+arguments when it returns to the next frame. This is done by jumping with
+GP_ARG_REGS as in:
+
+ jump %ENTRY_CODE(Sp(0)) GP_ARG_REGS; // NB. all GP arg regs live!
+
+However, special care must be taken when these arguments are propagated:
+
+The body of such a function MUST NOT use any floating-point
+or vector registers. DO NOT add any e.g. debug printing logic that
+has any chance whatsoever of using floating-point or vector registers.
+If you DO want to edit the function in such a way that it may use
+vector registers, you will need to define multiple different copies
+of the function, as we do e.g. for stg_stack_underflow_frame
+(see Jumps.h).
+
+See Note [realArgRegsCover] in GHC.Cmm.CallConv for more details.
+*/
+
/* ----------------------------------------------------------------------------
Restore a saved cost centre
------------------------------------------------------------------------- */
=====================================
utils/deriveConstants/Main.hs
=====================================
@@ -518,6 +518,8 @@ wanteds os = concat
,closureFieldGcptr C "StgInd" "indirectee"
+ ,closureSize C "StgStopAfterRetFrame"
+
,closureSize C "StgMutVar"
,closureField C "StgMutVar" "var"
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f7d2b30a12d81ff8948b13366a048e2…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f7d2b30a12d81ff8948b13366a048e2…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/ghci-multiple-home-units] Update "loading compiled code" GHCi documentation
by Hannes Siebenhandl (@fendor) 27 May '25
by Hannes Siebenhandl (@fendor) 27 May '25
27 May '25
Hannes Siebenhandl pushed to branch wip/fendor/ghci-multiple-home-units at Glasgow Haskell Compiler / GHC
Commits:
b1feabf0 by fendor at 2025-05-27T17:57:05+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
1 changed file:
- docs/users_guide/ghci.rst
Changes:
=====================================
docs/users_guide/ghci.rst
=====================================
@@ -251,8 +251,8 @@ We can compile ``D``, then load the whole program, like this:
.. code-block:: none
- ghci> :! ghc -c -dynamic D.hs
- ghci> :load A
+ ghci> :! ghc -c -this-unit-id interactive-session -dynamic D.hs
+ ghci> :load A B C D
Compiling B ( B.hs, interpreted )
Compiling C ( C.hs, interpreted )
Compiling A ( A.hs, interpreted )
@@ -268,6 +268,10 @@ Note the :ghc-flag:`-dynamic` flag to GHC: GHCi uses dynamically-linked object
code (if you are on a platform that supports it), and so in order to use
compiled code with GHCi it must be compiled for dynamic linking.
+Also, note the :ghc-flag:`-this-unit-id ⟨unit-id⟩` `interactive-session` to GHC: GHCi
+can only use the object code of a module loaded via :ghci-cmd:`:load`,
+if the object code has been compiled for the `interactive-session`.
+
At any time you can use the command :ghci-cmd:`:show modules` to get a list of
the modules currently loaded into GHCi:
@@ -301,8 +305,8 @@ So let's try compiling one of the other modules:
.. code-block:: none
- *ghci> :! ghc -c C.hs
- *ghci> :load A
+ *ghci> :! ghc -c -this-unit-id interactive-session -dynamic C.hs
+ *ghci> :load A B C D
Compiling D ( D.hs, interpreted )
Compiling B ( B.hs, interpreted )
Compiling C ( C.hs, interpreted )
@@ -316,7 +320,7 @@ rejected ``C``\'s object file. Ok, so let's also compile ``D``:
.. code-block:: none
- *ghci> :! ghc -c D.hs
+ *ghci> :! ghc -c -this-unit-id interactive-session -dynamic D.hs
*ghci> :reload
Ok, modules loaded: A, B, C, D.
@@ -325,7 +329,7 @@ picked up by :ghci-cmd:`:reload`, only :ghci-cmd:`:load`:
.. code-block:: none
- *ghci> :load A
+ *ghci> :load A B C D
Compiling B ( B.hs, interpreted )
Compiling A ( A.hs, interpreted )
Ok, modules loaded: A, B, C (C.o), D (D.o).
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1feabf08cafcd5b77985e1b57f7b2b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1feabf08cafcd5b77985e1b57f7b2b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/ghci-multiple-home-units] 2 commits: Make GHCi commands compatible with multiple home units
by Hannes Siebenhandl (@fendor) 27 May '25
by Hannes Siebenhandl (@fendor) 27 May '25
27 May '25
Hannes Siebenhandl pushed to branch wip/fendor/ghci-multiple-home-units at Glasgow Haskell Compiler / GHC
Commits:
0fbcc2e9 by fendor at 2025-05-27T16:16:15+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
- - - - -
c3ed675a by fendor at 2025-05-27T16:16:24+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
21 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- testsuite/tests/linters/notes.stdout
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -38,7 +38,9 @@ module GHC (
setSessionDynFlags,
setUnitDynFlags,
getProgramDynFlags, setProgramDynFlags,
+ setProgramHUG, setProgramHUG_,
getInteractiveDynFlags, setInteractiveDynFlags,
+ normaliseInteractiveDynFlags, initialiseInteractiveDynFlags,
interpretPackageEnv,
-- * Logging
@@ -55,6 +57,7 @@ module GHC (
addTarget,
removeTarget,
guessTarget,
+ guessTargetId,
-- * Loading\/compiling the program
depanal, depanalE,
@@ -83,6 +86,7 @@ module GHC (
getModuleGraph,
isLoaded,
isLoadedModule,
+ isLoadedHomeModule,
topSortModuleGraph,
-- * Inspecting modules
@@ -155,6 +159,7 @@ module GHC (
getBindings, getInsts, getNamePprCtx,
findModule, lookupModule,
findQualifiedModule, lookupQualifiedModule,
+ lookupLoadedHomeModuleByModuleName, lookupAllQualifiedModuleNames,
renamePkgQualM, renameRawPkgQualM,
isModuleTrusted, moduleTrustReqs,
getNamesInScope,
@@ -443,6 +448,7 @@ import Control.Concurrent
import Control.Monad
import Control.Monad.Catch as MC
import Data.Foldable
+import Data.Function ((&))
import Data.IORef
import Data.List (isPrefixOf)
import Data.Typeable ( Typeable )
@@ -458,7 +464,7 @@ import System.Environment ( getEnv, getProgName )
import System.Exit ( exitWith, ExitCode(..) )
import System.FilePath
import System.IO.Error ( isDoesNotExistError )
-import GHC.Unit.Home.PackageTable
+
-- %************************************************************************
-- %* *
@@ -861,6 +867,113 @@ setProgramDynFlags_ invalidate_needed dflags = do
when invalidate_needed $ invalidateModSummaryCache
return changed
+-- | Sets the program 'HomeUnitGraph'.
+--
+-- Sets the given 'HomeUnitGraph' as the 'HomeUnitGraph' of the current
+-- session. If the package flags change, we reinitialise the 'UnitState'
+-- of all 'HomeUnitEnv's in the current session.
+--
+-- This function unconditionally invalidates the module graph cache.
+--
+-- Precondition: the given 'HomeUnitGraph' must have the same keys as the 'HomeUnitGraph'
+-- of the current session. I.e., assuming the new 'HomeUnitGraph' is called
+-- 'new_hug', then:
+--
+-- @
+-- do
+-- hug <- hsc_HUG \<$\> getSession
+-- pure $ unitEnv_keys new_hug == unitEnv_keys hug
+-- @
+--
+-- If this precondition is violated, the function will crash.
+--
+-- Conceptually, similar to 'setProgramDynFlags', but performs the same check
+-- for all 'HomeUnitEnv's.
+setProgramHUG :: GhcMonad m => HomeUnitGraph -> m Bool
+setProgramHUG =
+ setProgramHUG_ True
+
+-- | Same as 'setProgramHUG', but gives you control over whether you want to
+-- invalidate the module graph cache.
+setProgramHUG_ :: GhcMonad m => Bool -> HomeUnitGraph -> m Bool
+setProgramHUG_ invalidate_needed new_hug0 = do
+ logger <- getLogger
+
+ hug0 <- hsc_HUG <$> getSession
+ (changed, new_hug1) <- checkNewHugDynFlags logger hug0 new_hug0
+
+ if changed
+ then do
+ unit_env0 <- hsc_unit_env <$> getSession
+ home_unit_graph <- HUG.unitEnv_traverseWithKey
+ (updateHomeUnit logger unit_env0 new_hug1)
+ (ue_home_unit_graph unit_env0)
+
+ let dflags1 = homeUnitEnv_dflags $ HUG.unitEnv_lookup (ue_currentUnit unit_env0) home_unit_graph
+ let unit_env = UnitEnv
+ { ue_platform = targetPlatform dflags1
+ , ue_namever = ghcNameVersion dflags1
+ , ue_home_unit_graph = home_unit_graph
+ , ue_current_unit = ue_currentUnit unit_env0
+ , ue_eps = ue_eps unit_env0
+ }
+ modifySession $ \h ->
+ -- hscSetFlags takes care of updating the logger as well.
+ hscSetFlags dflags1 h{ hsc_unit_env = unit_env }
+ else do
+ modifySession (\env ->
+ env
+ -- Set the new 'HomeUnitGraph'.
+ & hscUpdateHUG (const new_hug1)
+ -- hscSetActiveUnitId makes sure that the 'hsc_dflags'
+ -- are up-to-date.
+ & hscSetActiveUnitId (hscActiveUnitId env)
+ -- Make sure the logger is also updated.
+ & hscUpdateLoggerFlags)
+
+ when invalidate_needed $ invalidateModSummaryCache
+ pure changed
+ where
+ checkNewHugDynFlags :: GhcMonad m => Logger -> HomeUnitGraph -> HomeUnitGraph -> m (Bool, HomeUnitGraph)
+ checkNewHugDynFlags logger old_hug new_hug = do
+ -- Traverse the new HUG and check its 'DynFlags'.
+ -- The old 'HUG' is used to check whether package flags have changed.
+ hugWithCheck <- HUG.unitEnv_traverseWithKey
+ (\unitId homeUnit -> do
+ let newFlags = homeUnitEnv_dflags homeUnit
+ oldFlags = homeUnitEnv_dflags (HUG.unitEnv_lookup unitId old_hug)
+ checkedFlags <- checkNewDynFlags logger newFlags
+ pure
+ ( packageFlagsChanged oldFlags checkedFlags
+ , homeUnit { homeUnitEnv_dflags = checkedFlags }
+ )
+ )
+ new_hug
+ let
+ -- Did any of the package flags change?
+ changed = or $ fmap fst hugWithCheck
+ hug = fmap snd hugWithCheck
+ pure (changed, hug)
+
+ updateHomeUnit :: GhcMonad m => Logger -> UnitEnv -> HomeUnitGraph -> (UnitId -> HomeUnitEnv -> m HomeUnitEnv)
+ updateHomeUnit logger unit_env updates = \uid homeUnitEnv -> do
+ let cached_unit_dbs = homeUnitEnv_unit_dbs homeUnitEnv
+ dflags = case HUG.unitEnv_lookup_maybe uid updates of
+ Nothing -> homeUnitEnv_dflags homeUnitEnv
+ Just env -> homeUnitEnv_dflags env
+ old_hpt = homeUnitEnv_hpt homeUnitEnv
+ home_units = HUG.allUnits (ue_home_unit_graph unit_env)
+
+ (dbs,unit_state,home_unit,mconstants) <- liftIO $ initUnits logger dflags cached_unit_dbs home_units
+
+ updated_dflags <- liftIO $ updatePlatformConstants dflags mconstants
+ pure HomeUnitEnv
+ { homeUnitEnv_units = unit_state
+ , homeUnitEnv_unit_dbs = Just dbs
+ , homeUnitEnv_dflags = updated_dflags
+ , homeUnitEnv_hpt = old_hpt
+ , homeUnitEnv_home_unit = Just home_unit
+ }
-- When changing the DynFlags, we want the changes to apply to future
-- loads, but without completely discarding the program. But the
@@ -900,24 +1013,8 @@ getProgramDynFlags = getSessionDynFlags
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
setInteractiveDynFlags dflags = do
logger <- getLogger
- dflags' <- checkNewDynFlags logger dflags
- dflags'' <- checkNewInteractiveDynFlags logger dflags'
- modifySessionM $ \hsc_env0 -> do
- let ic0 = hsc_IC hsc_env0
-
- -- Initialise (load) plugins in the interactive environment with the new
- -- DynFlags
- plugin_env <- liftIO $ initializePlugins $ mkInteractiveHscEnv $
- hsc_env0 { hsc_IC = ic0 { ic_dflags = dflags'' }}
-
- -- Update both plugins cache and DynFlags in the interactive context.
- return $ hsc_env0
- { hsc_IC = ic0
- { ic_plugins = hsc_plugins plugin_env
- , ic_dflags = hsc_dflags plugin_env
- }
- }
-
+ icdflags <- normaliseInteractiveDynFlags logger dflags
+ modifySessionM (initialiseInteractiveDynFlags icdflags)
-- | Get the 'DynFlags' used to evaluate interactive expressions.
getInteractiveDynFlags :: GhcMonad m => m DynFlags
@@ -1022,6 +1119,36 @@ normalise_hyp fp
-----------------------------------------------------------------------------
+-- | Normalise the 'DynFlags' for us in an interactive context.
+--
+-- Makes sure unsupported Flags and other incosistencies are reported and removed.
+normaliseInteractiveDynFlags :: MonadIO m => Logger -> DynFlags -> m DynFlags
+normaliseInteractiveDynFlags logger dflags = do
+ dflags' <- checkNewDynFlags logger dflags
+ checkNewInteractiveDynFlags logger dflags'
+
+-- | Given a set of normalised 'DynFlags' (see 'normaliseInteractiveDynFlags')
+-- for the interactive context, initialize the 'InteractiveContext'.
+--
+-- Initialized plugins and sets the 'DynFlags' as the 'ic_dflags' of the
+-- 'InteractiveContext'.
+initialiseInteractiveDynFlags :: GhcMonad m => DynFlags -> HscEnv -> m HscEnv
+initialiseInteractiveDynFlags dflags hsc_env0 = do
+ let ic0 = hsc_IC hsc_env0
+
+ -- Initialise (load) plugins in the interactive environment with the new
+ -- DynFlags
+ plugin_env <- liftIO $ initializePlugins $ mkInteractiveHscEnv $
+ hsc_env0 { hsc_IC = ic0 { ic_dflags = dflags }}
+
+ -- Update both plugins cache and DynFlags in the interactive context.
+ return $ hsc_env0
+ { hsc_IC = ic0
+ { ic_plugins = hsc_plugins plugin_env
+ , ic_dflags = hsc_dflags plugin_env
+ }
+ }
+
-- | Checks the set of new DynFlags for possibly erroneous option
-- combinations when invoking 'setSessionDynFlags' and friends, and if
-- found, returns a fixed copy (if possible).
@@ -1084,7 +1211,7 @@ removeTarget target_id
where
filter targets = [ t | t@Target { targetId = id } <- targets, id /= target_id ]
--- | Attempts to guess what Target a string refers to. This function
+-- | Attempts to guess what 'Target' a string refers to. This function
-- implements the @--make@/GHCi command-line syntax for filenames:
--
-- - if the string looks like a Haskell source filename, then interpret it
@@ -1093,27 +1220,52 @@ removeTarget target_id
-- - if adding a .hs or .lhs suffix yields the name of an existing file,
-- then use that
--
--- - otherwise interpret the string as a module name
+-- - If it looks like a module name, interpret it as such
--
+-- - otherwise, this function throws a 'GhcException'.
guessTarget :: GhcMonad m => String -> Maybe UnitId -> Maybe Phase -> m Target
guessTarget str mUnitId (Just phase)
= do
tuid <- unitIdOrHomeUnit mUnitId
return (Target (TargetFile str (Just phase)) True tuid Nothing)
-guessTarget str mUnitId Nothing
+guessTarget str mUnitId Nothing = do
+ targetId <- guessTargetId str
+ toTarget targetId
+ where
+ obj_allowed
+ | '*':_ <- str = False
+ | otherwise = True
+ toTarget tid = do
+ tuid <- unitIdOrHomeUnit mUnitId
+ pure $ Target tid obj_allowed tuid Nothing
+
+-- | Attempts to guess what 'TargetId' a string refers to. This function
+-- implements the @--make@/GHCi command-line syntax for filenames:
+--
+-- - if the string looks like a Haskell source filename, then interpret it
+-- as such
+--
+-- - if adding a .hs or .lhs suffix yields the name of an existing file,
+-- then use that
+--
+-- - If it looks like a module name, interpret it as such
+--
+-- - otherwise, this function throws a 'GhcException'.
+guessTargetId :: GhcMonad m => String -> m TargetId
+guessTargetId str
| isHaskellSrcFilename file
- = target (TargetFile file Nothing)
+ = pure (TargetFile file Nothing)
| otherwise
= do exists <- liftIO $ doesFileExist hs_file
if exists
- then target (TargetFile hs_file Nothing)
+ then pure (TargetFile hs_file Nothing)
else do
exists <- liftIO $ doesFileExist lhs_file
if exists
- then target (TargetFile lhs_file Nothing)
+ then pure (TargetFile lhs_file Nothing)
else do
if looksLikeModuleName file
- then target (TargetModule (mkModuleName file))
+ then pure (TargetModule (mkModuleName file))
else do
dflags <- getDynFlags
liftIO $ throwGhcExceptionIO
@@ -1121,16 +1273,12 @@ guessTarget str mUnitId Nothing
text "target" <+> quotes (text file) <+>
text "is not a module name or a source file"))
where
- (file,obj_allowed)
- | '*':rest <- str = (rest, False)
- | otherwise = (str, True)
+ file
+ | '*':rest <- str = rest
+ | otherwise = str
- hs_file = file <.> "hs"
- lhs_file = file <.> "lhs"
-
- target tid = do
- tuid <- unitIdOrHomeUnit mUnitId
- pure $ Target tid obj_allowed tuid Nothing
+ hs_file = file <.> "hs"
+ lhs_file = file <.> "lhs"
-- | Unwrap 'UnitId' or retrieve the 'UnitId'
-- of the current 'HomeUnit'.
@@ -1251,11 +1399,11 @@ type TypecheckedSource = LHsBinds GhcTc
--
-- This function ignores boot modules and requires that there is only one
-- non-boot module with the given name.
-getModSummary :: GhcMonad m => ModuleName -> m ModSummary
+getModSummary :: GhcMonad m => Module -> m ModSummary
getModSummary mod = do
mg <- liftM hsc_mod_graph getSession
let mods_by_name = [ ms | ms <- mgModSummaries mg
- , ms_mod_name ms == mod
+ , ms_mod ms == mod
, isBootSummary ms == NotBoot ]
case mods_by_name of
[] -> do dflags <- getDynFlags
@@ -1286,7 +1434,9 @@ typecheckModule pmod = do
liftIO $ do
let ms = modSummary pmod
let lcl_dflags = ms_hspp_opts ms -- take into account pragmas (OPTIONS_GHC, etc.)
- let lcl_hsc_env = hscSetFlags lcl_dflags hsc_env
+ let lcl_hsc_env =
+ hscSetFlags lcl_dflags $
+ hscSetActiveUnitId (toUnitId $ moduleUnit $ ms_mod ms) hsc_env
let lcl_logger = hsc_logger lcl_hsc_env
(tc_gbl_env, rn_info) <- hscTypecheckRename lcl_hsc_env ms $
HsParsedModule { hpm_module = parsedSource pmod,
@@ -1428,17 +1578,28 @@ compileCore simplify fn = do
getModuleGraph :: GhcMonad m => m ModuleGraph -- ToDo: DiGraph ModSummary
getModuleGraph = liftM hsc_mod_graph getSession
+{-# DEPRECATED isLoaded "Prefer 'isLoadedModule' and 'isLoadedHomeModule'" #-}
-- | Return @True@ \<==> module is loaded.
isLoaded :: GhcMonad m => ModuleName -> m Bool
isLoaded m = withSession $ \hsc_env -> liftIO $ do
- hmi <- lookupHpt (hsc_HPT hsc_env) m
- return $! isJust hmi
+ hmis <- HUG.lookupAllHug (hsc_HUG hsc_env) m
+ return $! not (null hmis)
+-- | Check whether a 'ModuleName' is found in the 'HomePackageTable'
+-- for the given 'UnitId'.
isLoadedModule :: GhcMonad m => UnitId -> ModuleName -> m Bool
isLoadedModule uid m = withSession $ \hsc_env -> liftIO $ do
hmi <- HUG.lookupHug (hsc_HUG hsc_env) uid m
return $! isJust hmi
+-- | Check whether 'Module' is part of the 'HomeUnitGraph'.
+--
+-- Similar to 'isLoadedModule', but for 'Module's.
+isLoadedHomeModule :: GhcMonad m => Module -> m Bool
+isLoadedHomeModule m = withSession $ \hsc_env -> liftIO $ do
+ hmi <- HUG.lookupHugByModule m (hsc_HUG hsc_env)
+ return $! isJust hmi
+
-- | Return the bindings for the current interactive session.
getBindings :: GhcMonad m => m [TyThing]
getBindings = withSession $ \hsc_env ->
@@ -1470,7 +1631,7 @@ data ModuleInfo = ModuleInfo {
-- | Request information about a loaded 'Module'
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) -- XXX: Maybe X
getModuleInfo mdl = withSession $ \hsc_env -> do
- if moduleUnitId mdl `S.member` hsc_all_home_unit_ids hsc_env
+ if HUG.memberHugUnit (moduleUnit mdl) (hsc_HUG hsc_env)
then liftIO $ getHomeModuleInfo hsc_env mdl
else liftIO $ getPackageModuleInfo hsc_env mdl
@@ -1826,6 +1987,50 @@ lookupLoadedHomeModule uid mod_name = withSession $ \hsc_env -> liftIO $ do
Just mod_info -> return (Just (mi_module (hm_iface mod_info)))
_not_a_home_module -> return Nothing
+-- | Lookup the given 'ModuleName' in the 'HomeUnitGraph'.
+--
+-- Returns 'Nothing' if no 'Module' has the given 'ModuleName'.
+-- Otherwise, returns all 'Module's that have the given 'ModuleName'.
+--
+-- A 'ModuleName' is generally not enough to uniquely identify a 'Module', since
+-- there can be multiple units exposing the same 'ModuleName' in the case of
+-- multiple home units.
+-- Thus, this function may return more than one possible 'Module'.
+-- We leave it up to the caller to decide how to handle the ambiguity.
+-- For example, GHCi may prompt the user to clarify which 'Module' is the correct one.
+--
+lookupLoadedHomeModuleByModuleName :: GhcMonad m => ModuleName -> m (Maybe [Module])
+lookupLoadedHomeModuleByModuleName mod_name = withSession $ \hsc_env -> liftIO $ do
+ trace_if (hsc_logger hsc_env) (text "lookupLoadedHomeModuleByModuleName" <+> ppr mod_name)
+ HUG.lookupAllHug (hsc_HUG hsc_env) mod_name >>= \case
+ [] -> return Nothing
+ mod_infos -> return (Just (mi_module . hm_iface <$> mod_infos))
+
+-- | Given a 'ModuleName' and 'PkgQual', lookup all 'Module's that may fit the criteria.
+--
+-- Identically to 'lookupLoadedHomeModuleByModuleName', there may be more than one
+-- 'Module' in the 'HomeUnitGraph' that has the given 'ModuleName'.
+--
+-- The result is guaranteed to be non-empty, if no 'Module' can be found,
+-- this function throws an error.
+lookupAllQualifiedModuleNames :: GhcMonad m => PkgQual -> ModuleName -> m [Module]
+lookupAllQualifiedModuleNames NoPkgQual mod_name = withSession $ \hsc_env -> do
+ home <- lookupLoadedHomeModuleByModuleName mod_name
+ case home of
+ Just m -> return m
+ Nothing -> liftIO $ do
+ let fc = hsc_FC hsc_env
+ let units = hsc_units hsc_env
+ let dflags = hsc_dflags hsc_env
+ let fopts = initFinderOpts dflags
+ res <- findExposedPackageModule fc fopts units mod_name NoPkgQual
+ case res of
+ Found _ m -> return [m]
+ err -> throwOneError $ noModError hsc_env noSrcSpan mod_name err
+lookupAllQualifiedModuleNames pkgqual mod_name = do
+ m <- findQualifiedModule pkgqual mod_name
+ pure [m]
+
-- | Check that a module is safe to import (according to Safe Haskell).
--
-- We return True to indicate the import is safe and False otherwise
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -277,11 +277,20 @@ downsweepInteractiveImports hsc_env ic = unsafeInterleaveIO $ do
where
--
- mkEdge :: InteractiveImport -> (UnitId, ImportLevel, PkgQual, GenWithIsBoot (Located ModuleName))
+ mkEdge :: InteractiveImport -> Either ModuleNodeEdge (UnitId, ImportLevel, PkgQual, GenWithIsBoot (Located ModuleName))
-- A simple edge to a module from the same home unit
mkEdge (IIModule n) =
- let unitId = homeUnitId $ hsc_home_unit hsc_env
- in (unitId, NormalLevel, NoPkgQual, GWIB (noLoc n) NotBoot)
+ let
+ mod_node_key = ModNodeKeyWithUid
+ { mnkModuleName = GWIB (moduleName n) NotBoot
+ , mnkUnitId =
+ -- 'toUnitId' is safe here, as we can't import modules that
+ -- don't have a 'UnitId'.
+ toUnitId (moduleUnit n)
+ }
+ mod_node_edge =
+ ModuleNodeEdge NormalLevel (NodeKey_Module mod_node_key)
+ in Left mod_node_edge
-- A complete import statement
mkEdge (IIDecl i) =
let lvl = convImportLevel (ideclLevelSpec i)
@@ -289,37 +298,41 @@ downsweepInteractiveImports hsc_env ic = unsafeInterleaveIO $ do
is_boot = ideclSource i
mb_pkg = renameRawPkgQual (hsc_unit_env hsc_env) (unLoc $ ideclName i) (ideclPkgQual i)
unitId = homeUnitId $ hsc_home_unit hsc_env
- in (unitId, lvl, mb_pkg, GWIB (noLoc wanted_mod) is_boot)
+ in Right (unitId, lvl, mb_pkg, GWIB (noLoc wanted_mod) is_boot)
loopFromInteractive :: HscEnv
- -> [(UnitId, ImportLevel, PkgQual, GenWithIsBoot (Located ModuleName))]
+ -> [Either ModuleNodeEdge (UnitId, ImportLevel, PkgQual, GenWithIsBoot (Located ModuleName))]
-> M.Map NodeKey ModuleGraphNode
-> IO ([ModuleNodeEdge],M.Map NodeKey ModuleGraphNode)
loopFromInteractive _ [] cached_nodes = return ([], cached_nodes)
-loopFromInteractive hsc_env (edge:edges) cached_nodes = do
- let (unitId, lvl, mb_pkg, GWIB wanted_mod is_boot) = edge
- let home_unit = ue_unitHomeUnit unitId (hsc_unit_env hsc_env)
- let k _ loc mod =
- let key = moduleToMnk mod is_boot
- in return $ FoundHome (ModuleNodeFixed key loc)
- found <- liftIO $ summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg []
- case found of
- -- Case 1: Home modules have to already be in the cache.
- FoundHome (ModuleNodeFixed mod _) -> do
- let edge = ModuleNodeEdge lvl (NodeKey_Module mod)
- -- Note: Does not perform any further downsweep as the module must already be in the cache.
- (edges, cached_nodes') <- loopFromInteractive hsc_env edges cached_nodes
- return (edge : edges, cached_nodes')
- -- Case 2: External units may not be in the cache, if we haven't already initialised the
- -- module graph. We can construct the module graph for those here by calling loopUnit.
- External uid -> do
- let hsc_env' = hscSetActiveHomeUnit home_unit hsc_env
- cached_nodes' = loopUnit hsc_env' cached_nodes [uid]
- edge = ModuleNodeEdge lvl (NodeKey_ExternalUnit uid)
- (edges, cached_nodes') <- loopFromInteractive hsc_env edges cached_nodes'
- return (edge : edges, cached_nodes')
- -- And if it's not found.. just carry on and hope.
- _ -> loopFromInteractive hsc_env edges cached_nodes
+loopFromInteractive hsc_env (edge:edges) cached_nodes =
+ case edge of
+ Left edge -> do
+ (edges, cached_nodes') <- loopFromInteractive hsc_env edges cached_nodes
+ return (edge : edges, cached_nodes')
+ Right (unitId, lvl, mb_pkg, GWIB wanted_mod is_boot) -> do
+ let home_unit = ue_unitHomeUnit unitId (hsc_unit_env hsc_env)
+ let k _ loc mod =
+ let key = moduleToMnk mod is_boot
+ in return $ FoundHome (ModuleNodeFixed key loc)
+ found <- liftIO $ summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg []
+ case found of
+ -- Case 1: Home modules have to already be in the cache.
+ FoundHome (ModuleNodeFixed mod _) -> do
+ let edge = ModuleNodeEdge lvl (NodeKey_Module mod)
+ -- Note: Does not perform any further downsweep as the module must already be in the cache.
+ (edges, cached_nodes') <- loopFromInteractive hsc_env edges cached_nodes
+ return (edge : edges, cached_nodes')
+ -- Case 2: External units may not be in the cache, if we haven't already initialised the
+ -- module graph. We can construct the module graph for those here by calling loopUnit.
+ External uid -> do
+ let hsc_env' = hscSetActiveHomeUnit home_unit hsc_env
+ cached_nodes' = loopUnit hsc_env' cached_nodes [uid]
+ edge = ModuleNodeEdge lvl (NodeKey_ExternalUnit uid)
+ (edges, cached_nodes') <- loopFromInteractive hsc_env edges cached_nodes'
+ return (edge : edges, cached_nodes')
+ -- And if it's not found.. just carry on and hope.
+ _ -> loopFromInteractive hsc_env edges cached_nodes
-- | Create a module graph from a list of installed modules.
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -162,6 +162,7 @@ module GHC.Driver.Session (
updOptLevel,
setTmpDir,
setUnitId,
+ setHomeUnitId,
TurnOnFlag,
turnOn,
@@ -3114,6 +3115,9 @@ parseUnitArg =
setUnitId :: String -> DynFlags -> DynFlags
setUnitId p d = d { homeUnitId_ = stringToUnitId p }
+setHomeUnitId :: UnitId -> DynFlags -> DynFlags
+setHomeUnitId p d = d { homeUnitId_ = p }
+
setWorkingDirectory :: String -> DynFlags -> DynFlags
setWorkingDirectory p d = d { workingDirectory = Just p }
=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -918,12 +918,10 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
case mb_found of
InstalledFound loc -> do
-- See Note [Home module load error]
- case mhome_unit of
- Just home_unit
- | isHomeInstalledModule home_unit mod
- , not (isOneShot (ghcMode dflags))
- -> return (Failed (HomeModError mod loc))
- _ -> do
+ if HUG.memberHugUnitId (moduleUnit mod) (hsc_HUG hsc_env)
+ && not (isOneShot (ghcMode dflags))
+ then return (Failed (HomeModError mod loc))
+ else do
r <- read_file logger name_cache unit_state dflags wanted_mod (ml_hi_file loc)
case r of
Failed err
=====================================
compiler/GHC/Rename/Unbound.hs
=====================================
@@ -364,7 +364,7 @@ importSuggestions looking_for ic currMod imports rdr_name
pick_interactive :: InteractiveImport -> Bool
pick_interactive (IIDecl d) | mod_name == Just (unLoc (ideclName d)) = True
| mod_name == fmap unLoc (ideclAs d) = True
- pick_interactive (IIModule m) | mod_name == Just m = True
+ pick_interactive (IIModule m) | mod_name == Just (moduleName m) = True
pick_interactive _ = False
-- We want to keep only one for each original module; preferably one with an
=====================================
compiler/GHC/Runtime/Context.hs
=====================================
@@ -115,6 +115,51 @@ The details are a bit tricky though:
modules.
+Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+The 'InteractiveContext' is used to store 'DynFlags', 'Plugins' and similar
+information about the so-called interactive "home unit". We are using
+quotes here, since, originally, GHC wasn't aware of more than one 'HomeUnitEnv's.
+So the 'InteractiveContext' was a hack/solution to have 'DynFlags' and 'Plugins'
+independent of the 'DynFlags' and 'Plugins' stored in 'HscEnv'.
+Nowadays, GHC has support for multiple home units via the 'HomeUnitGraph', thus,
+this part of the 'InteractiveContext' is strictly speaking redundant, as we
+can simply manage one 'HomeUnitEnv' for the 'DynFlags' and 'Plugins' that are
+currently stored in the 'InteractiveContext'.
+
+As a matter of fact, that's exactly what we do nowadays.
+That means, we can also lift other restrictions in the future, for example
+allowing @:seti@ commands to modify the package-flags, since we now have a
+separate 'UnitState' for the interactive session.
+However, we did not rip out 'ic_dflags' and 'ic_plugins', yet, as it makes
+it easier to access them for functions that want to use the interactive 'DynFlags',
+such as 'runInteractiveHsc' and 'mkInteractiveHscEnv', without having to look that
+information up in the 'HomeUnitGraph'.
+It is reasonable to change this in the future, and remove 'ic_dflags' and 'ic_plugins'.
+
+We keep 'ic_dflags' and 'ic_plugins' around, but we also store a 'HomeUnitEnv'
+for the 'DynFlags' and 'Plugins' of the interactive session.
+
+It is important to keep the 'DynFlags' in these two places consistent.
+
+In other words, whenever you update the 'DynFlags' of the 'interactiveGhciUnitId'
+in the 'HscEnv', then you also need to update the 'DynFlags' of the
+'InteractiveContext'.
+The easiest way to update them is via 'setInteractiveDynFlags'.
+However, careful, footgun! It is very easy to call 'setInteractiveDynFlags'
+and forget to call 'normaliseInteractiveDynFlags' on the 'DynFlags' in the
+'HscEnv'! This is important, because you may, accidentally, have enabled
+Language Extensions that are not supported in the interactive ghc session,
+which we do not want.
+
+To summarise, the 'ic_dflags' and 'ic_plugins' are currently used to
+conveniently cache them for easy access.
+The 'ic_dflags' must be identical to the 'DynFlags' stored in the 'HscEnv'
+for the 'HomeUnitEnv' identified by 'interactiveGhciUnitId'.
+
+See Note [Multiple Home Units aware GHCi] for the design and rationale for
+the current 'interactiveGhciUnitId'.
+
Note [Interactively-bound Ids in GHCi]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The Ids bound by previous Stmts in GHCi are currently
@@ -296,7 +341,7 @@ data InteractiveImport
-- ^ Bring the exports of a particular module
-- (filtered by an import decl) into scope
- | IIModule ModuleName
+ | IIModule Module
-- ^ Bring into scope the entire top-level envt of
-- of this module, including the things imported
-- into it.
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -119,7 +119,6 @@ import GHC.Unit
import GHC.Unit.Module.Graph
import GHC.Unit.Module.ModIface
import GHC.Unit.Home.ModInfo
-import GHC.Unit.Home.PackageTable
import GHC.Tc.Module ( runTcInteractive, tcRnTypeSkolemising, loadUnqualIfaces )
import GHC.Tc.Solver (simplifyWantedsTcM)
@@ -823,16 +822,17 @@ findGlobalRdrEnv hsc_env imports
idecls :: [LImportDecl GhcPs]
idecls = [noLocA d | IIDecl d <- imports]
- imods :: [ModuleName]
+ imods :: [Module]
imods = [m | IIModule m <- imports]
- mkEnv mod = mkTopLevEnv hsc_env mod >>= \case
- Left err -> pure $ Left (mod, err)
- Right env -> pure $ Right env
+ mkEnv mod = do
+ mkTopLevEnv hsc_env mod >>= \case
+ Left err -> pure $ Left (moduleName mod, err)
+ Right env -> pure $ Right env
-mkTopLevEnv :: HscEnv -> ModuleName -> IO (Either String GlobalRdrEnv)
+mkTopLevEnv :: HscEnv -> Module -> IO (Either String GlobalRdrEnv)
mkTopLevEnv hsc_env modl
- = lookupHpt hpt modl >>= \case
+ = HUG.lookupHugByModule modl hug >>= \case
Nothing -> pure $ Left "not a home module"
Just details ->
case mi_top_env (hm_iface details) of
@@ -841,7 +841,7 @@ mkTopLevEnv hsc_env modl
let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports)
pure $ Right $ plusGlobalRdrEnv imports_env exports_env
where
- hpt = hsc_HPT hsc_env
+ hug = hsc_HUG hsc_env
-- | Make the top-level environment with all bindings imported by this module.
-- Exported bindings from this module are not included in the result.
@@ -877,11 +877,9 @@ getContext = withSession $ \HscEnv{ hsc_IC=ic } ->
-- its full top-level scope available.
moduleIsInterpreted :: GhcMonad m => Module -> m Bool
moduleIsInterpreted modl = withSession $ \h ->
- if notHomeModule (hsc_home_unit h) modl
- then return False
- else liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case
- Just hmi -> return (isJust $ homeModInfoByteCode hmi)
- _not_a_home_module -> return False
+ liftIO (HUG.lookupHugByModule modl (hsc_HUG h)) >>= \case
+ Just hmi -> return (isJust $ homeModInfoByteCode hmi)
+ _not_a_home_module -> return False
-- | Looks up an identifier in the current interactive context (for :info)
-- Filter the instances by the ones whose tycons (or classes resp)
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -77,7 +77,7 @@ import Control.Monad
import Data.Char
import GHC.Unit.Module
-import GHC.Unit.Home.PackageTable (lookupHpt)
+import qualified GHC.Unit.Home.Graph as HUG
import Data.Array
import Data.Coerce (coerce)
@@ -436,8 +436,7 @@ schemeER_wrk d p rhs = schemeE d 0 p rhs
-- If that is 'Nothing', consider breakpoints to be disabled and skip the
-- instruction.
--
--- If the breakpoint is inlined from another module, look it up in the home
--- package table.
+-- If the breakpoint is inlined from another module, look it up in the HUG (home unit graph).
-- If the module doesn't exist there, or its module pointer is null (which means
-- that the 'ModBreaks' value is uninitialized), skip the instruction.
break_info ::
@@ -450,7 +449,7 @@ break_info hsc_env mod current_mod current_mod_breaks
| mod == current_mod
= pure $ check_mod_ptr =<< current_mod_breaks
| otherwise
- = ioToBc (lookupHpt (hsc_HPT hsc_env) (moduleName mod)) >>= \case
+ = ioToBc (HUG.lookupHugByModule mod (hsc_HUG hsc_env)) >>= \case
Just hp -> pure $ check_mod_ptr (getModBreaks hp)
Nothing -> pure Nothing
where
=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -461,7 +461,7 @@ computeLinkDependencies cfg unit_env link_spec finder_opts finder_cache ar_cache
-- all the units we want to link together, without their dependencies
let root_units = filter (/= ue_currentUnit unit_env)
- $ filter (/= interactiveUnitId)
+ $ filter (/= interactiveUnitId) -- TODO @fendor: what does this do?
$ nub
$ rts_wired_units ++ reverse obj_units ++ reverse units
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -150,7 +150,6 @@ import GHC.Types.Basic hiding( SuccessFlag(..) )
import GHC.Types.Annotations
import GHC.Types.SrcLoc
import GHC.Types.SourceFile
-import GHC.Types.PkgQual
import qualified GHC.LanguageExtensions as LangExt
import GHC.Unit.Env as UnitEnv
@@ -2119,15 +2118,18 @@ runTcInteractive hsc_env thing_inside
, let local_gres = filter isLocalGRE gres
, not (null local_gres) ]) ]
- ; let getOrphans m mb_pkg = fmap (\iface -> mi_module iface
- : dep_orphs (mi_deps iface))
- (loadSrcInterface (text "runTcInteractive") m
- NotBoot mb_pkg)
+ ; let getOrphansForModuleName m mb_pkg = do
+ iface <- loadSrcInterface (text "runTcInteractive") m NotBoot mb_pkg
+ pure $ mi_module iface : dep_orphs (mi_deps iface)
+
+ getOrphansForModule m = do
+ iface <- loadModuleInterface (text "runTcInteractive") m
+ pure $ mi_module iface : dep_orphs (mi_deps iface)
; !orphs <- fmap (force . concat) . forM (ic_imports icxt) $ \i ->
case i of -- force above: see #15111
- IIModule n -> getOrphans n NoPkgQual
- IIDecl i -> getOrphans (unLoc (ideclName i))
+ IIModule n -> getOrphansForModule n
+ IIDecl i -> getOrphansForModuleName (unLoc (ideclName i))
(renameRawPkgQual (hsc_unit_env hsc_env) (unLoc $ ideclName i) (ideclPkgQual i))
=====================================
compiler/GHC/Types/Name/Ppr.hs
=====================================
@@ -13,6 +13,7 @@ import GHC.Data.FastString
import GHC.Unit
import GHC.Unit.Env
+import qualified GHC.Unit.Home.Graph as HUG
import GHC.Types.Name
import GHC.Types.Name.Reader
@@ -72,12 +73,11 @@ mkNamePprCtx :: Outputable info => PromotionTickContext -> UnitEnv -> GlobalRdrE
mkNamePprCtx ptc unit_env env
= QueryQualify
(mkQualName env)
- (mkQualModule unit_state home_unit)
+ (mkQualModule unit_state unit_env)
(mkQualPackage unit_state)
(mkPromTick ptc env)
where
unit_state = ue_homeUnitState unit_env
- home_unit = ue_homeUnit unit_env
mkQualName :: Outputable info => GlobalRdrEnvX info -> QueryQualifyName
mkQualName env = qual_name where
@@ -215,10 +215,12 @@ Side note (int-index):
-- | Creates a function for formatting modules based on two heuristics:
-- (1) if the module is the current module, don't qualify, and (2) if there
-- is only one exposed package which exports this module, don't qualify.
-mkQualModule :: UnitState -> Maybe HomeUnit -> QueryQualifyModule
-mkQualModule unit_state mhome_unit mod
- | Just home_unit <- mhome_unit
- , isHomeModule home_unit mod = False
+mkQualModule :: UnitState -> UnitEnv -> QueryQualifyModule
+mkQualModule unit_state unitEnv mod
+ -- Check whether the unit of the module is in the HomeUnitGraph.
+ -- If it is, then we consider this 'mod' to be "local" and don't
+ -- want to qualify it.
+ | HUG.memberHugUnit (moduleUnit mod) (ue_home_unit_graph unitEnv) = False
| [(_, pkgconfig)] <- lookup,
mkUnit pkgconfig == moduleUnit mod
=====================================
compiler/GHC/Unit/Env.hs
=====================================
@@ -241,7 +241,7 @@ isUnitEnvInstalledModule ue m = maybe False (`isHomeInstalledModule` m) hu
-- -------------------------------------------------------
ue_findHomeUnitEnv :: HasDebugCallStack => UnitId -> UnitEnv -> HomeUnitEnv
-ue_findHomeUnitEnv uid e = case HUG.lookupHugUnit uid (ue_home_unit_graph e) of
+ue_findHomeUnitEnv uid e = case HUG.lookupHugUnitId uid (ue_home_unit_graph e) of
Nothing -> pprPanic "Unit unknown to the internal unit environment"
$ text "unit (" <> ppr uid <> text ")"
$$ ppr (HUG.allUnits (ue_home_unit_graph e))
@@ -311,7 +311,7 @@ ue_unitHomeUnit uid = expectJust . ue_unitHomeUnit_maybe uid
ue_unitHomeUnit_maybe :: UnitId -> UnitEnv -> Maybe HomeUnit
ue_unitHomeUnit_maybe uid ue_env =
- HUG.homeUnitEnv_home_unit =<< HUG.lookupHugUnit uid (ue_home_unit_graph ue_env)
+ HUG.homeUnitEnv_home_unit =<< HUG.lookupHugUnitId uid (ue_home_unit_graph ue_env)
-- -------------------------------------------------------
-- Query and modify the currently active unit
@@ -319,7 +319,7 @@ ue_unitHomeUnit_maybe uid ue_env =
ue_currentHomeUnitEnv :: HasDebugCallStack => UnitEnv -> HomeUnitEnv
ue_currentHomeUnitEnv e =
- case HUG.lookupHugUnit (ue_currentUnit e) (ue_home_unit_graph e) of
+ case HUG.lookupHugUnitId (ue_currentUnit e) (ue_home_unit_graph e) of
Just unitEnv -> unitEnv
Nothing -> pprPanic "packageNotFound" $
(ppr $ ue_currentUnit e) $$ ppr (HUG.allUnits (ue_home_unit_graph e))
@@ -389,7 +389,7 @@ ue_transitiveHomeDeps uid e =
-- FIXME: Shouldn't this be a proper assertion only used in debug mode?
assertUnitEnvInvariant :: HasDebugCallStack => UnitEnv -> UnitEnv
assertUnitEnvInvariant u =
- case HUG.lookupHugUnit (ue_current_unit u) (ue_home_unit_graph u) of
+ case HUG.lookupHugUnitId (ue_current_unit u) (ue_home_unit_graph u) of
Just _ -> u
Nothing ->
pprPanic "invariant" (ppr (ue_current_unit u) $$ ppr (HUG.allUnits (ue_home_unit_graph u)))
=====================================
compiler/GHC/Unit/Home/Graph.hs
=====================================
@@ -34,7 +34,10 @@ module GHC.Unit.Home.Graph
, lookupHug
, lookupHugByModule
, lookupHugUnit
-
+ , lookupHugUnitId
+ , lookupAllHug
+ , memberHugUnit
+ , memberHugUnitId
-- ** Reachability
, transitiveHomeDeps
@@ -62,6 +65,8 @@ module GHC.Unit.Home.Graph
, unitEnv_insert
, unitEnv_new
, unitEnv_lookup
+ , unitEnv_traverseWithKey
+ , unitEnv_assocs
) where
import GHC.Prelude
@@ -73,6 +78,7 @@ import GHC.Unit.Home.PackageTable
import GHC.Unit.Module
import GHC.Unit.Module.ModIface
import GHC.Unit.State
+import GHC.Utils.Monad (mapMaybeM)
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -222,7 +228,7 @@ updateUnitFlags uid f = unitEnv_adjust update uid
-- | Compute the transitive closure of a unit in the 'HomeUnitGraph'.
-- If the argument unit is not present in the graph returns Nothing.
transitiveHomeDeps :: UnitId -> HomeUnitGraph -> Maybe [UnitId]
-transitiveHomeDeps uid hug = case lookupHugUnit uid hug of
+transitiveHomeDeps uid hug = case lookupHugUnitId uid hug of
Nothing -> Nothing
Just hue -> Just $
Set.toList (loop (Set.singleton uid) (homeUnitDepends (homeUnitEnv_units hue)))
@@ -234,7 +240,7 @@ transitiveHomeDeps uid hug = case lookupHugUnit uid hug of
let hue = homeUnitDepends
. homeUnitEnv_units
. expectJust
- $ lookupHugUnit uid hug
+ $ lookupHugUnitId uid hug
in loop (Set.insert uid acc) (hue ++ uids)
--------------------------------------------------------------------------------
@@ -246,21 +252,47 @@ transitiveHomeDeps uid hug = case lookupHugUnit uid hug of
lookupHug :: HomeUnitGraph -> UnitId -> ModuleName -> IO (Maybe HomeModInfo)
lookupHug hug uid mod = do
case unitEnv_lookup_maybe uid hug of
- -- Really, here we want "lookup HPT" rather than unitEnvLookup
Nothing -> pure Nothing
Just hue -> lookupHpt (homeUnitEnv_hpt hue) mod
-- | Lookup the 'HomeModInfo' of a 'Module' in the 'HomeUnitGraph' (via the 'HomePackageTable' of the corresponding unit)
lookupHugByModule :: Module -> HomeUnitGraph -> IO (Maybe HomeModInfo)
-lookupHugByModule mod hug
- | otherwise = do
- case unitEnv_lookup_maybe (toUnitId $ moduleUnit mod) hug of
- Nothing -> pure Nothing
- Just env -> lookupHptByModule (homeUnitEnv_hpt env) mod
+lookupHugByModule mod hug =
+ case lookupHugUnit (moduleUnit mod) hug of
+ Nothing -> pure Nothing
+ Just env -> lookupHptByModule (homeUnitEnv_hpt env) mod
+
+-- | Lookup all 'HomeModInfo' that have the same 'ModuleName' as the given 'ModuleName'.
+-- 'ModuleName's are not unique in the case of multiple home units, so there can be
+-- more than one possible 'HomeModInfo'.
+--
+-- You should always prefer 'lookupHug' and 'lookupHugByModule' when possible.
+lookupAllHug :: HomeUnitGraph -> ModuleName -> IO [HomeModInfo]
+lookupAllHug hug mod = mapMaybeM (\uid -> lookupHug hug uid mod) (Set.toList $ unitEnv_keys hug)
-- | Lookup a 'HomeUnitEnv' by 'UnitId' in a 'HomeUnitGraph'
-lookupHugUnit :: UnitId -> HomeUnitGraph -> Maybe HomeUnitEnv
-lookupHugUnit = unitEnv_lookup_maybe
+lookupHugUnitId :: UnitId -> HomeUnitGraph -> Maybe HomeUnitEnv
+lookupHugUnitId = unitEnv_lookup_maybe
+
+-- | Check whether the 'UnitId' is present in the 'HomeUnitGraph'
+memberHugUnitId :: UnitId -> HomeUnitGraph -> Bool
+memberHugUnitId u = isJust . lookupHugUnitId u
+
+-- | Lookup up the 'HomeUnitEnv' by the 'Unit' in the 'HomeUnitGraph'.
+-- If the 'Unit' can be turned into a 'UnitId', we behave identical to 'lookupHugUnitId'.
+--
+-- A 'HoleUnit' is never part of the 'HomeUnitGraph', only instantiated 'Unit's
+lookupHugUnit :: Unit -> HomeUnitGraph -> Maybe HomeUnitEnv
+lookupHugUnit unit hug =
+ if isHoleUnit unit
+ then Nothing
+ else lookupHugUnitId (toUnitId unit) hug
+
+-- | Check whether the 'Unit' is present in the 'HomeUnitGraph'
+--
+-- A 'HoleUnit' is never part of the 'HomeUnitGraph', only instantiated 'Unit's
+memberHugUnit :: Unit -> HomeUnitGraph -> Bool
+memberHugUnit u = isJust . lookupHugUnit u
--------------------------------------------------------------------------------
-- * Internal representation map
@@ -313,6 +345,13 @@ unitEnv_foldWithKey f z (UnitEnvGraph g)= Map.foldlWithKey' f z g
unitEnv_lookup :: UnitEnvGraphKey -> UnitEnvGraph v -> v
unitEnv_lookup u env = expectJust $ unitEnv_lookup_maybe u env
+unitEnv_traverseWithKey :: Applicative f => (UnitEnvGraphKey -> a -> f b) -> UnitEnvGraph a -> f (UnitEnvGraph b)
+unitEnv_traverseWithKey f unitEnv =
+ UnitEnvGraph <$> Map.traverseWithKey f (unitEnv_graph unitEnv)
+
+unitEnv_assocs :: UnitEnvGraph a -> [(UnitEnvGraphKey, a)]
+unitEnv_assocs (UnitEnvGraph x) = Map.assocs x
+
--------------------------------------------------------------------------------
-- * Utilities
--------------------------------------------------------------------------------
=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -63,12 +63,16 @@ module GHC.Unit.Types
, mainUnitId
, thisGhcUnitId
, interactiveUnitId
+ , interactiveGhciUnitId
+ , interactiveSessionUnitId
, ghcInternalUnit
, rtsUnit
, mainUnit
, thisGhcUnit
, interactiveUnit
+ , interactiveGhciUnit
+ , interactiveSessionUnit
, isInteractiveModule
, wiredInUnitIds
@@ -588,20 +592,24 @@ Make sure you change 'GHC.Unit.State.findWiredInUnits' if you add an entry here.
-}
ghcInternalUnitId, rtsUnitId,
- mainUnitId, thisGhcUnitId, interactiveUnitId :: UnitId
+ mainUnitId, thisGhcUnitId, interactiveUnitId, interactiveGhciUnitId, interactiveSessionUnitId :: UnitId
ghcInternalUnit, rtsUnit,
- mainUnit, thisGhcUnit, interactiveUnit :: Unit
+ mainUnit, thisGhcUnit, interactiveUnit, interactiveGhciUnit, interactiveSessionUnit :: Unit
ghcInternalUnitId = UnitId (fsLit "ghc-internal")
rtsUnitId = UnitId (fsLit "rts")
thisGhcUnitId = UnitId (fsLit cProjectUnitId) -- See Note [GHC's Unit Id]
interactiveUnitId = UnitId (fsLit "interactive")
+interactiveGhciUnitId = UnitId (fsLit "interactive-ghci")
+interactiveSessionUnitId = UnitId (fsLit "interactive-session")
ghcInternalUnit = RealUnit (Definite ghcInternalUnitId)
rtsUnit = RealUnit (Definite rtsUnitId)
thisGhcUnit = RealUnit (Definite thisGhcUnitId)
interactiveUnit = RealUnit (Definite interactiveUnitId)
+interactiveGhciUnit = RealUnit (Definite interactiveGhciUnitId)
+interactiveSessionUnit = RealUnit (Definite interactiveSessionUnitId)
-- | This is the package Id for the current program. It is the default
-- package Id if you don't specify a package name. We don't add this prefix
=====================================
docs/users_guide/ghci.rst
=====================================
@@ -251,8 +251,8 @@ We can compile ``D``, then load the whole program, like this:
.. code-block:: none
- ghci> :! ghc -c -dynamic D.hs
- ghci> :load A
+ ghci> :! ghc -c -this-unit-id interactive-session -dynamic D.hs
+ ghci> :load A B C D
Compiling B ( B.hs, interpreted )
Compiling C ( C.hs, interpreted )
Compiling A ( A.hs, interpreted )
@@ -268,6 +268,10 @@ Note the :ghc-flag:`-dynamic` flag to GHC: GHCi uses dynamically-linked object
code (if you are on a platform that supports it), and so in order to use
compiled code with GHCi it must be compiled for dynamic linking.
+Also, note the :ghc-flag:`-this-unit-id` `interactive-session` to GHC: GHCi
+can only use the object code of a module loaded via :ghci-cmd:`:load`,
+if the object code has been compiled for the `interactive-session`.
+
At any time you can use the command :ghci-cmd:`:show modules` to get a list of
the modules currently loaded into GHCi:
@@ -301,8 +305,8 @@ So let's try compiling one of the other modules:
.. code-block:: none
- *ghci> :! ghc -c C.hs
- *ghci> :load A
+ *ghci> :! ghc -c -this-unit-id interactive-session -dynamic C.hs
+ *ghci> :load A B C D
Compiling D ( D.hs, interpreted )
Compiling B ( B.hs, interpreted )
Compiling C ( C.hs, interpreted )
@@ -316,7 +320,7 @@ rejected ``C``\'s object file. Ok, so let's also compile ``D``:
.. code-block:: none
- *ghci> :! ghc -c D.hs
+ *ghci> :! ghc -c -this-unit-id interactive-session -dynamic D.hs
*ghci> :reload
Ok, modules loaded: A, B, C, D.
@@ -325,7 +329,7 @@ picked up by :ghci-cmd:`:reload`, only :ghci-cmd:`:load`:
.. code-block:: none
- *ghci> :load A
+ *ghci> :load A B C D
Compiling B ( B.hs, interpreted )
Compiling A ( A.hs, interpreted )
Ok, modules loaded: A, B, C (C.o), D (D.o).
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -113,6 +113,7 @@ import GHC.Utils.Misc
import qualified GHC.LanguageExtensions as LangExt
import qualified GHC.Data.Strict as Strict
import GHC.Types.Error
+import qualified GHC.Unit.Home.Graph as HUG
-- Haskell Libraries
import System.Console.Haskeline as Haskeline
@@ -129,6 +130,7 @@ import Data.Array
import qualified Data.ByteString.Char8 as BS
import Data.Char
import Data.Function
+import qualified Data.Foldable as Foldable
import Data.IORef ( IORef, modifyIORef, newIORef, readIORef, writeIORef )
import Data.List ( find, intercalate, intersperse,
isPrefixOf, isSuffixOf, nub, partition, sort, sortBy, (\\) )
@@ -204,31 +206,31 @@ ghciCommands = map mkCmd [
-- Hugs users are accustomed to :e, so make sure it doesn't overlap
("?", keepGoing help, noCompletion),
("add", keepGoingPaths addModule, completeFilename),
- ("abandon", keepGoing abandonCmd, noCompletion),
- ("break", keepGoing breakCmd, completeBreakpoint),
- ("back", keepGoing backCmd, noCompletion),
+ ("abandon", keepGoing abandonCmd, noCompletion),
+ ("break", keepGoing breakCmd, completeBreakpoint),
+ ("back", keepGoing backCmd, noCompletion),
("browse", keepGoing' (browseCmd False), completeModule),
("browse!", keepGoing' (browseCmd True), completeModule),
- ("cd", keepGoingMulti' changeDirectory, completeFilename),
- ("continue", keepGoing continueCmd, noCompletion),
+ ("cd", keepGoing' changeDirectory, completeFilename),
+ ("continue", keepGoing' continueCmd, noCompletion),
("cmd", keepGoing cmdCmd, completeExpression),
("def", keepGoing (defineMacro False), completeExpression),
("def!", keepGoing (defineMacro True), completeExpression),
("delete", keepGoing deleteCmd, noCompletion),
("disable", keepGoing disableCmd, noCompletion),
("doc", keepGoing' docCmd, completeIdentifier),
- ("edit", keepGoingMulti' editFile, completeFilename),
+ ("edit", keepGoing' editFile, completeFilename),
("enable", keepGoing enableCmd, noCompletion),
("force", keepGoing forceCmd, completeExpression),
("forward", keepGoing forwardCmd, noCompletion),
- ("help", keepGoingMulti help, noCompletion),
- ("history", keepGoingMulti historyCmd, noCompletion),
- ("info", keepGoingMulti' (info False), completeIdentifier),
- ("info!", keepGoingMulti' (info True), completeIdentifier),
+ ("help", keepGoing help, noCompletion),
+ ("history", keepGoing historyCmd, noCompletion),
+ ("info", keepGoing' (info False), completeIdentifier),
+ ("info!", keepGoing' (info True), completeIdentifier),
("issafe", keepGoing' isSafeCmd, completeModule),
("ignore", keepGoing ignoreCmd, noCompletion),
- ("kind", keepGoingMulti' (kindOfType False), completeIdentifier),
- ("kind!", keepGoingMulti' (kindOfType True), completeIdentifier),
+ ("kind", keepGoing' (kindOfType False), completeIdentifier),
+ ("kind!", keepGoing' (kindOfType True), completeIdentifier),
("load", keepGoingPaths loadModule_, completeHomeModuleOrFile),
("load!", keepGoingPaths loadModuleDefer, completeHomeModuleOrFile),
("list", keepGoing' listCmd, noCompletion),
@@ -236,19 +238,19 @@ ghciCommands = map mkCmd [
("main", keepGoing runMain, completeFilename),
("print", keepGoing printCmd, completeExpression),
("quit", quit, noCompletion),
- ("reload", keepGoingMulti' reloadModule, noCompletion),
- ("reload!", keepGoingMulti' reloadModuleDefer, noCompletion),
- ("run", keepGoing runRun, completeFilename),
+ ("reload", keepGoing' reloadModule, noCompletion),
+ ("reload!", keepGoing' reloadModuleDefer, noCompletion),
+ ("run", keepGoing' runRun, completeFilename),
("script", keepGoing' scriptCmd, completeFilename),
- ("set", keepGoingMulti setCmd, completeSetOptions),
- ("seti", keepGoingMulti setiCmd, completeSeti),
- ("show", keepGoingMulti' showCmd, completeShowOptions),
- ("showi", keepGoing showiCmd, completeShowiOptions),
+ ("set", keepGoing setCmd, completeSetOptions),
+ ("seti", keepGoing setiCmd, completeSeti),
+ ("show", keepGoing' showCmd, completeShowOptions),
+ ("showi", keepGoing showiCmd, completeShowiOptions),
("sprint", keepGoing sprintCmd, completeExpression),
("step", keepGoing stepCmd, completeIdentifier),
("steplocal", keepGoing stepLocalCmd, completeIdentifier),
("stepmodule",keepGoing stepModuleCmd, completeIdentifier),
- ("type", keepGoingMulti' typeOfExpr, completeExpression),
+ ("type", keepGoing' typeOfExpr, completeExpression),
("trace", keepGoing traceCmd, completeExpression),
("unadd", keepGoingPaths unAddModule, completeFilename),
("undef", keepGoing undefineMacro, completeMacro),
@@ -316,24 +318,11 @@ showSDocForUserQualify doc = do
keepGoing :: (String -> GHCi ()) -> (String -> InputT GHCi CmdExecOutcome)
keepGoing a str = keepGoing' (lift . a) str
-keepGoingMulti :: (String -> GHCi ()) -> (String -> InputT GHCi CmdExecOutcome)
-keepGoingMulti a str = keepGoingMulti' (lift . a) str
-
keepGoing' :: GhciMonad m => (a -> m ()) -> a -> m CmdExecOutcome
keepGoing' a str = do
- in_multi <- inMultiMode
- if in_multi
- then reportError GhciCommandNotSupportedInMultiMode
- else a str
+ a str
return CmdSuccess
--- For commands which are actually support in multi-mode, initially just :reload
-keepGoingMulti' :: GhciMonad m => (String -> m ()) -> String -> m CmdExecOutcome
-keepGoingMulti' a str = a str >> return CmdSuccess
-
-inMultiMode :: GhciMonad m => m Bool
-inMultiMode = multiMode <$> getGHCiState
-
keepGoingPaths :: ([FilePath] -> InputT GHCi ()) -> (String -> InputT GHCi CmdExecOutcome)
keepGoingPaths a str
= do case toArgsNoLoc str of
@@ -489,9 +478,6 @@ default_args = []
interactiveUI :: GhciSettings -> [(FilePath, Maybe UnitId, Maybe Phase)] -> Maybe [String]
-> Ghc ()
interactiveUI config srcs maybe_exprs = do
- -- This is a HACK to make sure dynflags are not overwritten when setting
- -- options. When GHCi is made properly multi component it should be removed.
- modifySession (\env -> hscSetActiveUnitId (hscActiveUnitId env) env)
-- HACK! If we happen to get into an infinite loop (eg the user
-- types 'let x=x in x' at the prompt), then the thread will block
-- on a blackhole, and become unreachable during GC. The GC will
@@ -507,21 +493,7 @@ interactiveUI config srcs maybe_exprs = do
-- Initialise buffering for the *interpreted* I/O system
(nobuffering, flush) <- runInternal initInterpBuffering
- -- The initial set of DynFlags used for interactive evaluation is the same
- -- as the global DynFlags, plus -XExtendedDefaultRules and
- -- -XNoMonomorphismRestriction.
- -- See Note [Changing language extensions for interactive evaluation] #10857
- dflags <- getDynFlags
- let dflags' = (xopt_set_unlessExplSpec
- LangExt.ExtendedDefaultRules xopt_set)
- . (xopt_set_unlessExplSpec
- LangExt.MonomorphismRestriction xopt_unset)
- $ dflags
- GHC.setInteractiveDynFlags dflags'
- _ <- GHC.setProgramDynFlags
- -- Set Opt_KeepGoing so that :reload loads as much as
- -- possible
- (gopt_set dflags Opt_KeepGoing)
+ installInteractiveHomeUnits
-- Update the LogAction. Ensure we don't override the user's log action lest
-- we break -ddump-json (#14078)
@@ -553,9 +525,6 @@ interactiveUI config srcs maybe_exprs = do
case simpleImportDecl preludeModuleName of
-- Set to True because Prelude is implicitly imported.
impDecl@ImportDecl{ideclExt=ext} -> impDecl{ideclExt = ext{ideclImplicit=True}}
- hsc_env <- GHC.getSession
- let !in_multi = length (hsc_all_home_unit_ids hsc_env) > 1
- -- We force this to make sure we don't retain the hsc_env when reloading
empty_cache <- liftIO newIfaceCache
startGHCi (runGHCi srcs maybe_exprs)
GHCiState{ progname = default_progname,
@@ -566,7 +535,6 @@ interactiveUI config srcs maybe_exprs = do
stop = default_stop,
editor = default_editor,
options = [],
- multiMode = in_multi,
localConfig = SourceLocalConfig,
-- We initialize line number as 0, not 1, because we use
-- current line number while reporting errors which is
@@ -595,6 +563,236 @@ interactiveUI config srcs maybe_exprs = do
return ()
+{-
+Note [Multiple Home Units aware GHCi]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+GHCi supports multiple home units natively and as a first class citizen.
+All GHCi sessions use a multiple home unit session and have at least three
+home units:
+
+1. A home unit for the ghci session prompt
+2. A home unit for scripts (i.e., modules that are ':load'ed or ':add'ed.)
+3. The home unit specified by the user.
+3+. If the users themselves provides more than one home unit.
+
+The first home unit is the "interactive-ghci" unit, called the 'interactiveGhciUnit'.
+It contains the same 'DynFlags' that are used by the 'InteractiveContext' for
+interactive evaluation of expressions.
+This 'HomeUnitEnv' is only used on the prompt of GHCi, so we may refer to it as
+"interactive-prompt" unit.
+See Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+for discussing its role.
+
+The second home unit is the "interactive-session", called 'interactiveSessionUnit'
+which is used for loading Scripts into GHCi that are not 'Target's of any home unit,
+via `:load` or `:add`.
+This home unit is necessary, as we can't guess to which home unit the 'Target' should
+be added.
+
+Both of these "interactive" home units depend on all other 'HomeUnitEnv's that
+are passed as arguments on the cli.
+Additionally, the "interactive-ghci" unit depends on "interactive-session".
+
+We always evaluate expressions in the context of the
+"interactive-ghci" session.
+Since "interactive-ghci" depends on all home units, we can import any 'Module'
+from the other home units with ease.
+
+As we have a clear 'HomeUnitGraph' hierarchy, we can set 'interactiveGhciUnitId'
+as the active home unit for the full duration of the GHCi session.
+In GHCi, we always set 'interactiveGhciUnitId' to be the currently active home unit.
+
+=== Single Home Unit Case Diagram
+
+ Example: ghci -this-unit-id main ...
+ Equivalent to: ghci -unit @unitA
+
+ ┌───────────────────┐ ┌─────────────────────┐
+ │ Interactive Prompt│ │ Interactive Session │
+ │ │───────►│ │
+ │ interactive-ghci │ │ interactive-session │
+ └────────┬──────────┘ └──────────┬──────────┘
+ │ │
+ └───────────────┬──────────────┘
+ │
+ │
+ ┌────▼───┐
+ │ Unit A │
+ │ main │
+ └────────┘
+
+
+=== Multi Home Unit Case Diagram
+
+ Example: ghci -unit @unitA -unit @unitB -unit @unitC
+
+ ┌───────────────────┐ ┌─────────────────────┐
+ │ Interactive Prompt│ │ Interactive Session │
+ │ │───────►│ │
+ │ interactive-ghci │ │ interactive-session │
+ └────────┬──────────┘ └──────────┬──────────┘
+ │ │
+ └───────────────┬──────────────┘
+ │
+ ┌─────────────┼─────────────┐
+ ┌────▼───┐ ┌────▼───┐ ┌────▼───┐
+ │ Unit A │ │ Unit B │ │ Unit C │
+ │ a-0.0 │ │ b-0.0 │ │ c-0.0 │
+ └────────┘ └────────┘ └────────┘
+
+As we can see, this design scales to an arbitrary number of Home Units.
+
+=== 'interactiveGhciUnit' Home Unit
+
+The 'interactiveGhciUnit' home unit is used for storing the 'DynFlags' of
+the interactive context.
+There is considerable overlap with the 'InteractiveContext,
+see Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+for details.
+
+The 'DynFlags' of the 'interactiveGhciUnit' can be modified by using `:seti`
+commands in the GHCi session.
+
+=== 'interactiveSessionUnit' Home Unit
+
+The 'interactiveSessionUnit' home unit is used as a kitchen sink for Modules that
+are not part of a home unit already.
+When the user types ":load", it is not trivial to figure to which home unit the module
+should be added to.
+Especially, when there is more than home unit. Thus, we always ":load"ed modules
+to this home unit.
+
+The 'DynFlags' of the 'interactiveSessionUnit' can be modified via the ':set'
+commands in the GHCi session.
+-}
+
+-- | Set up the multiple home unit session.
+-- Installs a 'HomeUnitEnv' for the ghci-prompt and one for the ghci-session in the
+-- current 'HscEnv'.
+--
+-- Installs the two home units 'interactiveGhciUnit' and 'interactiveSessionUnit', which
+-- both depend on any other 'HomeUnitEnv' that is already present in the current
+-- 'HomeUnitGraph'.
+--
+-- In other words, in each GHCi session, there are always at least three 'HomeUnitEnv's:
+--
+-- * 'interactiveGhciUnit'
+-- * 'interactiveSessionUnit'
+-- * 'mainUnit' (by default)
+--
+-- The 'interactiveGhciUnit' is the currently active unit, i.e. @hscActiveUnit hsc_env == 'interactiveGhciUnitId'@,
+-- and it stays as the active unit for the entire duration of GHCi.
+-- Within GHCi, you can rely on this property.
+--
+-- For motivation and design, see Note [Multiple Home Units aware GHCi]
+installInteractiveHomeUnits :: GHC.GhcMonad m => m ()
+installInteractiveHomeUnits = do
+ logger <- getLogger
+ hsc_env <- GHC.getSession
+ -- The initial set of DynFlags used for interactive evaluation is the same
+ -- as the global DynFlags, plus:
+ -- * -XExtendedDefaultRules and
+ -- * -XNoMonomorphismRestriction.
+ -- See Note [Changing language extensions for interactive evaluation] #10857
+ dflags <- getDynFlags
+ let
+ dflags0' =
+ (xopt_set_unlessExplSpec LangExt.ExtendedDefaultRules xopt_set) .
+ (xopt_set_unlessExplSpec LangExt.MonomorphismRestriction xopt_unset) $
+ dflags
+ -- Disable warnings about unused packages
+ -- It doesn't matter for the interactive session.
+ -- See Note [No unused package warnings for the interactive session]
+ dflags0 = wopt_unset dflags0' Opt_WarnUnusedPackages
+
+ -- Trivial '-package-id <uid>' flag
+ homeUnitPkgFlag uid =
+ ExposePackage
+ (unitIdString uid)
+ (UnitIdArg $ RealUnit (Definite uid))
+ (ModRenaming False [])
+
+ sessionUnitExposedFlag =
+ homeUnitPkgFlag interactiveSessionUnitId
+
+ -- Explicitly depends on all home units and 'sessionUnitExposedFlag'.
+ -- Normalise the 'dflagsPrompt', as they will be used for 'ic_dflags'
+ -- of the 'InteractiveContext'.
+ -- See Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+ -- Additionally, we remove all 'importPaths', to avoid accidentally adding
+ -- any 'Target's to this 'Unit'.
+ dflagsPrompt <- GHC.normaliseInteractiveDynFlags logger $
+ setHomeUnitId interactiveGhciUnitId $ dflags0
+ { packageFlags =
+ [ sessionUnitExposedFlag ] ++
+ [ homeUnitPkgFlag uid
+ | homeUnitEnv <- Foldable.toList $ hsc_HUG hsc_env
+ , Just homeUnit <- [homeUnitEnv_home_unit homeUnitEnv]
+ , let uid = homeUnitId homeUnit
+ ] ++
+ (packageFlags dflags0)
+ , importPaths = []
+ }
+
+ let
+ -- Explicitly depends on all current home units.
+ -- Additionally, we remove all 'importPaths', to avoid accidentally adding
+ -- any 'Target's to this 'Unit' that are not ':load'ed.
+ dflagsSession =
+ setHomeUnitId interactiveSessionUnitId $ dflags
+ { packageFlags =
+ [ homeUnitPkgFlag uid
+ | homeUnitEnv <- Foldable.toList $ hsc_HUG hsc_env
+ , Just homeUnit <- [homeUnitEnv_home_unit homeUnitEnv]
+ , let uid = homeUnitId homeUnit
+ ] ++
+ (packageFlags dflags)
+ , importPaths = []
+ }
+
+ let
+ cached_unit_dbs =
+ concat
+ . catMaybes
+ . fmap homeUnitEnv_unit_dbs
+ $ Foldable.toList
+ $ hsc_HUG hsc_env
+
+ all_unit_ids =
+ S.insert interactiveGhciUnitId $
+ S.insert interactiveSessionUnitId $
+ hsc_all_home_unit_ids hsc_env
+
+ ghciPromptUnit <- setupHomeUnitFor logger dflagsPrompt all_unit_ids cached_unit_dbs
+ ghciSessionUnit <- setupHomeUnitFor logger dflagsSession all_unit_ids cached_unit_dbs
+ let
+ -- Setup up the HUG, install the interactive home units
+ withInteractiveUnits =
+ HUG.unitEnv_insert interactiveGhciUnitId ghciPromptUnit
+ . HUG.unitEnv_insert interactiveSessionUnitId ghciSessionUnit
+
+ -- Finish up the setup, install the new HUG and make the 'interactiveGhciUnitId'
+ -- the active unit.
+ modifySessionM (\env -> do
+ -- Set the new HUG
+ let newEnv0 = hscUpdateHUG withInteractiveUnits env
+ -- Make sure the 'interactiveGhciUnitId' is active and 'hsc_dflags'
+ -- are populated correctly.
+ -- The 'interactiveGhciUnitId' will stay as the active unit within GHCi.
+ let newEnv1 = hscSetActiveUnitId interactiveGhciUnitId newEnv0
+ -- Use the 'DynFlags' of the 'interactiveGhciUnitId' for the 'InteractiveContext'.
+ GHC.initialiseInteractiveDynFlags dflagsPrompt newEnv1
+ )
+
+ pure ()
+ where
+ setupHomeUnitFor :: GHC.GhcMonad m => Logger -> DynFlags -> S.Set UnitId -> [UnitDatabase UnitId] -> m HomeUnitEnv
+ setupHomeUnitFor logger dflags all_home_units cached_unit_dbs = do
+ (dbs,unit_state,home_unit,_mconstants) <-
+ liftIO $ initUnits logger dflags (Just cached_unit_dbs) all_home_units
+ hpt <- liftIO emptyHomePackageTable
+ pure (HUG.mkHomeUnitEnv unit_state (Just dbs) dflags hpt (Just home_unit))
+
reportError :: GhciMonad m => GhciCommandMessage -> m ()
reportError err = do
printError err
@@ -933,7 +1131,7 @@ getInfoForPrompt = do
| otherwise = unLoc (ideclName d)
modules_names =
- ['*':(moduleNameString m) | IIModule m <- rev_imports] ++
+ ['*':(moduleNameString (moduleName m)) | IIModule m <- rev_imports] ++
[moduleNameString (myIdeclName d) | IIDecl d <- rev_imports]
line = 1 + line_number st
@@ -1971,13 +2169,27 @@ wrapDeferTypeErrors :: GHC.GhcMonad m => m a -> m a
wrapDeferTypeErrors load =
MC.bracket
(do
- -- Force originalFlags to avoid leaking the associated HscEnv
- !originalFlags <- getDynFlags
- void $ GHC.setProgramDynFlags $
- setGeneralFlag' Opt_DeferTypeErrors originalFlags
- return originalFlags)
- (\originalFlags -> void $ GHC.setProgramDynFlags originalFlags)
+ -- Force originalHUG to avoid leaking the associated HscEnv
+ !originalHUG <- hsc_HUG <$> GHC.getSession
+ _ <- GHC.setProgramHUG (fmap deferTypeErrors originalHUG)
+ return originalHUG)
+ (\originalHUG ->
+ -- Restore the old 'DynFlags' for each home unit.
+ -- This makes sure that '-fdefer-type-errors' is unset again, iff it wasn't set before.
+ modifySession (hscUpdateHUG (restoreOriginalDynFlags originalHUG)))
(\_ -> load)
+ where
+ deferTypeErrors home_unit_env =
+ home_unit_env
+ { homeUnitEnv_dflags =
+ setGeneralFlag' Opt_DeferTypeErrors (homeUnitEnv_dflags home_unit_env)
+ }
+
+ restoreOriginalDynFlags (HUG.UnitEnvGraph old) (HUG.UnitEnvGraph new) = HUG.UnitEnvGraph $
+ M.unionWith (\b a ->
+ a { homeUnitEnv_dflags = homeUnitEnv_dflags b
+ })
+ old new
loadModule :: GhciMonad m => [(FilePath, Maybe UnitId, Maybe Phase)] -> m SuccessFlag
loadModule fs = do
@@ -1986,7 +2198,7 @@ loadModule fs = do
-- | @:load@ command
loadModule_ :: GhciMonad m => [FilePath] -> m ()
-loadModule_ fs = void $ loadModule (zip3 fs (repeat Nothing) (repeat Nothing))
+loadModule_ fs = void $ loadModule (zip3 fs (repeat (Just interactiveSessionUnitId)) (repeat Nothing))
loadModuleDefer :: GhciMonad m => [FilePath] -> m ()
loadModuleDefer = wrapDeferTypeErrors . loadModule_
@@ -2030,7 +2242,8 @@ addModule :: GhciMonad m => [FilePath] -> m ()
addModule files = do
revertCAFs -- always revert CAFs on load/add.
files' <- mapM expandPath files
- targets <- mapM (\m -> GHC.guessTarget m Nothing Nothing) files'
+ -- New targets are always added to the 'interactiveSessionUnitId' 'HomeUnitEnv'.
+ targets <- mapM (\m -> GHC.guessTarget m (Just interactiveSessionUnitId) Nothing) files'
targets' <- filterM checkTarget targets
-- remove old targets with the same id; e.g. for :add *M
mapM_ GHC.removeTarget [ tid | Target { targetId = tid } <- targets' ]
@@ -2063,7 +2276,8 @@ addModule files = do
unAddModule :: GhciMonad m => [FilePath] -> m ()
unAddModule files = do
files' <- mapM expandPath files
- targets <- mapM (\m -> GHC.guessTarget m Nothing Nothing) files'
+ -- New targets are always added to the 'interactiveSessionUnitId' 'HomeUnitEnv'.
+ targets <- mapM (\m -> GHC.guessTarget m (Just interactiveSessionUnitId) Nothing) files'
let removals = [ tid | Target { targetId = tid } <- targets ]
mapM_ GHC.removeTarget removals
_ <- doLoadAndCollectInfo (Unadd $ length removals) LoadAllTargets
@@ -2102,10 +2316,7 @@ doLoadAndCollectInfo load_type howmuch = do
doLoad load_type howmuch >>= \case
Succeeded | doCollectInfo -> do
mod_summaries <- GHC.mgModSummaries <$> getModuleGraph
- -- MP: :set +c code path only works in single package mode atm, hence
- -- this call to isLoaded is ok. collectInfo needs to be modified further to
- -- work with :set +c so I have punted on that for now.
- loaded <- filterM GHC.isLoaded (map ms_mod_name mod_summaries)
+ loaded <- filterM GHC.isLoadedHomeModule (map ms_mod mod_summaries)
v <- mod_infos <$> getGHCiState
!newInfos <- collectInfo v loaded
modifyGHCiState (\st -> st { mod_infos = newInfos })
@@ -2187,7 +2398,7 @@ setContextAfterLoad keep_ctxt (Just graph) = do
-- We import the module with a * iff
-- - it is interpreted, and
-- - -XSafe is off (it doesn't allow *-imports)
- let new_ctx | star_ok = [mkIIModule (GHC.moduleName m)]
+ let new_ctx | star_ok = [mkIIModule m]
| otherwise = [mkIIDecl (GHC.moduleName m)]
setContextKeepingPackageModules keep_ctxt new_ctx
@@ -2222,9 +2433,10 @@ keepPackageImports = filterM is_pkg_import
is_pkg_import (IIDecl d)
= do pkgqual <- GHC.renameRawPkgQualM mod_name (ideclPkgQual d)
e <- MC.try $ GHC.findQualifiedModule pkgqual mod_name
+ hug <- hsc_HUG <$> GHC.getSession
case e :: Either SomeException Module of
Left _ -> return False
- Right m -> return (not (isMainUnitModule m))
+ Right m -> return $ not (HUG.memberHugUnit (moduleUnit m) hug)
where
mod_name = unLoc (ideclName d)
@@ -2607,7 +2819,7 @@ guessCurrentModule cmd = do
imports <- GHC.getContext
case imports of
[] -> throwGhcException $ CmdLineError (':' : cmd ++ ": no current module")
- IIModule m : _ -> GHC.findQualifiedModule NoPkgQual m
+ IIModule m : _ -> pure m
IIDecl d : _ -> do
pkgqual <- GHC.renameRawPkgQualM (unLoc $ ideclName d) (ideclPkgQual d)
GHC.findQualifiedModule pkgqual (unLoc (ideclName d))
@@ -2628,7 +2840,7 @@ browseModule bang modl exports_only = do
then pure $ GHC.modInfoExports mod_info
else do
hsc_env <- GHC.getSession
- mmod_env <- liftIO $ mkTopLevEnv hsc_env (moduleName modl)
+ mmod_env <- liftIO $ mkTopLevEnv hsc_env modl
case mmod_env of
Left err -> throwGhcException (CmdLineError (GHC.moduleNameString (GHC.moduleName modl) ++ " " ++ err))
Right mod_env -> pure $ map greName . globalRdrEnvElts $ mod_env
@@ -2737,8 +2949,9 @@ addModulesToContext starred unstarred = restoreContextOnFailure $ do
addModulesToContext_ :: GhciMonad m => [ModuleName] -> [ModuleName] -> m ()
addModulesToContext_ starred unstarred = do
- mapM_ addII (map mkIIModule starred ++ map mkIIDecl unstarred)
- setGHCContextFromGHCiState
+ starredModules <- traverse lookupModuleName starred
+ mapM_ addII (map mkIIModule starredModules ++ map mkIIDecl unstarred)
+ setGHCContextFromGHCiState
remModulesFromContext :: GhciMonad m => [ModuleName] -> [ModuleName] -> m ()
remModulesFromContext starred unstarred = do
@@ -2804,14 +3017,14 @@ checkAdd ii = do
dflags <- getDynFlags
let safe = safeLanguageOn dflags
case ii of
- IIModule modname
+ IIModule mod
| safe -> throwGhcException $ CmdLineError "can't use * imports with Safe Haskell"
- | otherwise -> wantInterpretedModuleName modname >> return ()
+ | otherwise -> checkInterpretedModule mod >> return ()
IIDecl d -> do
let modname = unLoc (ideclName d)
pkgqual <- GHC.renameRawPkgQualM modname (ideclPkgQual d)
- m <- GHC.lookupQualifiedModule pkgqual modname
+ m <- lookupQualifiedModuleName pkgqual modname
when safe $ do
t <- GHC.isModuleTrusted m
unless t $ throwGhcException $ ProgramError $ ""
@@ -2874,13 +3087,13 @@ getImplicitPreludeImports iidecls = do
-- -----------------------------------------------------------------------------
-- Utils on InteractiveImport
-mkIIModule :: ModuleName -> InteractiveImport
+mkIIModule :: Module -> InteractiveImport
mkIIModule = IIModule
mkIIDecl :: ModuleName -> InteractiveImport
mkIIDecl = IIDecl . simpleImportDecl
-iiModules :: [InteractiveImport] -> [ModuleName]
+iiModules :: [InteractiveImport] -> [Module]
iiModules is = [m | IIModule m <- is]
isIIModule :: InteractiveImport -> Bool
@@ -2888,7 +3101,7 @@ isIIModule (IIModule _) = True
isIIModule _ = False
iiModuleName :: InteractiveImport -> ModuleName
-iiModuleName (IIModule m) = m
+iiModuleName (IIModule m) = moduleName m
iiModuleName (IIDecl d) = unLoc (ideclName d)
preludeModuleName :: ModuleName
@@ -2990,8 +3203,23 @@ showOptions show_all
then text "none."
else hsep (map (\o -> char '+' <> text (optToStr o)) opts)
))
- liftIO $ showDynFlags show_all dflags
-
+ mapNonInteractiveHomeUnitsM (liftIO . showDynFlags show_all)
+
+mapNonInteractiveHomeUnitsM :: GHC.GhcMonad m => (DynFlags -> m ()) -> m ()
+mapNonInteractiveHomeUnitsM printer = do
+ hug <- hsc_HUG <$> GHC.getSession
+ singleOrMultipleHomeUnits
+ $ map (\(uid, homeUnit) -> (uid, homeUnitEnv_dflags homeUnit))
+ $ filter (\(uid, _) -> uid /= interactiveSessionUnitId
+ && uid /= interactiveGhciUnitId)
+ $ HUG.unitEnv_assocs hug
+ where
+ singleOrMultipleHomeUnits [] =
+ liftIO $ putStrLn "GHCi: internal error - no home unit configured"
+ singleOrMultipleHomeUnits [(_, dflags)] = printer dflags
+ singleOrMultipleHomeUnits xs = mapM_ (\(uid, dflags) -> do
+ liftIO $ putStrLn (showSDoc dflags (text "Unit ID:" <+> ppr uid))
+ printer dflags) xs
showDynFlags :: Bool -> DynFlags -> IO ()
showDynFlags show_all dflags = do
@@ -3117,69 +3345,206 @@ setOptions wds =
-- then, dynamic flags
when (not (null minus_opts)) $ newDynFlags False minus_opts
--- | newDynFlags will *not* read package environment files, therefore we
--- use 'parseDynamicFlagsCmdLine' rather than 'parseDynamicFlags'. This
--- function is called very often and results in repeatedly loading
--- environment files (see #19650)
+-- Note [No unused package warnings for the interactive session]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- The interactive session (also called "interactive-prompt" occassionally) should not
+-- report unused packages, as it will essentially always report packages
+-- as unused.
+-- The "interactive-prompt" doesn't contain any 'Module's, so most packages
+-- are unused.
+-- As this would flood the user with warnings they can't do anything about,
+-- we decide to unconditionally turn off the warning 'Opt_WarnUnusedPackages'.
+--
+-- Unused packages in GHCi are still reported via the 'interactive-session' unit.
+-- See Note [Multiple Home Units aware GHCi] for an explanation about the
+-- "interactive-prompt" and 'interactive-session' unit.
+
+-- | 'newDynFlags' adds the given user options to the session.
+--
+-- If 'True' is passed, we add the options only to the interactive 'DynFlags'.
+-- Otherwise, the options are added to each 'HomeUnitEnv' in the current session.
+--
+-- This function will check whether we need to re-initialise the 'UnitState',
+-- for example when the user writes ':set -package containers'.
+--
+-- Any warnings during parsing, or validation of the new 'DynFlags' will be
+-- directly reported to the user.
newDynFlags :: GhciMonad m => Bool -> [String] -> m ()
newDynFlags interactive_only minus_opts = do
- let lopts = map noLoc minus_opts
+ let lopts = map noLoc minus_opts
- logger <- getLogger
- idflags0 <- GHC.getInteractiveDynFlags
- (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts
+ case interactive_only of
+ True -> addToInteractiveDynFlags lopts
+ False -> addToProgramDynFlags lopts
- liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns)
+ idflags <- hsc_dflags <$> GHC.getSession
+ installInteractivePrint (interactivePrint idflags) False
+
+-- | Add the given options to the interactive 'DynFlags'.
+-- This function will normalise and validate the 'DynFlags' and report warnings
+-- directly to the user.
+--
+-- Updates both the 'hsc_dflags' of 'HscEnv', and the 'ic_dflags' of the 'InteractiveContext'.
+--
+-- 'addToInteractiveDynFlags' will *not* read package environment files, therefore we
+-- use 'parseDynamicFlagsCmdLine' rather than 'parseDynamicFlags'. This
+-- function is called very often and results in repeatedly loading
+-- environment files (see #19650)
+addToInteractiveDynFlags :: GhciMonad m => [Located String] -> m ()
+addToInteractiveDynFlags lopts = do
+ logger <- getLogger
+ env <- GHC.getSession
+ let idflags0 = hsc_dflags env
+ (idflags1, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger idflags0 lopts
+
+ liftIO $ printOrThrowDiagnostics logger (initPrintConfig idflags1) (initDiagOpts idflags1) (GhcDriverMessage <$> warns)
+ when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers)
+
+ when (packageFlagsChanged idflags1 idflags0) $ do
+ liftIO $ hPutStrLn stderr "cannot set package flags with :seti; use :set"
+
+ idflags_norm <- GHC.normaliseInteractiveDynFlags logger idflags1
+ -- Strictly speaking, 'setProgramHUG' performs more work than necessary,
+ -- as we know the majority of flags haven't changed.
+ _ <- GHC.setProgramHUG (hsc_HUG $ hscSetFlags idflags_norm env)
+ -- Initialise the Interactive DynFlags.
+ -- Sets the 'ic_dflags' and initialises the 'ic_plugins'.
+ -- See Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+ idflags <- hsc_dflags <$> GHC.getSession
+ modifySessionM (GHC.initialiseInteractiveDynFlags idflags)
+
+-- | Add the given options to all 'DynFlags' in the 'HomeUnitGraph'.
+-- This function will validate the 'DynFlags' and report warnings directly to the user.
+--
+-- We additionally normalise the 'DynFlags' for the 'interactiveGhciUnitId' for use
+-- in the 'InteractiveContext'.
+--
+-- 'addToProgramDynFlags' will *not* read package environment files, therefore we
+-- use 'parseDynamicFlagsCmdLine' rather than 'parseDynamicFlags'. This
+-- function is called very often and results in repeatedly loading
+-- environment files (see #19650)
+addToProgramDynFlags :: GhciMonad m => [Located String] -> m ()
+addToProgramDynFlags lopts = do
+ logger <- getLogger
+ initial_hug <- hsc_HUG <$> GHC.getSession
+ -- Update the 'DynFlags' of each 'HomeUnitEnv'.
+ -- Parse the new 'DynFlags', and report potential issues once.
+ -- Arguably, we may want to report issues for each non-builtin 'HomeUnitEnv'
+ -- individually.
+ updates <- HUG.unitEnv_traverseWithKey (\uid homeUnitEnv -> do
+ let oldFlags = HUG.homeUnitEnv_dflags homeUnitEnv
+ (newFlags, leftovers, warns) <- DynFlags.parseDynamicFlagsCmdLine logger oldFlags lopts
+ -- We only want to report inconsistencies and warnings once.
+ -- Thus, we do it only once for the 'interactiveGhciUnitId'
+ when (uid == interactiveGhciUnitId) $ do
+ liftIO $ printOrThrowDiagnostics logger (initPrintConfig newFlags) (initDiagOpts newFlags) (GhcDriverMessage <$> warns)
when (not $ null leftovers) (unknownFlagsErr $ map unLoc leftovers)
- when (interactive_only && packageFlagsChanged idflags1 idflags0) $ do
- liftIO $ hPutStrLn stderr "cannot set package flags with :seti; use :set"
- GHC.setInteractiveDynFlags idflags1
- installInteractivePrint (interactivePrint idflags1) False
-
- dflags0 <- getDynFlags
-
- when (not interactive_only) $ do
- (dflags1, _, _) <- liftIO $ DynFlags.parseDynamicFlagsCmdLine logger dflags0 lopts
- must_reload <- GHC.setProgramDynFlags dflags1
-
- -- if the package flags changed, reset the context and link
- -- the new packages.
- hsc_env <- GHC.getSession
- let dflags2 = hsc_dflags hsc_env
- let interp = hscInterp hsc_env
- when (packageFlagsChanged dflags2 dflags0) $ do
- when (verbosity dflags2 > 0) $
- liftIO . putStrLn $
- "package flags have changed, resetting and loading new packages..."
- -- Clear caches and eventually defined breakpoints. (#1620)
- clearCaches
- when must_reload $ do
- let units = preloadUnits (hsc_units hsc_env)
- liftIO $ Loader.loadPackages interp hsc_env units
- -- package flags changed, we can't re-use any of the old context
- setContextAfterLoad False Nothing
- -- and copy the package flags to the interactive DynFlags
- idflags <- GHC.getInteractiveDynFlags
- GHC.setInteractiveDynFlags
- idflags{ packageFlags = packageFlags dflags2 }
-
- let ld0length = length $ ldInputs dflags0
- fmrk0length = length $ cmdlineFrameworks dflags0
-
- newLdInputs = drop ld0length (ldInputs dflags2)
- newCLFrameworks = drop fmrk0length (cmdlineFrameworks dflags2)
-
- dflags' = dflags2 { ldInputs = newLdInputs
- , cmdlineFrameworks = newCLFrameworks
- }
- hsc_env' = hscSetFlags dflags' hsc_env
-
- when (not (null newLdInputs && null newCLFrameworks)) $
- liftIO $ Loader.loadCmdLineLibs (hscInterp hsc_env') hsc_env'
-
- return ()
+ -- Special Logic!
+ -- Currently, the interactive 'DynFlags' have additional restrictions,
+ -- for example modifying package flags is not supported!
+ -- The interactive 'DynFlags' get normalised to uphold this restriction.
+ -- As a special precaution, we also don't want to report unusued packages warnings
+ -- for the interactive session.
+ -- See Note [No unused package warnings for the interactive session]
+ --
+ -- See Note [Multiple Home Units aware GHCi] for details about how
+ -- the interactive session is structured.
+ newFlags' <-
+ if uid == interactiveGhciUnitId
+ then do
+ -- See Note [No unused package warnings for the interactive session]
+ let icdflags1 = wopt_unset newFlags Opt_WarnUnusedPackages
+ GHC.normaliseInteractiveDynFlags logger icdflags1
+ else
+ pure newFlags
+ pure (homeUnitEnv { homeUnitEnv_dflags = newFlags' })
+ )
+ initial_hug
+ -- Update the HUG!
+ -- This might force us to reload the 'UnitState' of each 'HomeUnitEnv'
+ -- if package flags were changed.
+ must_reload <- GHC.setProgramHUG updates
+
+ -- Initialise the Interactive DynFlags.
+ -- Sets the 'ic_dflags' and initialises the 'ic_plugins'.
+ -- See Note [Relation between the 'InteractiveContext' and 'interactiveGhciUnitId']
+ icdflags <- hsc_dflags <$> GHC.getSession
+ modifySessionM (GHC.initialiseInteractiveDynFlags icdflags)
+
+ -- if the package flags changed, reset the context and link
+ -- the new packages.
+ hsc_env <- GHC.getSession
+ let dflags2 = hsc_dflags hsc_env
+ when must_reload $ do
+ when (verbosity dflags2 > 0) $
+ liftIO . putStrLn $
+ "package flags have changed, resetting and loading new packages..."
+
+ -- Clear caches and eventually defined breakpoints. (#1620)
+ clearCaches
+ reloadPackages hsc_env
+
+ reloadLinkerOptions hsc_env initial_hug
+
+reloadPackages :: GhciMonad m => HscEnv -> m ()
+reloadPackages hsc_env = do
+ let
+ units =
+ concatMap (preloadUnits . HUG.homeUnitEnv_units)
+ (Foldable.toList $ hsc_HUG hsc_env)
+ liftIO $ Loader.loadPackages (hscInterp hsc_env) hsc_env units
+ -- package flags changed, we can't re-use any of the old context
+ setContextAfterLoad False Nothing
+
+-- | Reload the linker options.
+--
+-- Synopsis: @'reloadLinkerOptions' hsc_env old_hug@
+--
+-- After the HUG is modified, the linker may need to be reloaded.
+-- The linker is reloaded via 'loadCmdLineLibs', if the library inputs
+-- have changed.
+-- To determine whether the library inputs have changed, we need the
+-- old HUG, which is passed as the argument 'old_hug'.
+--
+-- This function will crash, if the 'old_hug' doesn't have exactly
+-- the same keys has the given 'hsc_env'. I.e.
+--
+-- @
+-- HUG.unitEnv_keys old_hug == HUG.unitEnv_keys (hsc_HUG hsc_env)
+-- @
+reloadLinkerOptions :: MonadIO m => HscEnv -> HomeUnitGraph -> m ()
+reloadLinkerOptions hsc_env old_hug = do
+ let
+ new_hug = hsc_HUG hsc_env
+ let
+ (needs_updates, updated_hug) = HUG.unitEnv_traverseWithKey (\key unitEnv ->
+ let
+ old_flags = homeUnitEnv_dflags (HUG.unitEnv_lookup key old_hug)
+ new_flags = homeUnitEnv_dflags unitEnv
+ ld0length = length $ ldInputs old_flags
+ fmrk0length = length $ cmdlineFrameworks old_flags
+
+ newLdInputs = drop ld0length (ldInputs new_flags)
+ newCLFrameworks = drop fmrk0length (cmdlineFrameworks new_flags)
+
+ dflags' = new_flags { ldInputs = newLdInputs
+ , cmdlineFrameworks = newCLFrameworks
+ }
+ in
+ (S.Any (not (null newLdInputs && null newCLFrameworks)),
+ unitEnv { homeUnitEnv_dflags = dflags' })
+ ) new_hug
+
+ hsc_env' =
+ hscSetActiveUnitId (hscActiveUnitId hsc_env)
+ $ hscUpdateHUG (const updated_hug)
+ $ hsc_env
+
+ when (S.getAny needs_updates) $
+ liftIO $ Loader.loadCmdLineLibs (hscInterp hsc_env') hsc_env'
unknownFlagsErr :: GhciMonad m => [String] -> m ()
unknownFlagsErr fs = mapM_ (\f -> reportError (GhciUnknownFlag f (suggestions f))) fs
@@ -3261,7 +3626,6 @@ showCmd "" = showOptions False
showCmd "-a" = showOptions True
showCmd str = do
st <- getGHCiState
- dflags <- getDynFlags
hsc_env <- GHC.getSession
let lookupCmd :: String -> Maybe (m ())
@@ -3299,8 +3663,10 @@ showCmd str = do
case words str of
[w] | Just action <- lookupCmd w -> action
- _ -> let helpCmds = [ text name | (True, name, _) <- cmds ]
- in throwGhcException $ CmdLineError $ showSDoc dflags
+ _ -> do
+ let helpCmds = [ text name | (True, name, _) <- cmds ]
+ dflags <- getDynFlags
+ throwGhcException $ CmdLineError $ showSDoc dflags
$ hang (text "syntax:") 4
$ hang (text ":show") 6
$ brackets (fsep $ punctuate (text " |") helpCmds)
@@ -3321,7 +3687,7 @@ showImports = do
trans_ctx = transient_ctx st
show_one (IIModule star_m)
- = ":module +*" ++ moduleNameString star_m
+ = ":module +*" ++ moduleNameString (moduleName star_m)
show_one (IIDecl imp) = showPpr dflags imp
prel_iidecls <- getImplicitPreludeImports (rem_ctx ++ trans_ctx)
@@ -3427,16 +3793,14 @@ pprStopped res =
mb_mod_name = moduleName <$> ibi_tick_mod <$> GHC.resumeBreakpointId res
showUnits :: GHC.GhcMonad m => m ()
-showUnits = do
- dflags <- getDynFlags
+showUnits = mapNonInteractiveHomeUnitsM $ \dflags -> do
let pkg_flags = packageFlags dflags
liftIO $ putStrLn $ showSDoc dflags $
text ("active package flags:"++if null pkg_flags then " none" else "") $$
nest 2 (vcat (map pprFlag pkg_flags))
showPaths :: GHC.GhcMonad m => m ()
-showPaths = do
- dflags <- getDynFlags
+showPaths = mapNonInteractiveHomeUnitsM $ \dflags -> do
liftIO $ do
cwd <- getCurrentDirectory
putStrLn $ showSDoc dflags $
@@ -3448,7 +3812,7 @@ showPaths = do
nest 2 (vcat (map text ipaths))
showLanguages :: GHC.GhcMonad m => m ()
-showLanguages = getDynFlags >>= liftIO . showLanguages' False
+showLanguages = mapNonInteractiveHomeUnitsM $ liftIO . showLanguages' False
showiLanguages :: GHC.GhcMonad m => m ()
showiLanguages = GHC.getInteractiveDynFlags >>= liftIO . showLanguages' False
@@ -3627,11 +3991,11 @@ completeBreakpoint = wrapCompleter spaces $ \w -> do -- #3000
filterM GHC.moduleIsInterpreted hmods
-- Return all possible bids for a given Module
- bidsByModule :: GhciMonad m => [ModuleName] -> Module -> m [String]
+ bidsByModule :: GhciMonad m => [Module] -> Module -> m [String]
bidsByModule nonquals mod = do
(_, decls) <- getModBreak mod
let bids = nub $ declPath <$> elems decls
- pure $ case (moduleName mod) `elem` nonquals of
+ pure $ case mod `elem` nonquals of
True -> bids
False -> (combineModIdent (showModule mod)) <$> bids
@@ -4036,8 +4400,7 @@ breakSwitch (arg1:rest)
| all isDigit arg1 = do
imports <- GHC.getContext
case iiModules imports of
- (mn : _) -> do
- md <- lookupModuleName mn
+ (md : _) -> do
breakByModuleLine md (read arg1) rest
[] -> do
liftIO $ putStrLn "No modules are loaded with debugging support."
@@ -4169,8 +4532,7 @@ list2 [arg] | all isDigit arg = do
case iiModules imports of
[] -> liftIO $ putStrLn "No module to list"
(mn : _) -> do
- md <- lookupModuleName mn
- listModuleLine md (read arg)
+ listModuleLine mn (read arg)
list2 [arg1,arg2] | looksLikeModuleName arg1, all isDigit arg2 = do
md <- wantInterpretedModule arg1
listModuleLine md (read arg2)
@@ -4426,10 +4788,20 @@ lookupModule :: GHC.GhcMonad m => String -> m Module
lookupModule mName = lookupModuleName (GHC.mkModuleName mName)
lookupModuleName :: GHC.GhcMonad m => ModuleName -> m Module
-lookupModuleName mName = GHC.lookupQualifiedModule NoPkgQual mName
-
-isMainUnitModule :: Module -> Bool
-isMainUnitModule m = GHC.moduleUnit m == mainUnit
+lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
+
+lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
+lookupQualifiedModuleName qual modl = do
+ GHC.lookupAllQualifiedModuleNames qual modl >>= \case
+ [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [m] -> pure m
+ ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ where
+ str = moduleNameString modl
+ errorMsg ms = intercalate "\n"
+ [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
+ | m <- ms
+ ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
@@ -4476,15 +4848,19 @@ wantInterpretedModule str = wantInterpretedModuleName (GHC.mkModuleName str)
wantInterpretedModuleName :: GHC.GhcMonad m => ModuleName -> m Module
wantInterpretedModuleName modname = do
- modl <- lookupModuleName modname
- let str = moduleNameString modname
- home_unit <- hsc_home_unit <$> GHC.getSession
- unless (isHomeModule home_unit modl) $
- throwGhcException (CmdLineError ("module '" ++ str ++ "' is from another package;\nthis command requires an interpreted module"))
- is_interpreted <- GHC.moduleIsInterpreted modl
- when (not is_interpreted) $
- throwGhcException (CmdLineError ("module '" ++ str ++ "' is not interpreted; try \':add *" ++ str ++ "' first"))
- return modl
+ modl <- lookupModuleName modname
+ checkInterpretedModule modl
+
+checkInterpretedModule :: GHC.GhcMonad m => Module -> m Module
+checkInterpretedModule modl = do
+ let str = moduleNameString $ moduleName modl
+ hug <- hsc_HUG <$> GHC.getSession
+ unless (HUG.memberHugUnit (moduleUnit modl) hug) $
+ throwGhcException (CmdLineError ("module '" ++ str ++ "' is from another package;\nthis command requires an interpreted module"))
+ is_interpreted <- GHC.moduleIsInterpreted modl
+ when (not is_interpreted) $
+ throwGhcException (CmdLineError ("module '" ++ str ++ "' is not interpreted; try \':add *" ++ str ++ "' first"))
+ return modl
wantNameFromInterpretedModule :: GHC.GhcMonad m
=> (Name -> SDoc -> m ())
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -465,7 +465,7 @@ instance DiagnosticCodeNameSpace GHCi where
type GhciDiagnosticCode :: Symbol -> Nat
type family GhciDiagnosticCode c = n | n -> c where
- GhciDiagnosticCode "GhciCommandNotSupportedInMultiMode" = 83514
+ GhciDiagnosticCode "GhciCommandNotSupportedInMultiMode" = Outdated 83514
GhciDiagnosticCode "GhciInvalidArgumentString" = 68894
GhciDiagnosticCode "GhciCommandSyntaxError" = 72682
GhciDiagnosticCode "GhciInvalidPromptString" = 50882
=====================================
ghc/GHCi/UI/Info.hs
=====================================
@@ -113,7 +113,7 @@ srcSpanFilePath = unpackFS . srcSpanFile
-- | Try to find the location of the given identifier at the given
-- position in the module.
findLoc :: GhcMonad m
- => Map ModuleName ModInfo
+ => Map Module ModInfo
-> RealSrcSpan
-> String
-> ExceptT GhciModuleError m (ModInfo,Name,SrcSpan)
@@ -133,7 +133,7 @@ findLoc infos span0 string = do
-- | Find any uses of the given identifier in the codebase.
findNameUses :: (GhcMonad m)
- => Map ModuleName ModInfo
+ => Map Module ModInfo
-> RealSrcSpan
-> String
-> ExceptT GhciModuleError m [SrcSpan]
@@ -160,7 +160,7 @@ stripSurrounding xs = filter (not . isRedundant) xs
-- | Try to resolve the name located at the given position, or
-- otherwise resolve based on the current module's scope.
findName :: GhcMonad m
- => Map ModuleName ModInfo
+ => Map Module ModInfo
-> RealSrcSpan
-> ModInfo
-> String
@@ -186,11 +186,11 @@ findName infos span0 mi string =
-- | Try to resolve the name from another (loaded) module's exports.
resolveNameFromModule :: GhcMonad m
- => Map ModuleName ModInfo
+ => Map Module ModInfo
-> Name
-> ExceptT GhciModuleError m Name
resolveNameFromModule infos name = do
- info <- maybe (throwE $ GhciNoModuleForName name) pure (nameModule_maybe name >>= \modL -> M.lookup (moduleName modL) infos)
+ info <- maybe (throwE $ GhciNoModuleForName name) pure (nameModule_maybe name >>= \modL -> M.lookup modL infos)
let all_names = modInfo_rdrs info
maybe (throwE GhciNoMatchingModuleExport) pure $
find (matchName name) all_names
@@ -206,7 +206,7 @@ resolveName spans' si = listToMaybe $ mapMaybe spaninfoVar $
-- | Try to find the type of the given span.
findType :: GhcMonad m
- => Map ModuleName ModInfo
+ => Map Module ModInfo
-> RealSrcSpan
-> String
-> ExceptT GhciModuleError m (ModInfo, Type)
@@ -228,34 +228,36 @@ findType infos span0 string = do
-- | Guess a module name from a file path.
guessModule :: GhcMonad m
- => Map ModuleName ModInfo -> FilePath -> MaybeT m ModuleName
+ => Map Module ModInfo -> FilePath -> MaybeT m Module
guessModule infos fp = do
- target <- lift $ guessTarget fp Nothing Nothing
- case targetId target of
- TargetModule mn -> return mn
+ target <- lift $ guessTargetId fp
+ case target of
+ TargetModule mn -> MaybeT $ pure $ findModByModuleName mn
TargetFile fp' _ -> guessModule' fp'
where
- guessModule' :: GhcMonad m => FilePath -> MaybeT m ModuleName
+ guessModule' :: GhcMonad m => FilePath -> MaybeT m Module
guessModule' fp' = case findModByFp fp' of
Just mn -> return mn
Nothing -> do
fp'' <- liftIO (makeRelativeToCurrentDirectory fp')
- target' <- lift $ guessTarget fp'' Nothing Nothing
- case targetId target' of
- TargetModule mn -> return mn
+ target' <- lift $ guessTargetId fp''
+ case target' of
+ TargetModule mn -> MaybeT . pure $ findModByModuleName mn
_ -> MaybeT . pure $ findModByFp fp''
- findModByFp :: FilePath -> Maybe ModuleName
+ findModByFp :: FilePath -> Maybe Module
findModByFp fp' = fst <$> find ((Just fp' ==) . mifp) (M.toList infos)
where
- mifp :: (ModuleName, ModInfo) -> Maybe FilePath
+ mifp :: (Module, ModInfo) -> Maybe FilePath
mifp = ml_hs_file . ms_location . modinfoSummary . snd
+ findModByModuleName :: ModuleName -> Maybe Module
+ findModByModuleName mn = find ((== mn) . moduleName) (M.keys infos)
-- | Collect type info data for the loaded modules.
-collectInfo :: (GhcMonad m) => Map ModuleName ModInfo -> [ModuleName]
- -> m (Map ModuleName ModInfo)
+collectInfo :: (GhcMonad m) => Map Module ModInfo -> [Module]
+ -> m (Map Module ModInfo)
collectInfo ms loaded = do
df <- getDynFlags
unit_state <- hsc_units <$> getSession
@@ -299,17 +301,17 @@ srcFilePath modSum = fromMaybe obj_fp src_fp
ms_loc = ms_location modSum
-- | Get info about the module: summary, types, etc.
-getModInfo :: (GhcMonad m) => ModuleName -> m ModInfo
-getModInfo name = do
- m <- getModSummary name
- p <- parseModule m
+getModInfo :: (GhcMonad m) => Module -> m ModInfo
+getModInfo m = do
+ mod_summary <- getModSummary m
+ p <- parseModule mod_summary
typechecked <- typecheckModule p
let allTypes = processAllTypeCheckedModule typechecked
let !rdr_env = tcg_rdr_env (fst $ tm_internals_ typechecked)
- ts <- liftIO $ getModificationTime $ srcFilePath m
+ ts <- liftIO $ getModificationTime $ srcFilePath mod_summary
return $
ModInfo
- { modinfoSummary = m
+ { modinfoSummary = mod_summary
, modinfoSpans = allTypes
, modinfoRdrEnv = forceGlobalRdrEnv rdr_env
, modinfoLastUpdate = ts
=====================================
ghc/GHCi/UI/Monad.hs
=====================================
@@ -91,7 +91,6 @@ data GHCiState = GHCiState
prompt_cont :: PromptFunction,
editor :: String,
stop :: String,
- multiMode :: Bool,
localConfig :: LocalConfigBehaviour,
options :: [GHCiOption],
line_number :: !Int, -- ^ input line
@@ -155,7 +154,7 @@ data GHCiState = GHCiState
long_help :: String,
lastErrorLocations :: IORef [(FastString, Int)],
- mod_infos :: !(Map ModuleName ModInfo),
+ mod_infos :: !(Map Module ModInfo),
flushStdHandles :: ForeignHValue,
-- ^ @hFlush stdout; hFlush stderr@ in the interpreter
=====================================
ghc/Main.hs
=====================================
@@ -302,7 +302,8 @@ ghciUI units srcs maybe_expr = do
[] -> return []
_ -> do
s <- initMake srcs
- return $ map (uncurry (,Nothing,)) s
+ dflags <- getDynFlags
+ return $ map (uncurry (,Just $ homeUnitId_ dflags,)) s
interactiveUI defaultGhciSettings hs_srcs maybe_expr
#endif
=====================================
testsuite/tests/linters/notes.stdout
=====================================
@@ -6,33 +6,33 @@ ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2556:55: Note [Plan (AFTE
ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2985:13: Note [Case binder next]
ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4345:8: Note [Lambda-bound unfoldings]
ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1387:37: Note [Gentle mode]
-ref compiler/GHC/Core/Opt/Specialise.hs:1761:29: Note [Arity decrease]
+ref compiler/GHC/Core/Opt/Specialise.hs:1758:29: Note [Arity decrease]
ref compiler/GHC/Core/TyCo/Rep.hs:1783:31: Note [What prevents a constraint from floating]
-ref compiler/GHC/Driver/DynFlags.hs:1218:52: Note [Eta-reduction in -O0]
-ref compiler/GHC/Driver/Main.hs:1901:34: Note [simpleTidyPgm - mkBootModDetailsTc]
+ref compiler/GHC/Driver/DynFlags.hs:1217:52: Note [Eta-reduction in -O0]
+ref compiler/GHC/Driver/Main.hs:1886:34: Note [simpleTidyPgm - mkBootModDetailsTc]
ref compiler/GHC/Hs/Expr.hs:189:63: Note [Pending Splices]
-ref compiler/GHC/Hs/Expr.hs:2194:87: Note [Lifecycle of a splice]
-ref compiler/GHC/Hs/Expr.hs:2230:7: Note [Pending Splices]
-ref compiler/GHC/Hs/Extension.hs:148:5: Note [Strict argument type constraints]
+ref compiler/GHC/Hs/Expr.hs:2208:87: Note [Lifecycle of a splice]
+ref compiler/GHC/Hs/Expr.hs:2244:7: Note [Pending Splices]
+ref compiler/GHC/Hs/Extension.hs:151:5: Note [Strict argument type constraints]
ref compiler/GHC/Hs/Pat.hs:151:74: Note [Lifecycle of a splice]
ref compiler/GHC/HsToCore/Pmc/Solver.hs:860:20: Note [COMPLETE sets on data families]
ref compiler/GHC/HsToCore/Quote.hs:1533:7: Note [How brackets and nested splices are handled]
ref compiler/GHC/Stg/Unarise.hs:457:32: Note [Renaming during unarisation]
ref compiler/GHC/Tc/Gen/HsType.hs:563:56: Note [Skolem escape prevention]
-ref compiler/GHC/Tc/Gen/HsType.hs:2717:7: Note [Matching a kind signature with a declaration]
+ref compiler/GHC/Tc/Gen/HsType.hs:2718:7: Note [Matching a kind signature with a declaration]
ref compiler/GHC/Tc/Gen/Pat.hs:284:20: Note [Typing patterns in pattern bindings]
-ref compiler/GHC/Tc/Gen/Pat.hs:1378:7: Note [Matching polytyped patterns]
+ref compiler/GHC/Tc/Gen/Pat.hs:1380:7: Note [Matching polytyped patterns]
ref compiler/GHC/Tc/Gen/Sig.hs:91:10: Note [Overview of type signatures]
-ref compiler/GHC/Tc/Gen/Splice.hs:368:16: Note [How brackets and nested splices are handled]
-ref compiler/GHC/Tc/Gen/Splice.hs:543:35: Note [PendingRnSplice]
-ref compiler/GHC/Tc/Gen/Splice.hs:670:7: Note [How brackets and nested splices are handled]
+ref compiler/GHC/Tc/Gen/Splice.hs:367:16: Note [How brackets and nested splices are handled]
+ref compiler/GHC/Tc/Gen/Splice.hs:542:35: Note [PendingRnSplice]
+ref compiler/GHC/Tc/Gen/Splice.hs:669:7: Note [How brackets and nested splices are handled]
ref compiler/GHC/Tc/Gen/Splice.hs:909:11: Note [How brackets and nested splices are handled]
ref compiler/GHC/Tc/Instance/Family.hs:458:35: Note [Constrained family instances]
-ref compiler/GHC/Tc/Solver/Rewrite.hs:1015:7: Note [Stability of rewriting]
-ref compiler/GHC/Tc/TyCl.hs:1322:6: Note [Unification variables need fresh Names]
+ref compiler/GHC/Tc/Solver/Rewrite.hs:1020:7: Note [Stability of rewriting]
+ref compiler/GHC/Tc/TyCl.hs:1662:6: Note [Unification variables need fresh Names]
ref compiler/GHC/Tc/Types/Constraint.hs:209:9: Note [NonCanonical Semantics]
ref compiler/GHC/Types/Demand.hs:304:25: Note [Preserving Boxity of results is rarely a win]
-ref compiler/GHC/Unit/Module/Deps.hs:86:13: Note [Structure of dep_boot_mods]
+ref compiler/GHC/Unit/Module/Deps.hs:97:13: Note [Structure of dep_boot_mods]
ref compiler/GHC/Utils/Monad.hs:415:34: Note [multiShotIO]
ref compiler/Language/Haskell/Syntax/Binds.hs:206:31: Note [fun_id in Match]
ref configure.ac:205:10: Note [Linking ghc-bin against threaded stage0 RTS]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9449adfd9d8a777f16cc5b6b4d50b0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9449adfd9d8a777f16cc5b6b4d50b0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109a] Buglet in continuation duplication
by Simon Peyton Jones (@simonpj) 26 May '25
by Simon Peyton Jones (@simonpj) 26 May '25
26 May '25
Simon Peyton Jones pushed to branch wip/T23109a at Glasgow Haskell Compiler / GHC
Commits:
1dd04c7f by Simon Peyton Jones at 2025-05-26T17:33:30+01:00
Buglet in continuation duplication
Need to account for strict demand; makes a difference to T19695
- - - - -
1 changed file:
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
Changes:
=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -3923,9 +3923,12 @@ mkDupableContWithDmds env df dmds
-- it, then postInlineUnconditionally will just inline it again, perhaps
-- taking an extra Simplifier iteration (e.g. in test T21839c). So make
-- a `let` only if `couldBeSmallEnoughToInline` says that it is big enough
+ -- NB: postInlineUnconditionally does not fire on strict demands,
+ -- so account for that too
; let uf_opts = seUnfoldingOpts env
; (let_floats2, arg'')
- <- if couldBeSmallEnoughToInline uf_opts (unfoldingUseThreshold uf_opts) arg'
+ <- if not (isStrUsedDmd dmd) &&
+ couldBeSmallEnoughToInline uf_opts (unfoldingUseThreshold uf_opts) arg'
then return (emptyLetFloats, arg')
else makeTrivial env NotTopLevel dmd (fsLit "karg") arg'
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1dd04c7f8e4272389c0fab21eeea1a0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1dd04c7f8e4272389c0fab21eeea1a0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] 2 commits: remove special case for HsExpanded in Ticks
by Apoorv Ingle (@ani) 26 May '25
by Apoorv Ingle (@ani) 26 May '25
26 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
3c4db9cf by Apoorv Ingle at 2025-05-26T11:18:53-05:00
remove special case for HsExpanded in Ticks
- - - - -
655c636b by Apoorv Ingle at 2025-05-26T11:19:29-05:00
check the right origin for record selector incomplete warnings
- - - - -
2 changed files:
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Tc/Instance/Class.hs
Changes:
=====================================
compiler/GHC/HsToCore/Ticks.hs
=====================================
@@ -583,7 +583,11 @@ addTickHsExpr (HsProc x pat cmdtop) =
addTickHsExpr (XExpr (WrapExpr w e)) =
liftM (XExpr . WrapExpr w) $
(addTickHsExpr e) -- Explicitly no tick on inside
-addTickHsExpr (XExpr (ExpandedThingTc o e)) = addTickHsExpanded o e
+addTickHsExpr (XExpr (ExpandedThingTc o e)) =
+ liftM (XExpr . ExpandedThingTc o) $
+ (addTickHsExpr e) -- Explicitly no tick on inside
+
+ -- addTickHsExpanded o e
addTickHsExpr e@(XExpr (ConLikeTc {})) = return e
@@ -607,24 +611,24 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts))
ListComp -> Just $ BinBox QualBinBox
_ -> Nothing
-addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc)
-addTickHsExpanded o e = liftM (XExpr . ExpandedThingTc o) $ case o of
- -- We always want statements to get a tick, so we can step over each one.
- -- To avoid duplicates we blacklist SrcSpans we already inserted here.
- OrigStmt (L pos _) _ -> do_tick_black pos
- _ -> skip
- where
- skip = addTickHsExpr e
- do_tick_black pos = do
- d <- getDensity
- case d of
- TickForCoverage -> tick_it_black pos
- TickForBreakPoints -> tick_it_black pos
- _ -> skip
- tick_it_black pos =
- unLoc <$> allocTickBox (ExpBox False) False False (locA pos)
- (withBlackListed (locA pos) $
- addTickHsExpr e)
+-- addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc)
+-- addTickHsExpanded o e = liftM (XExpr . ExpandedThingTc o) $ case o of
+-- -- We always want statements to get a tick, so we can step over each one.
+-- -- To avoid duplicates we blacklist SrcSpans we already inserted here.
+-- OrigStmt (L pos _) _ -> do_tick_black pos
+-- _ -> skip
+-- where
+-- skip = addTickHsExpr e
+-- do_tick_black pos = do
+-- d <- getDensity
+-- case d of
+-- TickForCoverage -> tick_it_black pos
+-- TickForBreakPoints -> tick_it_black pos
+-- _ -> skip
+-- tick_it_black pos =
+-- unLoc <$> allocTickBox (ExpBox False) False False (locA pos)
+-- (withBlackListed (locA pos) $
+-- addTickHsExpr e)
addTickTupArg :: HsTupArg GhcTc -> TM (HsTupArg GhcTc)
addTickTupArg (Present x e) = do { e' <- addTickLHsExpr e
=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -22,7 +22,7 @@ import GHC.Tc.Instance.Typeable
import GHC.Tc.Utils.TcMType
import GHC.Tc.Types.Evidence
import GHC.Tc.Types.CtLoc
-import GHC.Tc.Types.Origin ( InstanceWhat (..), SafeOverlapping, CtOrigin(GetFieldOrigin) )
+import GHC.Tc.Types.Origin ( InstanceWhat (..), SafeOverlapping, CtOrigin(OccurrenceOf) )
import GHC.Tc.Instance.Family( tcGetFamInstEnvs, tcInstNewTyCon_maybe, tcLookupDataFamInst, FamInstEnvs )
import GHC.Rename.Env( addUsedGRE, addUsedDataCons, DeprecationWarnings (..) )
@@ -1327,7 +1327,7 @@ warnIncompleteRecSel dflags sel_id ct_loc
-- GHC.Tc.Gen.App.tcInstFun arranges that the CtOrigin of (r.x) is GetFieldOrigin,
-- despite the expansion to (getField @"x" r)
- isGetFieldOrigin (GetFieldOrigin {}) = True
+ isGetFieldOrigin (OccurrenceOf f) = f `hasKey` getFieldClassOpKey
isGetFieldOrigin _ = False
lookupHasFieldLabel
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a7db680e0e4c4928e08191bed8030…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a7db680e0e4c4928e08191bed8030…
You're receiving this email because of your account on gitlab.haskell.org.
1
0