module InteractiveEvalTypes (
Resume(..), History(..), ExecResult(..),
SingleStep(..), isStep, ExecOptions(..),
BreakInfo(..)
) where
import GhcPrelude
import GHCi.RemoteTypes
import GHCi.Message (EvalExpr, ResumeContext)
import Id
import Name
import Module
import RdrName
import Type
import SrcLoc
import Exception
import Data.Word
import GHC.Stack.CCS
data ExecOptions
= ExecOptions
{ execSingleStep :: SingleStep
, execSourceFile :: String
, execLineNumber :: Int
, execWrap :: ForeignHValue -> EvalExpr ForeignHValue
}
data SingleStep
= RunToCompletion
| SingleStep
| RunAndLogSteps
isStep :: SingleStep -> Bool
isStep RunToCompletion = False
isStep _ = True
data ExecResult
= ExecComplete
{ execResult :: Either SomeException [Name]
, execAllocation :: Word64
}
| ExecBreak
{ breakNames :: [Name]
, breakInfo :: Maybe BreakInfo
}
data BreakInfo = BreakInfo
{ breakInfo_module :: Module
, breakInfo_number :: Int
}
data Resume = Resume
{ resumeStmt :: String
, resumeContext :: ForeignRef (ResumeContext [HValueRef])
, resumeBindings :: ([TyThing], GlobalRdrEnv)
, resumeFinalIds :: [Id]
, resumeApStack :: ForeignHValue
, resumeBreakInfo :: Maybe BreakInfo
, resumeSpan :: SrcSpan
, resumeDecl :: String
, resumeCCS :: RemotePtr CostCentreStack
, resumeHistory :: [History]
, resumeHistoryIx :: Int
}
data History
= History {
historyApStack :: ForeignHValue,
historyBreakInfo :: BreakInfo,
historyEnclosingDecls :: [String]
}