module GHC.Runtime.Eval.Types (
Resume(..), ResumeBindings, IcGlobalRdrEnv(..),
History(..), ExecResult(..),
SingleStep(..), enableGhcStepMode, breakHere,
ExecOptions(..)
) where
import GHC.Prelude
import GHCi.RemoteTypes
import GHCi.Message (EvalExpr, ResumeContext)
import GHC.Types.Id
import GHC.Types.Name
import GHC.Types.TyThing
import GHC.Types.Breakpoint
import GHC.Types.Name.Reader
import GHC.Types.SrcLoc
import GHC.Utils.Exception
import Data.Word
import GHC.Stack.CCS
data ExecOptions
= ExecOptions
{ ExecOptions -> SingleStep
execSingleStep :: SingleStep
, ExecOptions -> String
execSourceFile :: String
, ExecOptions -> Int
execLineNumber :: Int
, ExecOptions -> ForeignHValue -> EvalExpr ForeignHValue
execWrap :: ForeignHValue -> EvalExpr ForeignHValue
}
data SingleStep
= RunToCompletion
| RunAndLogSteps
| SingleStep
| LocalStep
{ SingleStep -> SrcSpan
breakAt :: SrcSpan }
| ModuleStep
{ breakAt :: SrcSpan }
enableGhcStepMode :: SingleStep -> Bool
enableGhcStepMode :: SingleStep -> Bool
enableGhcStepMode SingleStep
RunToCompletion = Bool
False
enableGhcStepMode SingleStep
_ = Bool
True
breakHere :: SingleStep -> SrcSpan -> Bool
breakHere :: SingleStep -> SrcSpan -> Bool
breakHere SingleStep
step SrcSpan
break_span = case SingleStep
step of
SingleStep
RunToCompletion -> Bool
False
SingleStep
RunAndLogSteps -> Bool
False
SingleStep
SingleStep -> Bool
True
LocalStep SrcSpan
span -> SrcSpan
break_span SrcSpan -> SrcSpan -> Bool
`isSubspanOf` SrcSpan
span
ModuleStep SrcSpan
span -> SrcSpan -> Maybe FastString
srcSpanFileName_maybe SrcSpan
span Maybe FastString -> Maybe FastString -> Bool
forall a. Eq a => a -> a -> Bool
== SrcSpan -> Maybe FastString
srcSpanFileName_maybe SrcSpan
break_span
data ExecResult
= ExecComplete
{ ExecResult -> Either SomeException [Name]
execResult :: Either SomeException [Name]
, ExecResult -> Word64
execAllocation :: Word64
}
| ExecBreak
{ ExecResult -> [Name]
breakNames :: [Name]
, ExecResult -> Maybe InternalBreakpointId
breakPointId :: Maybe InternalBreakpointId
}
data IcGlobalRdrEnv = IcGlobalRdrEnv
{ IcGlobalRdrEnv -> GlobalRdrEnv
igre_env :: !GlobalRdrEnv
, IcGlobalRdrEnv -> GlobalRdrEnv
igre_prompt_env :: !GlobalRdrEnv
}
data Resume = Resume
{ Resume -> String
resumeStmt :: String
, Resume -> ForeignRef (ResumeContext [HValueRef])
resumeContext :: ForeignRef (ResumeContext [HValueRef])
, Resume -> ResumeBindings
resumeBindings :: ResumeBindings
, Resume -> [Id]
resumeFinalIds :: [Id]
, Resume -> ForeignHValue
resumeApStack :: ForeignHValue
, Resume -> Maybe InternalBreakpointId
resumeBreakpointId :: Maybe InternalBreakpointId
, Resume -> SrcSpan
resumeSpan :: SrcSpan
, Resume -> String
resumeDecl :: String
, Resume -> RemotePtr CostCentreStack
resumeCCS :: RemotePtr CostCentreStack
, Resume -> [History]
resumeHistory :: [History]
, Resume -> Int
resumeHistoryIx :: Int
}
type ResumeBindings = ([TyThing], IcGlobalRdrEnv)
data History = History
{ History -> ForeignHValue
historyApStack :: ForeignHValue
, History -> InternalBreakpointId
historyBreakpointId :: InternalBreakpointId
, History -> [String]
historyEnclosingDecls :: [String]
}