never executed always true always false
1 -- -----------------------------------------------------------------------------
2 --
3 -- (c) The University of Glasgow, 2005-2007
4 --
5 -- Running statements interactively
6 --
7 -- -----------------------------------------------------------------------------
8
9 module GHC.Runtime.Eval.Types (
10 Resume(..), ResumeBindings, IcGlobalRdrEnv(..),
11 History(..), ExecResult(..),
12 SingleStep(..), isStep, ExecOptions(..)
13 ) where
14
15 import GHC.Prelude
16
17 import GHCi.RemoteTypes
18 import GHCi.Message (EvalExpr, ResumeContext)
19 import GHC.Types.Id
20 import GHC.Types.Name
21 import GHC.Types.TyThing
22 import GHC.Types.BreakInfo
23 import GHC.Types.Name.Reader
24 import GHC.Types.SrcLoc
25 import GHC.Utils.Exception
26
27 import Data.Word
28 import GHC.Stack.CCS
29
30 data ExecOptions
31 = ExecOptions
32 { execSingleStep :: SingleStep -- ^ stepping mode
33 , execSourceFile :: String -- ^ filename (for errors)
34 , execLineNumber :: Int -- ^ line number (for errors)
35 , execWrap :: ForeignHValue -> EvalExpr ForeignHValue
36 }
37
38 data SingleStep
39 = RunToCompletion
40 | SingleStep
41 | RunAndLogSteps
42
43 isStep :: SingleStep -> Bool
44 isStep RunToCompletion = False
45 isStep _ = True
46
47 data ExecResult
48 = ExecComplete
49 { execResult :: Either SomeException [Name]
50 , execAllocation :: Word64
51 }
52 | ExecBreak
53 { breakNames :: [Name]
54 , breakInfo :: Maybe BreakInfo
55 }
56
57 -- | Essentially a GlobalRdrEnv, but with additional cached values to allow
58 -- efficient re-calculation when the imports change.
59 -- Fields are strict to avoid space leaks (see T4029)
60 -- All operations are in GHC.Runtime.Context.
61 -- See Note [icReaderEnv recalculation]
62 data IcGlobalRdrEnv = IcGlobalRdrEnv
63 { igre_env :: !GlobalRdrEnv
64 -- ^ The final environment
65 , igre_prompt_env :: !GlobalRdrEnv
66 -- ^ Just the things defined at the prompt (excluding imports!)
67 }
68
69 data Resume = Resume
70 { resumeStmt :: String -- the original statement
71 , resumeContext :: ForeignRef (ResumeContext [HValueRef])
72 , resumeBindings :: ResumeBindings
73 , resumeFinalIds :: [Id] -- [Id] to bind on completion
74 , resumeApStack :: ForeignHValue -- The object from which we can get
75 -- value of the free variables.
76 , resumeBreakInfo :: Maybe BreakInfo
77 -- the breakpoint we stopped at
78 -- (module, index)
79 -- (Nothing <=> exception)
80 , resumeSpan :: SrcSpan -- just a copy of the SrcSpan
81 -- from the ModBreaks,
82 -- otherwise it's a pain to
83 -- fetch the ModDetails &
84 -- ModBreaks to get this.
85 , resumeDecl :: String -- ditto
86 , resumeCCS :: RemotePtr CostCentreStack
87 , resumeHistory :: [History]
88 , resumeHistoryIx :: Int -- 0 <==> at the top of the history
89 }
90
91 type ResumeBindings = ([TyThing], IcGlobalRdrEnv)
92
93 data History
94 = History {
95 historyApStack :: ForeignHValue,
96 historyBreakInfo :: BreakInfo,
97 historyEnclosingDecls :: [String] -- declarations enclosing the breakpoint
98 }