[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Remove most of `GHC.Internal.Pack`
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Mar 3 21:00:06 UTC 2025
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
3b78e139 by John Ericson at 2025-03-03T15:27:39-05:00
Remove most of `GHC.Internal.Pack`
Since bd82ac9f4716e28b185758ae514691d5a50c003f when `GHC.Pack` was
deleted, it is no longer used except for one function by the RTS.
- - - - -
b4fe0850 by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00
ghci: Don't set virtualCWD on every iteration
The calls to withVirtualCWD were introduced to fix #2973, but this bug
is no longer reproducible, even when `withVirtualCWD` is dropped.
This cleanup was originally motivated by the performance of :steplocal,
but the performance problem has now been fixed at its root in the next
commit.
Even then, `withVirtualCWD` seems to now be an unnecessary artifact, and
removing it simplifies the interpreter with no apparent drawbacks (testsuite is
also happy with this change)
- - - - -
73ba1e6e by Rodrigo Mesquita at 2025-03-03T15:28:16-05:00
ghci debugger: improve break/resume control flow
After interpreting bytecode (`evalStmt`), we may want to hand off
control to "GHCi.UI" in order to display an interactive break prompt:
1. When an /active/ breakpoint (one set with :break ...) is hit
2. At any breakpoint, when using :step from a breakpoint
3. At any breakpoint in the same function f, when :steplocal is called
from a breakpoint in f
4. At any breakpoint in the same module, when :stepmodule is used
Whether to pass control to the UI is now fully determined by
`handleRunStatus` which transforms an `EvalStatus_` into an
`ExecResult`. When `ExecBreak` is returned from `handleRunStatus` to
GHCi, it always means GHCi breaks.
`handleRunStatus` determines whether to loop and resume evaluation right away, or
when to return to GHCi (by returning `ExecBreak` or `ExecComplete`).
- (1) is queried using the `BreakpointStatus` message (the
`breakpointStatus` call)
- (2,3,4) are determined by the predicate `breakHere step span`, which
inspects the improved `SingleStep` type to determine whether we care
about this breakpoint even if it is not active.
This refactor solves two big performance problems with the previous control flow:
- We no longer call `withArgs/withProgram` repeatedly in the
break/resume loop, but rather just once "at the top".
- We now avoid computing the expensive `bindLocalsAtBreakpoint` for
breakpoints we'd never inspect.
In the interpreter_steplocal test added, calling `:steplocal` after breaking on `main = fib 25`
now takes 12 seconds rather than 49 seconds on my machine.
```
interpreter_steplocal(ghci) ghc/alloc 6,124,821,176 540,181,392 -91.2% GOOD
```
Fixes #25779
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
4a08d40d by Matthew Pickering at 2025-03-03T15:59:35-05:00
ghci: Serialise mi_top_env
When loading core from interface files (or from a bytecode object in
future) it's important to store what the top-level context of a module
is.
Otherwise, when you load the module into GHCi from the interface files,
only exported identifiers from the top-level module are in scope on the
repl.
See the added test which demonstrates what this enables.
The context at the GHCi prompt is everything that's in-scope in the
TopEnvIface module. Since TopEnvIface imports identifier "a", we can
evaluate "a" in the repl.
In addition to all this, we can use this information in order to
implement reifyModule in a more principled manner.
This becomes even more important when you're debugging and what to set
break-points on functions which are not imported.
- - - - -
ce7358e7 by Matthew Pickering at 2025-03-03T15:59:35-05:00
Implement reifyModule in terms of mi_top_env
mi_top_env provides precisely the information that reifyModule needs,
the user written imports.
This is important as it unblocks !9604 and #22188
Fixes #8489
- - - - -
6e0710bc by Ben Gamari at 2025-03-03T15:59:35-05:00
hadrian: Refactor handling of test suite environment
Previously we would set the environment variables used to run the
testsuite driver using `setEnv` to set them in the Hadrian process.
While looking into failures of a fix to #25752 I noticed this and took
the opportunity to refactor.
- - - - -
22 changed files:
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/PkgQual.hs
- compiler/GHC/Unit/Module/ModIface.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- hadrian/src/Rules/Test.hs
- libraries/ghc-internal/src/GHC/Internal/Pack.hs
- testsuite/tests/ghci/should_run/Makefile
- + testsuite/tests/ghci/should_run/TopEnvIface.hs
- + testsuite/tests/ghci/should_run/TopEnvIface.stdout
- + testsuite/tests/ghci/should_run/TopEnvIface2.hs
- testsuite/tests/ghci/should_run/all.T
Changes:
=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -47,7 +47,6 @@ import GHC.Core.RoughMap ( RoughMatchTc(..) )
import GHC.Driver.Config.HsToCore.Usage
import GHC.Driver.Env
-import GHC.Driver.Backend
import GHC.Driver.DynFlags
import GHC.Driver.Plugins
@@ -342,7 +341,7 @@ mkIface_ hsc_env
trust_info = setSafeMode safe_mode
annotations = map mkIfaceAnnotation anns
icomplete_matches = map mkIfaceCompleteMatch complete_matches
- !rdrs = maybeGlobalRdrEnv rdr_env
+ !rdrs = mkIfaceTopEnv rdr_env
emptyPartialModIface this_mod
-- Need to record this because it depends on the -instantiated-with flag
@@ -395,15 +394,11 @@ mkIface_ hsc_env
-- Desugar.addExportFlagsAndRules). The mi_top_env field is used
-- by GHCi to decide whether the module has its full top-level
-- scope available. (#5534)
- maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe IfaceTopEnv
- maybeGlobalRdrEnv rdr_env
- | backendWantsGlobalBindings (backend dflags)
- = Just $! let !exports = forceGlobalRdrEnv (globalRdrEnvLocal rdr_env)
- !imports = mkIfaceImports import_decls
- in IfaceTopEnv exports imports
- -- See Note [Forcing GREInfo] in GHC.Types.GREInfo.
- | otherwise
- = Nothing
+ mkIfaceTopEnv :: GlobalRdrEnv -> IfaceTopEnv
+ mkIfaceTopEnv rdr_env
+ = let !exports = sortAvails $ gresToAvailInfo $ globalRdrEnvElts $ globalRdrEnvLocal rdr_env
+ !imports = mkIfaceImports import_decls
+ in IfaceTopEnv exports imports
ifFamInstTcName = ifFamInstFam
@@ -515,8 +510,8 @@ mkIfaceImports :: [ImportUserSpec] -> [IfaceImport]
mkIfaceImports = map go
where
go (ImpUserSpec decl ImpUserAll) = IfaceImport decl ImpIfaceAll
- go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
- go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
+ go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (sortAvails env))
+ go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut (nameSetElemsStable ns))
mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas
=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -26,7 +26,8 @@ module GHC.Iface.Syntax (
IfaceCompleteMatch(..),
IfaceLFInfo(..), IfaceTopBndrInfo(..),
IfaceImport(..),
- ImpIfaceList(..),
+ ifImpModule,
+ ImpIfaceList(..), IfaceExport,
-- * Binding names
IfaceTopBndr,
@@ -69,6 +70,7 @@ import GHC.Types.Name.Set
import GHC.Types.Name.Reader
import GHC.Types.CostCentre
import GHC.Types.Literal
+import GHC.Types.Avail
import GHC.Types.ForeignCall
import GHC.Types.Annotations( AnnPayload, AnnTarget )
import GHC.Types.Basic
@@ -112,12 +114,48 @@ infixl 3 &&&
************************************************************************
-}
+type IfaceExport = AvailInfo
+
data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList
data ImpIfaceList
= ImpIfaceAll -- ^ no user import list
- | ImpIfaceExplicit !IfGlobalRdrEnv
- | ImpIfaceEverythingBut !NameSet
+ | ImpIfaceExplicit !DetOrdAvails
+ | ImpIfaceEverythingBut ![Name]
+
+
+-- | Extract the imported module from an IfaceImport
+ifImpModule :: IfaceImport -> Module
+ifImpModule (IfaceImport declSpec _) = is_mod declSpec
+
+instance Binary IfaceImport where
+ put_ bh (IfaceImport declSpec ifaceList) = do
+ put_ bh declSpec
+ put_ bh ifaceList
+ get bh = do
+ declSpec <- get bh
+ ifaceList <- get bh
+ return (IfaceImport declSpec ifaceList)
+
+instance Binary ImpIfaceList where
+ put_ bh ImpIfaceAll = putByte bh 0
+ put_ bh (ImpIfaceExplicit env) = do
+ putByte bh 1
+ put_ bh env
+ put_ bh (ImpIfaceEverythingBut ns) = do
+ putByte bh 2
+ put_ @[Name] bh ns
+ get bh = do
+ tag <- getByte bh
+ case tag of
+ 0 -> return ImpIfaceAll
+ 1 -> do
+ env <- get bh
+ return (ImpIfaceExplicit env)
+ 2 -> do
+ ns <- get @[Name] bh
+ return (ImpIfaceEverythingBut ns)
+ _ -> fail "instance Binary ImpIfaceList: Invalid tag"
-- | A binding top-level 'Name' in an interface file (e.g. the name of an
-- 'IfaceDecl').
=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -104,6 +104,7 @@ import GHC.Types.SourceText
import GHC.Types.Basic hiding ( SuccessFlag(..) )
import GHC.Types.CompleteMatch
import GHC.Types.SrcLoc
+import GHC.Types.Avail
import GHC.Types.TypeEnv
import GHC.Types.Unique.FM
import GHC.Types.Unique.DSet ( mkUniqDSet )
@@ -114,7 +115,7 @@ import GHC.Types.Literal
import GHC.Types.Var as Var
import GHC.Types.Var.Set
import GHC.Types.Name
-import GHC.Types.Name.Reader
+import GHC.Types.Name.Set
import GHC.Types.Name.Env
import GHC.Types.DefaultEnv ( ClassDefaults(..), defaultEnv )
import GHC.Types.Id
@@ -2242,9 +2243,7 @@ hydrateCgBreakInfo CgBreakInfo{..} = do
-- | This function is only used to construct the environment for GHCi,
-- so we make up fake locations
-tcIfaceImport :: HscEnv -> IfaceImport -> ImportUserSpec
-tcIfaceImport _ (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll
-tcIfaceImport _ (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut ns)
-tcIfaceImport hsc_env (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (hydrateGlobalRdrEnv get_GRE_info gre))
- where
- get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm
+tcIfaceImport :: IfaceImport -> ImportUserSpec
+tcIfaceImport (IfaceImport spec ImpIfaceAll) = ImpUserSpec spec ImpUserAll
+tcIfaceImport (IfaceImport spec (ImpIfaceEverythingBut ns)) = ImpUserSpec spec (ImpUserEverythingBut (mkNameSet ns))
+tcIfaceImport (IfaceImport spec (ImpIfaceExplicit gre)) = ImpUserSpec spec (ImpUserExplicit (getDetOrdAvails gre))
=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -2015,6 +2015,8 @@ lookupGREInfo hsc_env nm
-- and looks up the TyThing in the type environment.
--
-- See Note [Retrieving the GREInfo from interfaces] in GHC.Types.GREInfo.
+ -- Note: This function is very similar to 'tcIfaceGlobal', it would be better to
+ -- use that if possible.
= case nameModule_maybe nm of
Nothing -> UnboundGRE
Just mod ->
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -1189,7 +1189,7 @@ filterImports hsc_env iface decl_spec (Just (want_hiding, L l import_items))
(gres, imp_user_list) = case want_hiding of
Exactly ->
let gre_env = mkGlobalRdrEnv $ concatMap (gresFromIE decl_spec) items2
- in (gre_env, ImpUserExplicit gre_env)
+ in (gre_env, ImpUserExplicit (gresToAvailInfo $ globalRdrEnvElts $ gre_env))
EverythingBut ->
let hidden_names = mkNameSet $ concatMap (map greName . snd) items2
in (importsFromIface hsc_env iface decl_spec (Just hidden_names), ImpUserEverythingBut hidden_names)
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -18,7 +18,7 @@ module GHC.Runtime.Eval (
abandon, abandonAll,
getResumeContext,
getHistorySpan,
- getModBreaks,
+ getModBreaks, readModBreaks,
getHistoryModule,
setupBreakpoint,
back, forward,
@@ -53,7 +53,7 @@ import GHC.Driver.DynFlags
import GHC.Driver.Ppr
import GHC.Driver.Config
-import GHC.Rename.Names (importsFromIface)
+import GHC.Rename.Names (importsFromIface, gresFromAvails)
import GHC.Runtime.Eval.Types
import GHC.Runtime.Interpreter as GHCi
@@ -113,6 +113,7 @@ import GHC.Types.TyThing
import GHC.Types.Breakpoint
import GHC.Types.Unique.Map
+import GHC.Types.Avail
import GHC.Unit
import GHC.Unit.Module.Graph
import GHC.Unit.Module.ModIface
@@ -122,7 +123,7 @@ import GHC.Unit.Home.PackageTable
import GHC.Tc.Module ( runTcInteractive, tcRnType, loadUnqualIfaces )
import GHC.Tc.Solver (simplifyWantedsTcM)
-import GHC.Tc.Utils.Env (tcGetInstEnvs, lookupGlobal)
+import GHC.Tc.Utils.Env (tcGetInstEnvs)
import GHC.Tc.Utils.Instantiate (instDFunType)
import GHC.Tc.Utils.Monad
import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) )
@@ -130,14 +131,12 @@ import GHC.Tc.Zonk.Env ( ZonkFlexi (SkolemiseFlexi) )
import GHC.IfaceToCore
import Control.Monad
-import Control.Monad.Catch as MC
import Data.Array
import Data.Dynamic
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List (find,intercalate)
import Data.List.NonEmpty (NonEmpty)
-import System.Directory
import Unsafe.Coerce ( unsafeCoerce )
import qualified GHC.Unit.Home.Graph as HUG
@@ -156,9 +155,8 @@ getHistoryModule = ibi_tick_mod . historyBreakpointId
getHistorySpan :: HscEnv -> History -> IO SrcSpan
getHistorySpan hsc_env hist = do
let ibi = historyBreakpointId hist
- HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env) >>= pure . \case
- Just hmi -> modBreaks_locs (getModBreaks hmi) ! ibi_tick_index ibi
- _ -> panic "getHistorySpan"
+ brks <- readModBreaks hsc_env (ibi_tick_mod ibi)
+ return $ modBreaks_locs brks ! ibi_tick_index ibi
{- | Finds the enclosing top level function name -}
-- ToDo: a better way to do this would be to keep hold of the decl_path computed
@@ -166,9 +164,8 @@ getHistorySpan hsc_env hist = do
-- for each tick.
findEnclosingDecls :: HscEnv -> InternalBreakpointId -> IO [String]
findEnclosingDecls hsc_env ibi = do
- hmi <- expectJust <$> HUG.lookupHugByModule (ibi_tick_mod ibi) (hsc_HUG hsc_env)
- return $
- modBreaks_decls (getModBreaks hmi) ! ibi_tick_index ibi
+ brks <- readModBreaks hsc_env (ibi_tick_mod ibi)
+ return $ modBreaks_decls brks ! ibi_tick_index ibi
-- | Update fixity environment in the current interactive context.
updateFixityEnv :: GhcMonad m => FixityEnv -> m ()
@@ -232,10 +229,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do
updateFixityEnv fix_env
status <-
- withVirtualCWD $
- liftIO $ do
- let eval_opts = initEvalOpts idflags' (isStep execSingleStep)
- evalStmt interp eval_opts (execWrap hval)
+ liftIO $ do
+ let eval_opts = initEvalOpts idflags' (enableGhcStepMode execSingleStep)
+ evalStmt interp eval_opts (execWrap hval)
let ic = hsc_IC hsc_env
bindings = (ic_tythings ic, ic_gre_cache ic)
@@ -282,38 +278,17 @@ them. The relevant predicate is OccName.isDerivedOccName.
See #11051 for more background and examples.
-}
-withVirtualCWD :: GhcMonad m => m a -> m a
-withVirtualCWD m = do
- hsc_env <- getSession
-
- -- a virtual CWD is only necessary when we're running interpreted code in
- -- the same process as the compiler.
- case interpInstance <$> hsc_interp hsc_env of
- Just (ExternalInterp {}) -> m
- _ -> do
- let ic = hsc_IC hsc_env
- let set_cwd = do
- dir <- liftIO $ getCurrentDirectory
- case ic_cwd ic of
- Just dir -> liftIO $ setCurrentDirectory dir
- Nothing -> return ()
- return dir
-
- reset_cwd orig_dir = do
- virt_dir <- liftIO $ getCurrentDirectory
- hsc_env <- getSession
- let old_IC = hsc_IC hsc_env
- setSession hsc_env{ hsc_IC = old_IC{ ic_cwd = Just virt_dir } }
- liftIO $ setCurrentDirectory orig_dir
-
- MC.bracket set_cwd reset_cwd $ \_ -> m
-
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
parseImportDecl expr = withSession $ \hsc_env -> liftIO $ hscImport hsc_env expr
emptyHistory :: Int -> BoundedList History
emptyHistory size = nilBL size
+-- | Turn an 'EvalStatus_' result from interpreting Haskell into a GHCi 'ExecResult'.
+--
+-- This function is responsible for resuming execution at an intermediate
+-- breakpoint if we don't care about that breakpoint (e.g. if using :steplocal
+-- or :stepmodule, rather than :step, we only care about certain breakpoints).
handleRunStatus :: GhcMonad m
=> SingleStep -> String
-> ResumeBindings
@@ -322,92 +297,107 @@ handleRunStatus :: GhcMonad m
-> BoundedList History
-> m ExecResult
-handleRunStatus step expr bindings final_ids status history0
- | RunAndLogSteps <- step = tracing
- | otherwise = not_tracing
- where
- tracing
- | EvalBreak apStack_ref (Just eval_break) resume_ctxt _ccs <- status
- = do
- hsc_env <- getSession
- let interp = hscInterp hsc_env
- let dflags = hsc_dflags hsc_env
- ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break
- hmi <- liftIO $ expectJust <$>
- lookupHpt (hsc_HPT hsc_env) (moduleName (ibi_tick_mod ibi))
- let breaks = getModBreaks hmi
-
- b <- liftIO $
- breakpointStatus interp (modBreaks_flags breaks) (ibi_tick_index ibi)
- if b
- then not_tracing
- -- This breakpoint is explicitly enabled; we want to stop
- -- instead of just logging it.
- else do
- apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref
- history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi
- let !history' = history1 `consBL` history0
- -- history is strict, otherwise our BoundedList is pointless.
- fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
- let eval_opts = initEvalOpts dflags True
- status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv
- handleRunStatus RunAndLogSteps expr bindings final_ids
- status history'
- | otherwise
- = not_tracing
-
- not_tracing
- -- Hit a breakpoint
- | EvalBreak apStack_ref maybe_break resume_ctxt ccs <- status
- = do
- hsc_env <- getSession
- let interp = hscInterp hsc_env
- resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
- apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref
- ibi <- case maybe_break of
- Nothing -> pure Nothing
- Just break -> fmap Just $ liftIO $
- evalBreakpointToId (hsc_HPT hsc_env) break
- (hsc_env1, names, span, decl) <- liftIO $
- bindLocalsAtBreakpoint hsc_env apStack_fhv ibi
- let
- resume = Resume
- { resumeStmt = expr
- , resumeContext = resume_ctxt_fhv
- , resumeBindings = bindings
- , resumeFinalIds = final_ids
- , resumeApStack = apStack_fhv
- , resumeBreakpointId = ibi
- , resumeSpan = span
- , resumeHistory = toListBL history0
- , resumeDecl = decl
- , resumeCCS = ccs
- , resumeHistoryIx = 0
- }
- hsc_env2 = pushResume hsc_env1 resume
-
- setSession hsc_env2
- return (ExecBreak names ibi)
+handleRunStatus step expr bindings final_ids status history0 = do
+ hsc_env <- getSession
+ let
+ interp = hscInterp hsc_env
+ dflags = hsc_dflags hsc_env
+ case status of
-- Completed successfully
- | EvalComplete allocs (EvalSuccess hvals) <- status
- = do hsc_env <- getSession
- let final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids
- final_names = map getName final_ids
- interp = hscInterp hsc_env
- liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals)
- hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic}
- setSession hsc_env'
- return (ExecComplete (Right final_names) allocs)
+ EvalComplete allocs (EvalSuccess hvals) -> do
+ let
+ final_ic = extendInteractiveContextWithIds (hsc_IC hsc_env) final_ids
+ final_names = map getName final_ids
+ liftIO $ Loader.extendLoadedEnv interp (zip final_names hvals)
+ hsc_env' <- liftIO $ rttiEnvironment hsc_env{hsc_IC=final_ic}
+ setSession hsc_env'
+ return (ExecComplete (Right final_names) allocs)
-- Completed with an exception
- | EvalComplete alloc (EvalException e) <- status
- = return (ExecComplete (Left (fromSerializableException e)) alloc)
-
+ EvalComplete alloc (EvalException e) ->
+ return (ExecComplete (Left (fromSerializableException e)) alloc)
+
+ -- Nothing case: we stopped when an exception was raised, not at a breakpoint.
+ EvalBreak apStack_ref Nothing resume_ctxt ccs -> do
+ resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
+ apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref
+ let span = mkGeneralSrcSpan (fsLit "<unknown>")
+ (hsc_env1, names) <- liftIO $
+ bindLocalsAtBreakpoint hsc_env apStack_fhv span Nothing
+ let
+ resume = Resume
+ { resumeStmt = expr
+ , resumeContext = resume_ctxt_fhv
+ , resumeBindings = bindings
+ , resumeFinalIds = final_ids
+ , resumeApStack = apStack_fhv
+ , resumeBreakpointId = Nothing
+ , resumeSpan = span
+ , resumeHistory = toListBL history0
+ , resumeDecl = "<exception thrown>"
+ , resumeCCS = ccs
+ , resumeHistoryIx = 0
+ }
+ hsc_env2 = pushResume hsc_env1 resume
+
+ setSession hsc_env2
+ return (ExecBreak names Nothing)
+
+ -- Just case: we stopped at a breakpoint
+ EvalBreak apStack_ref (Just eval_break) resume_ctxt ccs -> do
+ ibi <- liftIO $ evalBreakpointToId (hsc_HPT hsc_env) eval_break
+ tick_brks <- liftIO $ readModBreaks hsc_env (ibi_tick_mod ibi)
+ let
+ span = modBreaks_locs tick_brks ! ibi_tick_index ibi
+ decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi
+
+ b <- liftIO $ breakpointStatus interp (modBreaks_flags tick_brks) (ibi_tick_index ibi)
+
+ apStack_fhv <- liftIO $ mkFinalizedHValue interp apStack_ref
+ resume_ctxt_fhv <- liftIO $ mkFinalizedHValue interp resume_ctxt
+
+ -- This breakpoint is explicitly enabled; we want to stop
+ -- instead of just logging it.
+ if b || breakHere step span then do
+ -- This function only returns control to ghci with 'ExecBreak' when it is really meant to break.
+ -- Specifically, for :steplocal or :stepmodule, don't return control
+ -- and simply resume execution from here until we hit a breakpoint we do want to stop at.
+ (hsc_env1, names) <- liftIO $
+ bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi)
+ let
+ resume = Resume
+ { resumeStmt = expr
+ , resumeContext = resume_ctxt_fhv
+ , resumeBindings = bindings
+ , resumeFinalIds = final_ids
+ , resumeApStack = apStack_fhv
+ , resumeBreakpointId = Just ibi
+ , resumeSpan = span
+ , resumeHistory = toListBL history0
+ , resumeDecl = decl
+ , resumeCCS = ccs
+ , resumeHistoryIx = 0
+ }
+ hsc_env2 = pushResume hsc_env1 resume
+ setSession hsc_env2
+ return (ExecBreak names (Just ibi))
+ else do
+ let eval_opts = initEvalOpts dflags (enableGhcStepMode step)
+ status <- liftIO $ GHCi.resumeStmt interp eval_opts resume_ctxt_fhv
+ history <- if not tracing then pure history0 else do
+ history1 <- liftIO $ mkHistory hsc_env apStack_fhv ibi
+ let !history' = history1 `consBL` history0
+ -- history is strict, otherwise our BoundedList is pointless.
+ return history'
+ handleRunStatus step expr bindings final_ids status history
+ where
+ tracing | RunAndLogSteps <- step = True
+ | otherwise = False
-resumeExec :: GhcMonad m => (SrcSpan->Bool) -> SingleStep -> Maybe Int
+resumeExec :: GhcMonad m => SingleStep -> Maybe Int
-> m ExecResult
-resumeExec canLogSpan step mbCnt
+resumeExec step mbCnt
= do
hsc_env <- getSession
let ic = hsc_IC hsc_env
@@ -445,42 +435,41 @@ resumeExec canLogSpan step mbCnt
, resumeBreakpointId = mb_brkpt
, resumeSpan = span
, resumeHistory = hist } ->
- withVirtualCWD $ do
+ do
-- When the user specified a break ignore count, set it
-- in the interpreter
case (mb_brkpt, mbCnt) of
(Just brkpt, Just cnt) -> setupBreakpoint hsc_env (toBreakpointId brkpt) cnt
_ -> return ()
- let eval_opts = initEvalOpts dflags (isStep step)
+ let eval_opts = initEvalOpts dflags (enableGhcStepMode step)
status <- liftIO $ GHCi.resumeStmt interp eval_opts fhv
let prevHistoryLst = fromListBL 50 hist
hist' = case mb_brkpt of
Nothing -> pure prevHistoryLst
Just bi
- | not $ canLogSpan span -> pure prevHistoryLst
- | otherwise -> do
+ | breakHere step span -> do
hist1 <- liftIO (mkHistory hsc_env apStack bi)
return $ hist1 `consBL` fromListBL 50 hist
+ | otherwise -> pure prevHistoryLst
handleRunStatus step expr bindings final_ids status =<< hist'
setupBreakpoint :: GhcMonad m => HscEnv -> BreakpointId -> Int -> m () -- #19157
setupBreakpoint hsc_env bi cnt = do
let modl = bi_tick_mod bi
- modBreaks <- getModBreaks . expectJust <$>
- liftIO (lookupHpt (hsc_HPT hsc_env) (moduleName modl))
+ modBreaks <- liftIO $ readModBreaks hsc_env modl
let breakarray = modBreaks_flags modBreaks
interp = hscInterp hsc_env
_ <- liftIO $ GHCi.storeBreakpoint interp breakarray (bi_tick_index bi) cnt
pure ()
-back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
+back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan)
back n = moveHist (+n)
-forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
+forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan)
forward n = moveHist (subtract n)
-moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan, String)
+moveHist :: GhcMonad m => (Int -> Int) -> m ([Name], Int, SrcSpan)
moveHist fn = do
hsc_env <- getSession
case ic_resume (hsc_IC hsc_env) of
@@ -498,15 +487,20 @@ moveHist fn = do
let
update_ic apStack mb_info = do
- (hsc_env1, names, span, decl) <-
- liftIO $ bindLocalsAtBreakpoint hsc_env apStack mb_info
+ span <- case mb_info of
+ Nothing -> return $ mkGeneralSrcSpan (fsLit "<unknown>")
+ Just ibi -> liftIO $ do
+ brks <- readModBreaks hsc_env (ibi_tick_mod ibi)
+ return $ modBreaks_locs brks ! ibi_tick_index ibi
+ (hsc_env1, names) <-
+ liftIO $ bindLocalsAtBreakpoint hsc_env apStack span mb_info
let ic = hsc_IC hsc_env1
r' = r { resumeHistoryIx = new_ix }
ic' = ic { ic_resume = r':rs }
setSession hsc_env1{ hsc_IC = ic' }
- return (names, new_ix, span, decl)
+ return (names, new_ix, span)
-- careful: we want apStack to be the AP_STACK itself, not a thunk
-- around it, hence the cases are carefully constructed below to
@@ -527,19 +521,25 @@ moveHist fn = do
result_fs :: FastString
result_fs = fsLit "_result"
+-- | Read the 'ModBreaks' of the given home 'Module' from the 'HomeUnitGraph'.
+readModBreaks :: HscEnv -> Module -> IO ModBreaks
+readModBreaks hsc_env mod =
+ getModBreaks . expectJust <$>
+ HUG.lookupHugByModule mod (hsc_HUG hsc_env)
+
bindLocalsAtBreakpoint
:: HscEnv
-> ForeignHValue
+ -> SrcSpan
-> Maybe InternalBreakpointId
- -> IO (HscEnv, [Name], SrcSpan, String)
+ -> IO (HscEnv, [Name])
-- Nothing case: we stopped when an exception was raised, not at a
-- breakpoint. We have no location information or local variables to
-- bind, all we can do is bind a local variable to the exception
-- value.
-bindLocalsAtBreakpoint hsc_env apStack Nothing = do
+bindLocalsAtBreakpoint hsc_env apStack span Nothing = do
let exn_occ = mkVarOccFS (fsLit "_exception")
- span = mkGeneralSrcSpan (fsLit "<unknown>")
exn_name <- newInteractiveBinder hsc_env exn_occ span
let e_fs = fsLit "e"
@@ -552,32 +552,21 @@ bindLocalsAtBreakpoint hsc_env apStack Nothing = do
interp = hscInterp hsc_env
--
Loader.extendLoadedEnv interp [(exn_name, apStack)]
- return (hsc_env{ hsc_IC = ictxt1 }, [exn_name], span, "<exception thrown>")
+ return (hsc_env{ hsc_IC = ictxt1 }, [exn_name])
-- Just case: we stopped at a breakpoint, we have information about the location
-- of the breakpoint and the free variables of the expression.
-bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do
- let
- interp = hscInterp hsc_env
-
- info_mod = ibi_info_mod ibi
- info_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName info_mod)
- let
- info_brks = getModBreaks info_hmi
- info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks)
-
- tick_mod = ibi_tick_mod ibi
- tick_hmi <- expectJust <$> lookupHpt (hsc_HPT hsc_env) (moduleName tick_mod)
- let
- tick_brks = getModBreaks tick_hmi
- occs = modBreaks_vars tick_brks ! ibi_tick_index ibi
- span = modBreaks_locs tick_brks ! ibi_tick_index ibi
- decl = intercalate "." $ modBreaks_decls tick_brks ! ibi_tick_index ibi
+bindLocalsAtBreakpoint hsc_env apStack_fhv span (Just ibi) = do
+ info_brks <- readModBreaks hsc_env (ibi_info_mod ibi)
+ tick_brks <- readModBreaks hsc_env (ibi_tick_mod ibi)
+ let info = expectJust $ IntMap.lookup (ibi_info_index ibi) (modBreaks_breakInfo info_brks)
+ interp = hscInterp hsc_env
+ occs = modBreaks_vars tick_brks ! ibi_tick_index ibi
-- Rehydrate to understand the breakpoint info relative to the current environment.
-- This design is critical to preventing leaks (#22530)
(mbVars, result_ty) <- initIfaceLoad hsc_env
- $ initIfaceLcl info_mod (text "debugger") NotBoot
+ $ initIfaceLcl (ibi_info_mod ibi) (text "debugger") NotBoot
$ hydrateCgBreakInfo info
let
@@ -624,7 +613,7 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do
Loader.extendLoadedEnv interp (zip names fhvs)
when result_ok $ Loader.extendLoadedEnv interp [(result_name, apStack_fhv)]
hsc_env1 <- rttiEnvironment hsc_env{ hsc_IC = ictxt1 }
- return (hsc_env1, if result_ok then result_name:names else names, span, decl)
+ return (hsc_env1, if result_ok then result_name:names else names)
where
-- We need a fresh Unique for each Id we bind, because the linker
-- state is single-threaded and otherwise we'd spam old bindings
@@ -848,21 +837,25 @@ mkTopLevEnv hsc_env modl
Nothing -> pure $ Left "not a home module"
Just details ->
case mi_top_env (hm_iface details) of
- Nothing -> pure $ Left "not interpreted"
- Just (IfaceTopEnv exports imports) -> do
+ (IfaceTopEnv exports imports) -> do
imports_env <-
runInteractiveHsc hsc_env
$ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env
$ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
$ forM imports $ \iface_import -> do
- let ImpUserSpec spec details = tcIfaceImport hsc_env iface_import
+ let ImpUserSpec spec details = tcIfaceImport iface_import
iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec)
pure $ case details of
ImpUserAll -> importsFromIface hsc_env iface spec Nothing
ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
- ImpUserExplicit x -> x
- let get_GRE_info nm = tyThingGREInfo <$> lookupGlobal hsc_env nm
- let exports_env = hydrateGlobalRdrEnv get_GRE_info exports
+ ImpUserExplicit x ->
+ -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y).
+ -- It is only used for error messages. It seems dubious even to add an import context to these GREs as
+ -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that
+ -- the test case produce the same output as before.
+ let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } }
+ in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x
+ let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports)
pure $ Right $ plusGlobalRdrEnv imports_env exports_env
where
hpt = hsc_HPT hsc_env
@@ -880,8 +873,8 @@ moduleIsInterpreted :: GhcMonad m => Module -> m Bool
moduleIsInterpreted modl = withSession $ \h ->
if notHomeModule (hsc_home_unit h) modl
then return False
- else liftIO (lookupHpt (hsc_HPT h) (moduleName modl)) >>= \case
- Just details -> return (isJust (mi_top_env (hm_iface details)))
+ else 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)
=====================================
compiler/GHC/Runtime/Eval/Types.hs
=====================================
@@ -9,7 +9,8 @@
module GHC.Runtime.Eval.Types (
Resume(..), ResumeBindings, IcGlobalRdrEnv(..),
History(..), ExecResult(..),
- SingleStep(..), isStep, ExecOptions(..)
+ SingleStep(..), enableGhcStepMode, breakHere,
+ ExecOptions(..)
) where
import GHC.Prelude
@@ -35,21 +36,59 @@ data ExecOptions
, execWrap :: ForeignHValue -> EvalExpr ForeignHValue
}
+-- | What kind of stepping are we doing?
data SingleStep
= RunToCompletion
- | SingleStep
+
+ -- | :trace [expr]
| RunAndLogSteps
-isStep :: SingleStep -> Bool
-isStep RunToCompletion = False
-isStep _ = True
+ -- | :step [expr]
+ | SingleStep
+
+ -- | :steplocal [expr]
+ | LocalStep
+ { breakAt :: SrcSpan }
+
+ -- | :stepmodule [expr]
+ | ModuleStep
+ { breakAt :: SrcSpan }
+
+-- | Whether this 'SingleStep' mode requires instructing the interpreter to
+-- step at every breakpoint.
+enableGhcStepMode :: SingleStep -> Bool
+enableGhcStepMode RunToCompletion = False
+enableGhcStepMode _ = True
+
+-- | Given a 'SingleStep' mode and the SrcSpan of a breakpoint we hit, return
+-- @True@ if based on the step-mode alone we should stop at this breakpoint.
+--
+-- In particular, this will always be @False@ for @'RunToCompletion'@ and
+-- @'RunAndLogSteps'@. We'd need further information e.g. about the user
+-- breakpoints to determine whether to break in those modes.
+breakHere :: SingleStep -> SrcSpan -> Bool
+breakHere step break_span = case step of
+ RunToCompletion -> False
+ RunAndLogSteps -> False
+ SingleStep -> True
+ LocalStep span -> break_span `isSubspanOf` span
+ ModuleStep span -> srcSpanFileName_maybe span == srcSpanFileName_maybe break_span
data ExecResult
+
+ -- | Execution is complete
= ExecComplete
{ execResult :: Either SomeException [Name]
, execAllocation :: Word64
}
- | ExecBreak
+
+ -- | Execution stopped at a breakpoint.
+ --
+ -- Note: `ExecBreak` is only returned by `handleRunStatus` when GHCi should
+ -- definitely stop at this breakpoint. GHCi is /not/ responsible for
+ -- subsequently deciding whether to really stop here.
+ -- `ExecBreak` always means GHCi breaks.
+ | ExecBreak
{ breakNames :: [Name]
, breakPointId :: Maybe InternalBreakpointId
}
=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -124,7 +124,7 @@ import GHC.Serialized
import GHC.Unit.Finder
import GHC.Unit.Module
import GHC.Unit.Module.ModIface
-import GHC.Unit.Module.Deps
+import GHC.Iface.Syntax
import GHC.Utils.Misc
import GHC.Utils.Panic as Panic
@@ -2887,16 +2887,12 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do
reifyFromIface reifMod = do
iface <- loadInterfaceForModule (text "reifying module from TH for" <+> ppr reifMod) reifMod
- let usages = [modToTHMod m | usage <- mi_usages iface,
- Just m <- [usageToModule (moduleUnit reifMod) usage] ]
+ let IfaceTopEnv _ imports = mi_top_env iface
+ -- Convert IfaceImport to module names
+ usages = [modToTHMod (ifImpModule imp) | imp <- imports]
return $ TH.ModuleInfo usages
- usageToModule :: Unit -> Usage -> Maybe Module
- usageToModule _ (UsageFile {}) = Nothing
- usageToModule this_pkg (UsageHomeModule { usg_mod_name = mn }) = Just $ mkModule this_pkg mn
- usageToModule _ (UsagePackageModule { usg_mod = m }) = Just m
- usageToModule _ (UsageMergedRequirement { usg_mod = m }) = Just m
- usageToModule this_pkg (UsageHomeModuleInterface { usg_mod_name = mn }) = Just $ mkModule this_pkg mn
+
------------------------------
mkThAppTs :: TH.Type -> [TH.Type] -> TH.Type
=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -206,7 +206,7 @@ data ImportUserSpec
data ImpUserList
= ImpUserAll -- ^ no user import list
- | ImpUserExplicit !GlobalRdrEnv
+ | ImpUserExplicit ![AvailInfo]
| ImpUserEverythingBut !NameSet
-- | A 'NameShape' is a substitution on 'Name's that can be used
=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -22,7 +22,8 @@ module GHC.Types.Avail (
filterAvails,
nubAvails,
sortAvails,
- DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails)
+ DetOrdAvails(DetOrdAvails, getDetOrdAvails, DefinitelyDeterministicAvails),
+ emptyDetOrdAvails
) where
import GHC.Prelude
@@ -74,7 +75,7 @@ type Avails = [AvailInfo]
-- We guarantee a deterministic order by either using the order explicitly
-- given by the user (e.g. in an explicit constructor export list) or instead
-- by sorting the avails with 'sortAvails'.
-newtype DetOrdAvails = DefinitelyDeterministicAvails Avails
+newtype DetOrdAvails = DefinitelyDeterministicAvails { getDetOrdAvails :: Avails }
deriving newtype (Binary, Outputable, NFData)
-- | It's always safe to match on 'DetOrdAvails'
@@ -245,3 +246,7 @@ instance Binary AvailInfo where
instance NFData AvailInfo where
rnf (Avail n) = rnf n
rnf (AvailTC a b) = rnf a `seq` rnf b
+
+-- | Create an empty DetOrdAvails
+emptyDetOrdAvails :: DetOrdAvails
+emptyDetOrdAvails = DefinitelyDeterministicAvails []
=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -133,6 +133,7 @@ import GHC.Unit.Module
import GHC.Utils.Misc as Utils
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Utils.Binary
import Control.DeepSeq
import Control.Monad ( guard )
@@ -1946,6 +1947,22 @@ data ImpDeclSpec
instance NFData ImpDeclSpec where
rnf = rwhnf -- Already strict in all fields
+instance Binary ImpDeclSpec where
+ put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot) = do
+ put_ bh mod
+ put_ bh as
+ put_ bh pkg_qual
+ put_ bh qual
+ put_ bh isboot
+
+ get bh = do
+ mod <- get bh
+ as <- get bh
+ pkg_qual <- get bh
+ qual <- get bh
+ isboot <- get bh
+ return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot)
+
-- | Import Item Specification
--
-- Describes import info a particular Name
=====================================
compiler/GHC/Types/PkgQual.hs
=====================================
@@ -6,6 +6,7 @@ module GHC.Types.PkgQual where
import GHC.Prelude
import GHC.Types.SourceText
import GHC.Unit.Types
+import GHC.Utils.Binary
import GHC.Utils.Outputable
import Data.Data
@@ -38,4 +39,22 @@ instance Outputable PkgQual where
ThisPkg u -> doubleQuotes (ppr u)
OtherPkg u -> doubleQuotes (ppr u)
+instance Binary PkgQual where
+ put_ bh NoPkgQual = putByte bh 0
+ put_ bh (ThisPkg u) = do
+ putByte bh 1
+ put_ bh u
+ put_ bh (OtherPkg u) = do
+ putByte bh 2
+ put_ bh u
+
+ get bh = do
+ tag <- getByte bh
+ case tag of
+ 0 -> return NoPkgQual
+ 1 -> do u <- get bh
+ return (ThisPkg u)
+ 2 -> do u <- get bh
+ return (OtherPkg u)
+ _ -> fail "instance Binary PkgQual: Invalid tag"
=====================================
compiler/GHC/Unit/Module/ModIface.hs
=====================================
@@ -111,7 +111,6 @@ import GHC.Types.Fixity
import GHC.Types.Fixity.Env
import GHC.Types.HpcInfo
import GHC.Types.Name
-import GHC.Types.Name.Reader (IfGlobalRdrEnv)
import GHC.Types.SafeHaskell
import GHC.Types.SourceFile
import GHC.Types.Unique.DSet
@@ -299,20 +298,13 @@ data ModIface_ (phase :: ModIfacePhase)
mi_defaults_ :: [IfaceDefault],
-- ^ default declarations exported by the module
- mi_top_env_ :: !(Maybe IfaceTopEnv),
+ mi_top_env_ :: IfaceTopEnv,
-- ^ Just enough information to reconstruct the top level environment in
-- the /original source/ code for this module. which
-- is NOT the same as mi_exports, nor mi_decls (which
-- may contains declarations for things not actually
-- defined by the user). Used for GHCi and for inspecting
-- the contents of modules via the GHC API only.
- --
- -- (We need the source file to figure out the
- -- top-level environment, if we didn't compile this module
- -- from source then this field contains @Nothing@).
- --
- -- Strictly speaking this field should live in the
- -- 'HomeModInfo', but that leads to more plumbing.
-- Instance declarations and rules
mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance
@@ -365,13 +357,23 @@ data ModIface_ (phase :: ModIfacePhase)
-- Enough information to reconstruct the top level environment for a module
data IfaceTopEnv
= IfaceTopEnv
- { ifaceTopExports :: !IfGlobalRdrEnv -- ^ all top level things in this module, including unexported stuff
+ { ifaceTopExports :: !DetOrdAvails -- ^ all top level things in this module, including unexported stuff
, ifaceImports :: ![IfaceImport] -- ^ all the imports in this module
}
instance NFData IfaceTopEnv where
rnf (IfaceTopEnv a b) = rnf a `seq` rnf b
+instance Binary IfaceTopEnv where
+ put_ bh (IfaceTopEnv exports imports) = do
+ put_ bh exports
+ put_ bh imports
+ get bh = do
+ exports <- get bh
+ imports <- get bh
+ return (IfaceTopEnv exports imports)
+
+
{-
Note [Strictness in ModIface]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -479,6 +481,7 @@ instance Binary ModIface where
mi_trust_ = trust,
mi_trust_pkg_ = trust_pkg,
mi_complete_matches_ = complete_matches,
+ mi_top_env_ = top_env,
mi_docs_ = docs,
mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we
-- can deal with it's pointer in the header
@@ -526,6 +529,7 @@ instance Binary ModIface where
put_ bh trust
put_ bh trust_pkg
put_ bh complete_matches
+ lazyPut bh top_env
lazyPutMaybe bh docs
get bh = do
@@ -560,6 +564,7 @@ instance Binary ModIface where
trust <- get bh
trust_pkg <- get bh
complete_matches <- get bh
+ top_env <- lazyGet bh
docs <- lazyGetMaybe bh
return (PrivateModIface {
mi_module_ = mod,
@@ -582,7 +587,6 @@ instance Binary ModIface where
mi_decls_ = decls,
mi_extra_decls_ = extra_decls,
mi_foreign_ = foreign_,
- mi_top_env_ = Nothing,
mi_defaults_ = defaults,
mi_insts_ = insts,
mi_fam_insts_ = fam_insts,
@@ -593,6 +597,7 @@ instance Binary ModIface where
-- And build the cached values
mi_complete_matches_ = complete_matches,
mi_docs_ = docs,
+ mi_top_env_ = top_env,
mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt
-- with specially when the file is read
mi_final_exts_ = ModIfaceBackend {
@@ -613,8 +618,6 @@ instance Binary ModIface where
}})
--- | The original names declared of a certain module that are exported
-type IfaceExport = AvailInfo
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface mod
@@ -638,7 +641,7 @@ emptyPartialModIface mod
mi_decls_ = [],
mi_extra_decls_ = Nothing,
mi_foreign_ = emptyIfaceForeign,
- mi_top_env_ = Nothing,
+ mi_top_env_ = IfaceTopEnv emptyDetOrdAvails [] ,
mi_hpc_ = False,
mi_trust_ = noIfaceTrustInfo,
mi_trust_pkg_ = False,
@@ -810,15 +813,14 @@ addSourceFingerprint val iface = iface { mi_src_hash_ = val }
-- | Copy fields that aren't serialised to disk to the new 'ModIface_'.
-- This includes especially hashes that are usually stored in the interface
--- file header and 'mi_top_env'.
+-- file header.
--
-- We need this function after calling 'shareIface', to make sure the
-- 'ModIface_' doesn't lose any information. This function does not discard
-- the in-memory byte array buffer 'mi_hi_bytes'.
restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase
restoreFromOldModIface old new = new
- { mi_top_env_ = mi_top_env_ old
- , mi_hsc_src_ = mi_hsc_src_ old
+ { mi_hsc_src_ = mi_hsc_src_ old
, mi_src_hash_ = mi_src_hash_ old
}
@@ -879,7 +881,7 @@ set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val
set_mi_foreign :: IfaceForeign -> ModIface_ phase -> ModIface_ phase
set_mi_foreign foreign_ iface = clear_mi_hi_bytes $ iface { mi_foreign_ = foreign_ }
-set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
+set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val }
set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase
@@ -996,7 +998,7 @@ pattern ModIface ::
[IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings ->
[IfaceAnnotation] -> [IfaceDeclExts phase] ->
Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign ->
- [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] ->
+ [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] ->
AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs ->
IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase ->
ModIface_ phase
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1310,7 +1310,7 @@ runStmt input step = do
m_result <- GhciMonad.runStmt stmt input step
case m_result of
Nothing -> return Nothing
- Just result -> Just <$> afterRunStmt (const True) result
+ Just result -> Just <$> afterRunStmt step result
-- `x = y` (a declaration) should be treated as `let x = y` (a statement).
-- The reason is because GHCi wasn't designed to support `x = y`, but then
@@ -1342,7 +1342,7 @@ runStmt input step = do
_ <- liftIO $ tryIO $ hFlushAll stdin
m_result <- GhciMonad.runDecls' decls
forM m_result $ \result ->
- afterRunStmt (const True) (GHC.ExecComplete (Right result) 0)
+ afterRunStmt step (GHC.ExecComplete (Right result) 0)
mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs
mk_stmt loc bind =
@@ -1359,9 +1359,9 @@ runStmt input step = do
modStr = moduleNameString $ moduleName $ icInteractiveModule $ ic
-- | Clean up the GHCi environment after a statement has run
-afterRunStmt :: GhciMonad m
- => (SrcSpan -> Bool) -> GHC.ExecResult -> m GHC.ExecResult
-afterRunStmt step_here run_result = do
+afterRunStmt :: GhciMonad m => SingleStep {-^ Type of step we took just before -}
+ -> GHC.ExecResult -> m GHC.ExecResult
+afterRunStmt step run_result = do
resumes <- GHC.getResumeContext
case run_result of
GHC.ExecComplete{..} ->
@@ -1372,9 +1372,7 @@ afterRunStmt step_here run_result = do
when show_types $ printTypeOfNames names
GHC.ExecBreak names mb_info
| first_resume : _ <- resumes
- , isNothing mb_info ||
- step_here (GHC.resumeSpan first_resume) -> do
- mb_id_loc <- toBreakIdAndLocation mb_info
+ -> do mb_id_loc <- toBreakIdAndLocation mb_info
let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc
if (null bCmd)
then printStoppedAtBreakInfo first_resume names
@@ -1383,8 +1381,9 @@ afterRunStmt step_here run_result = do
st <- getGHCiState
enqueueCommands [stop st]
return ()
- | otherwise -> resume step_here GHC.SingleStep Nothing >>=
- afterRunStmt step_here >> return ()
+
+ | otherwise -> resume step Nothing >>=
+ afterRunStmt step >> return ()
flushInterpBuffers
withSignalHandlers $ do
@@ -3810,7 +3809,7 @@ forceCmd = pprintClosureCommand False True
stepCmd :: GhciMonad m => String -> m ()
stepCmd arg = withSandboxOnly ":step" $ step arg
where
- step [] = doContinue (const True) GHC.SingleStep
+ step [] = doContinue GHC.SingleStep
step expression = runStmt expression GHC.SingleStep >> return ()
stepLocalCmd :: GhciMonad m => String -> m ()
@@ -3829,7 +3828,7 @@ stepLocalCmd arg = withSandboxOnly ":steplocal" $ step arg
Just loc -> do
md <- fromMaybe (panic "stepLocalCmd") <$> getCurrentBreakModule
current_toplevel_decl <- enclosingTickSpan md loc
- doContinue (`isSubspanOf` RealSrcSpan current_toplevel_decl Strict.Nothing) GHC.SingleStep
+ doContinue (GHC.LocalStep (RealSrcSpan current_toplevel_decl Strict.Nothing))
stepModuleCmd :: GhciMonad m => String -> m ()
stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg
@@ -3840,9 +3839,7 @@ stepModuleCmd arg = withSandboxOnly ":stepmodule" $ step arg
mb_span <- getCurrentBreakSpan
case mb_span of
Nothing -> stepCmd []
- Just pan -> do
- let f some_span = srcSpanFileName_maybe pan == srcSpanFileName_maybe some_span
- doContinue f GHC.SingleStep
+ Just pan -> doContinue (GHC.ModuleStep pan)
-- | Returns the span of the largest tick containing the srcspan given
enclosingTickSpan :: GhciMonad m => Module -> SrcSpan -> m RealSrcSpan
@@ -3863,14 +3860,14 @@ traceCmd :: GhciMonad m => String -> m ()
traceCmd arg
= withSandboxOnly ":trace" $ tr arg
where
- tr [] = doContinue (const True) GHC.RunAndLogSteps
+ tr [] = doContinue GHC.RunAndLogSteps
tr expression = runStmt expression GHC.RunAndLogSteps >> return ()
continueCmd :: GhciMonad m => String -> m () -- #19157
continueCmd argLine = withSandboxOnly ":continue" $
case contSwitch (words argLine) of
Left sdoc -> printForUser sdoc
- Right mbCnt -> doContinue' (const True) GHC.RunToCompletion mbCnt
+ Right mbCnt -> doContinue' GHC.RunToCompletion mbCnt
where
contSwitch :: [String] -> Either SDoc (Maybe Int)
contSwitch [ ] = Right Nothing
@@ -3878,13 +3875,13 @@ continueCmd argLine = withSandboxOnly ":continue" $
contSwitch _ = Left $
text "After ':continue' only one ignore count is allowed"
-doContinue :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> m ()
-doContinue pre step = doContinue' pre step Nothing
+doContinue :: GhciMonad m => SingleStep -> m ()
+doContinue step = doContinue' step Nothing
-doContinue' :: GhciMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m ()
-doContinue' pre step mbCnt= do
- runResult <- resume pre step mbCnt
- _ <- afterRunStmt pre runResult
+doContinue' :: GhciMonad m => SingleStep -> Maybe Int -> m ()
+doContinue' step mbCnt= do
+ runResult <- resume step mbCnt
+ _ <- afterRunStmt step runResult
return ()
abandonCmd :: GhciMonad m => String -> m ()
@@ -4036,7 +4033,7 @@ backCmd arg
| otherwise = liftIO $ putStrLn "Syntax: :back [num]"
where
back num = withSandboxOnly ":back" $ do
- (names, _, pan, _) <- GHC.back num
+ (names, _, pan) <- GHC.back num
printForUser $ text "Logged breakpoint at" <+> ppr pan
printTypeOfNames names
-- run the command set with ":set stop <cmd>"
@@ -4050,7 +4047,7 @@ forwardCmd arg
| otherwise = liftIO $ putStrLn "Syntax: :forward [num]"
where
forward num = withSandboxOnly ":forward" $ do
- (names, ix, pan, _) <- GHC.forward num
+ (names, ix, pan) <- GHC.forward num
printForUser $ (if (ix == 0)
then text "Stopped at"
else text "Logged breakpoint at") <+> ppr pan
=====================================
ghc/GHCi/UI/Monad.hs
=====================================
@@ -401,14 +401,14 @@ runDecls' decls = do
return Nothing)
(Just <$> GHC.runParsedDecls decls)
-resume :: GhciMonad m => (SrcSpan -> Bool) -> GHC.SingleStep -> Maybe Int -> m GHC.ExecResult
-resume canLogSpan step mbIgnoreCnt = do
+resume :: GhciMonad m => GHC.SingleStep -> Maybe Int -> m GHC.ExecResult
+resume step mbIgnoreCnt = do
st <- getGHCiState
reifyGHCi $ \x ->
withProgName (progname st) $
withArgs (args st) $
reflectGHCi x $ do
- GHC.resumeExec canLogSpan step mbIgnoreCnt
+ GHC.resumeExec step mbIgnoreCnt
-- --------------------------------------------------------------------------
-- timing & statistics
=====================================
hadrian/src/Rules/Test.hs
=====================================
@@ -1,8 +1,6 @@
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
module Rules.Test (testRules) where
-import System.Environment
-
import Base
import CommandLine
import Expression
@@ -171,7 +169,6 @@ testRules = do
root -/- timeoutPath %> \_ -> timeoutProgBuilder
"test" ~> do
-
args <- userSetting defaultTestArgs
let testCompilerArg = testCompiler args
let stg = fromMaybe Stage2 $ stageOf testCompilerArg
@@ -185,92 +182,98 @@ testRules = do
let ok_to_build = filter (isOkToBuild args) extra_targets
putVerbose $ " | ExtraTargets: " ++ intercalate ", " extra_targets
putVerbose $ " | ExtraTargets (ok-to-build): " ++ intercalate ", " ok_to_build
- need ok_to_build
-
- -- Prepare Ghc configuration file for input compiler.
- need [root -/- timeoutPath]
-
- cross <- flag CrossCompiling
-
- -- get relative path for the given program in the given stage
- let relative_path_stage s p = programPath =<< programContext s p
- let make_absolute rel_path = do
- abs_path <- liftIO (makeAbsolute rel_path)
- fixAbsolutePathOnWindows abs_path
-
- rel_ghc_pkg <- relative_path_stage Stage1 ghcPkg
- rel_hsc2hs <- relative_path_stage Stage1 hsc2hs
- rel_hp2ps <- relative_path_stage Stage1 hp2ps
- rel_haddock <- relative_path_stage (Stage0 InTreeLibs) haddock
- rel_hpc <- relative_path_stage (Stage0 InTreeLibs) hpc
- rel_runghc <- relative_path_stage (Stage0 InTreeLibs) runGhc
+ need $ ok_to_build ++ [root -/- timeoutPath]
-- force stage0 program building for cross
- when cross $ need [rel_hpc, rel_haddock, rel_runghc]
-
- prog_ghc_pkg <- make_absolute rel_ghc_pkg
- prog_hsc2hs <- make_absolute rel_hsc2hs
- prog_hp2ps <- make_absolute rel_hp2ps
- prog_haddock <- make_absolute rel_haddock
- prog_hpc <- make_absolute rel_hpc
- prog_runghc <- make_absolute rel_runghc
-
- ghcPath <- getCompilerPath testCompilerArg
-
- makePath <- builderPath $ Make ""
- top <- topDirectory
- ghcFlags <- runTestGhcFlags
- let ghciFlags = ghcFlags ++ unwords
- [ "--interactive", "-v0", "-ignore-dot-ghci"
- , "-fno-ghci-history", "-fprint-error-index-links=never"
- ]
- ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler)
- ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler)
-
- pythonPath <- builderPath Python
+ cross <- flag CrossCompiling
+ when cross $ mapM (relativePathStage (Stage0 InTreeLibs)) [hpc, haddock, runGhc] >>= need
-- Set environment variables for test's Makefile.
- -- TODO: Ideally we would define all those env vars in 'env', so that
- -- Shake can keep track of them, but it is not as easy as it seems
- -- to get that to work.
- liftIO $ do
- -- Many of those env vars are used by Makefiles in the
- -- test infrastructure, or from tests or their
- -- Makefiles.
- setEnv "MAKE" makePath
- setEnv "PYTHON" pythonPath
- setEnv "TEST_HC" ghcPath
- setEnv "TEST_HC_OPTS" ghcFlags
- setEnv "TEST_HC_OPTS_INTERACTIVE" ghciFlags
- setEnv "TEST_CC" ccPath
- setEnv "TEST_CC_OPTS" ccFlags
-
- when cross $ do
- setEnv "GHC_PKG" prog_ghc_pkg
- setEnv "HSC2HS" prog_hsc2hs
- setEnv "HP2PS_ABS" prog_hp2ps
- setEnv "HPC" prog_hpc
- setEnv "HADDOCK" prog_haddock
- setEnv "RUNGHC" prog_runghc
-
- setEnv "CHECK_PPR" (top -/- root -/- checkPprProgPath)
- setEnv "CHECK_EXACT" (top -/- root -/- checkExactProgPath)
- setEnv "DUMP_DECLS" (top -/- root -/- dumpDeclsProgPath)
- setEnv "COUNT_DEPS" (top -/- root -/- countDepsProgPath)
- setEnv "LINT_NOTES" (top -/- root -/- noteLinterProgPath)
- setEnv "LINT_CODES" (top -/- root -/- codeLinterProgPath)
- setEnv "LINT_WHITESPACE" (top -/- root -/- whitespaceLinterProgPath)
-
- -- This lets us bypass the need to generate a config
- -- through Make, which happens in testsuite/mk/boilerplate.mk
- -- which is in turn included by all test 'Makefile's.
- setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath)
-
+ env <- testEnv
-- Execute the test target.
-- We override the verbosity setting to make sure the user can see
-- the test output: https://gitlab.haskell.org/ghc/ghc/issues/15951.
- withVerbosity Diagnostic $ buildWithCmdOptions [] $ test_target RunTest
+ withVerbosity Diagnostic $ buildWithCmdOptions [AddEnv k v | (k,v) <- env] $ test_target RunTest
+
+testEnv :: Action [(String, String)]
+testEnv = do
+ cross <- flag CrossCompiling
+ makePath <- builderPath $ Make ""
+ prog_ghc_pkg <- absolutePathStage Stage1 ghcPkg
+ prog_hsc2hs <- absolutePathStage Stage1 hsc2hs
+ prog_hp2ps <- absolutePathStage Stage1 hp2ps
+ prog_haddock <- absolutePathStage (Stage0 InTreeLibs) haddock
+ prog_hpc <- absolutePathStage (Stage0 InTreeLibs) hpc
+ prog_runghc <- absolutePathStage (Stage0 InTreeLibs) runGhc
+
+ root <- buildRoot
+ args <- userSetting defaultTestArgs
+ let testCompilerArg = testCompiler args
+ ghcPath <- getCompilerPath testCompilerArg
+
+ top <- topDirectory
+ pythonPath <- builderPath Python
+ ccPath <- queryTargetTarget (Toolchain.prgPath . Toolchain.ccProgram . Toolchain.tgtCCompiler)
+ ccFlags <- queryTargetTarget (unwords . Toolchain.prgFlags . Toolchain.ccProgram . Toolchain.tgtCCompiler)
+ ghcFlags <- runTestGhcFlags
+ let ghciFlags = ghcFlags ++ unwords
+ [ "--interactive", "-v0", "-ignore-dot-ghci"
+ , "-fno-ghci-history", "-fprint-error-index-links=never"
+ ]
+
+ -- Many of those env vars are used by Makefiles in the
+ -- test infrastructure, or from tests or their
+ -- Makefiles.
+ return $
+ [ "MAKE" .= makePath
+ , "PYTHON" .= pythonPath
+ , "TEST_HC" .= ghcPath
+ , "TEST_HC_OPTS" .= ghcFlags
+ , "TEST_HC_OPTS_INTERACTIVE" .= ghciFlags
+ , "TEST_CC" .= ccPath
+ , "TEST_CC_OPTS" .= ccFlags
+ , "CHECK_PPR" .= (top -/- root -/- checkPprProgPath)
+ , "CHECK_EXACT" .= (top -/- root -/- checkExactProgPath)
+ , "DUMP_DECLS" .= (top -/- root -/- dumpDeclsProgPath)
+ , "COUNT_DEPS" .= (top -/- root -/- countDepsProgPath)
+ , "LINT_NOTES" .= (top -/- root -/- noteLinterProgPath)
+ , "LINT_CODES" .= (top -/- root -/- codeLinterProgPath)
+ , "LINT_WHITESPACE" .= (top -/- root -/- whitespaceLinterProgPath)
+ -- This lets us bypass the need to generate a config
+ -- through Make, which happens in testsuite/mk/boilerplate.mk
+ -- which is in turn included by all test 'Makefile's.
+ , "ghc_config_mk" .= (top -/- root -/- ghcConfigPath)
+ ] ++
+ if_ cross
+ [ "GHC_PKG" .= prog_ghc_pkg
+ , "HSC2HS" .= prog_hsc2hs
+ , "HP2PS_ABS" .= prog_hp2ps
+ , "HPC" .= prog_hpc
+ , "HADDOCK" .= prog_haddock
+ , "RUNGHC" .= prog_runghc
+ ]
+ where
+ if_ :: Bool -> [a] -> [a]
+ if_ True xs = xs
+ if_ False _ = []
+
+ (.=) = (,)
+
+needProgramStage :: Stage -> Package -> Action ()
+needProgramStage s p = relativePathStage s p >>= need . (:[])
+
+-- | Get relative path for the given program in the given stage.
+relativePathStage :: Stage -> Package -> Action FilePath
+relativePathStage s p = programPath =<< programContext s p
+
+absolutePathStage :: Stage -> Package -> Action FilePath
+absolutePathStage s p =
+ relativePathStage s p >>= make_absolute
+ where
+ make_absolute rel_path = do
+ abs_path <- liftIO (makeAbsolute rel_path)
+ fixAbsolutePathOnWindows abs_path
-- | Given a test compiler and a hadrian dependency (target), check if we
-- can build the target with the compiler
=====================================
libraries/ghc-internal/src/GHC/Internal/Pack.hs
=====================================
@@ -12,95 +12,20 @@
-- Stability : internal
-- Portability : non-portable (GHC Extensions)
--
--- ⚠ Warning: Starting @base-4.18@, this module is being deprecated.
--- See https://gitlab.haskell.org/ghc/ghc/-/issues/21461 for more information.
---
---
---
--- This module provides a small set of low-level functions for packing
--- and unpacking a chunk of bytes. Used by code emitted by the compiler
--- plus the prelude libraries.
---
--- The programmer level view of packed strings is provided by a GHC
--- system library PackedString.
+-- This function is just used by `rts_mkString`
--
-----------------------------------------------------------------------------
module GHC.Internal.Pack
(
- -- (**) - emitted by compiler.
-
- packCString#,
unpackCString,
- unpackCString#,
- unpackNBytes#,
- unpackFoldrCString#, -- (**)
- unpackAppendCString#, -- (**)
)
where
import GHC.Internal.Base
-import GHC.Internal.List ( length )
-import GHC.Internal.ST
import GHC.Internal.Ptr
-data ByteArray ix = ByteArray ix ix ByteArray#
-data MutableByteArray s ix = MutableByteArray ix ix (MutableByteArray# s)
-
unpackCString :: Ptr a -> [Char]
unpackCString a@(Ptr addr)
| a == nullPtr = []
| otherwise = unpackCString# addr
-
-packCString# :: [Char] -> ByteArray#
-packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes }
-
-packString :: [Char] -> ByteArray Int
-packString str = runST (packStringST str)
-
-packStringST :: [Char] -> ST s (ByteArray Int)
-packStringST str =
- let len = length str in
- packNBytesST len str
-
-packNBytesST :: Int -> [Char] -> ST s (ByteArray Int)
-packNBytesST (I# length#) str =
- {-
- allocate an array that will hold the string
- (not forgetting the NUL byte at the end)
- -}
- new_ps_array (length# +# 1#) >>= \ ch_array ->
- -- fill in packed string from "str"
- fill_in ch_array 0# str >>
- -- freeze the puppy:
- freeze_ps_array ch_array length#
- where
- fill_in :: MutableByteArray s Int -> Int# -> [Char] -> ST s ()
- fill_in arr_in# idx [] =
- write_ps_array arr_in# idx (chr# 0#) >>
- return ()
-
- fill_in arr_in# idx (C# c : cs) =
- write_ps_array arr_in# idx c >>
- fill_in arr_in# (idx +# 1#) cs
-
--- (Very :-) ``Specialised'' versions of some CharArray things...
-
-new_ps_array :: Int# -> ST s (MutableByteArray s Int)
-write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s ()
-freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int)
-
-new_ps_array size = ST $ \ s ->
- case (newByteArray# size s) of { (# s2#, barr# #) ->
- (# s2#, MutableByteArray bot bot barr# #) }
- where
- bot = errorWithoutStackTrace "new_ps_array"
-
-write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# ->
- case writeCharArray# barr# n ch s# of { s2# ->
- (# s2#, () #) }
-
--- same as unsafeFreezeByteArray
-freeze_ps_array (MutableByteArray _ _ arr#) len# = ST $ \ s# ->
- case unsafeFreezeByteArray# arr# s# of { (# s2#, frozen# #) ->
- (# s2#, ByteArray 0 (I# len#) frozen# #) }
=====================================
testsuite/tests/ghci/should_run/Makefile
=====================================
@@ -7,3 +7,9 @@ T3171:
echo "do Control.Concurrent.threadDelay 3000000; putStrLn \"threadDelay was not interrupted\"" | \
"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) & \
sleep 2; kill -INT $$!; wait
+
+TopEnvIface:
+ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface
+ # Second compilation starts from interface files, but still can print "a"
+ "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) TopEnvIface -v1 -e "a" -e ":q" -fwrite-if-simplified-core -fwrite-interface
+
=====================================
testsuite/tests/ghci/should_run/TopEnvIface.hs
=====================================
@@ -0,0 +1,4 @@
+module TopEnvIface where
+
+import TopEnvIface2
+
=====================================
testsuite/tests/ghci/should_run/TopEnvIface.stdout
=====================================
@@ -0,0 +1,8 @@
+[1 of 2] Compiling TopEnvIface2 ( TopEnvIface2.hs, interpreted )
+[2 of 2] Compiling TopEnvIface ( TopEnvIface.hs, interpreted )
+Ok, two modules loaded.
+"I should be printed twice"
+Leaving GHCi.
+Ok, two modules loaded.
+"I should be printed twice"
+Leaving GHCi.
=====================================
testsuite/tests/ghci/should_run/TopEnvIface2.hs
=====================================
@@ -0,0 +1,3 @@
+module TopEnvIface2 where
+
+a = "I should be printed twice"
=====================================
testsuite/tests/ghci/should_run/all.T
=====================================
@@ -96,3 +96,4 @@ test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O
test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script'])
test('T10920', [only_ways(ghci_ways), extra_files(['LocalPrelude/Prelude.hs'])], ghci_script, ['T10920.script'])
+test('TopEnvIface', [only_ways(ghci_ways)], makefile_test, [])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ac8222607ba91e0de2eb22577b3c491d20b818b...6e0710bcbccb97b2555c6664bcfaed9aeac636a0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ac8222607ba91e0de2eb22577b3c491d20b818b...6e0710bcbccb97b2555c6664bcfaed9aeac636a0
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250303/99616552/attachment-0001.html>
More information about the ghc-commits
mailing list