Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Resume = Resume {
- resumeStmt :: String
- resumeContext :: ForeignRef (ResumeContext [HValueRef])
- resumeBindings :: ResumeBindings
- resumeFinalIds :: [Id]
- resumeApStack :: ForeignHValue
- resumeBreakInfo :: Maybe BreakInfo
- resumeSpan :: SrcSpan
- resumeDecl :: String
- resumeCCS :: RemotePtr CostCentreStack
- resumeHistory :: [History]
- resumeHistoryIx :: Int
- data History = History {}
- execStmt :: GhcMonad m => String -> ExecOptions -> m ExecResult
- execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
- data ExecOptions = ExecOptions {}
- execOptions :: ExecOptions
- data ExecResult
- = ExecComplete { }
- | ExecBreak {
- breakNames :: [Name]
- breakInfo :: Maybe BreakInfo
- resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m ExecResult
- runDecls :: GhcMonad m => String -> m [Name]
- runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
- runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name]
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
- data SingleStep
- abandon :: GhcMonad m => m Bool
- abandonAll :: GhcMonad m => m Bool
- getResumeContext :: GhcMonad m => m [Resume]
- getHistorySpan :: HscEnv -> History -> SrcSpan
- getModBreaks :: HomeModInfo -> ModBreaks
- getHistoryModule :: History -> Module
- setupBreakpoint :: GhcMonad m => HscEnv -> BreakInfo -> Int -> m ()
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- setContext :: GhcMonad m => [InteractiveImport] -> m ()
- getContext :: GhcMonad m => m [InteractiveImport]
- getNamesInScope :: GhcMonad m => m [Name]
- getRdrNamesInScope :: GhcMonad m => m [RdrName]
- moduleIsInterpreted :: GhcMonad m => Module -> m Bool
- getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- exprType :: GhcMonad m => TcRnExprMode -> String -> m Type
- typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind)
- parseName :: GhcMonad m => String -> m (NonEmpty Name)
- parseInstanceHead :: GhcMonad m => String -> m Type
- getInstancesForType :: GhcMonad m => Type -> m [ClsInst]
- getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe [HsDoc GhcRn], IntMap (HsDoc GhcRn)))
- data GetDocsFailure
- showModule :: GhcMonad m => ModSummary -> m String
- moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
- parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs)
- compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue
- compileExpr :: GhcMonad m => String -> m HValue
- dynCompileExpr :: GhcMonad m => String -> m Dynamic
- compileExprRemote :: GhcMonad m => String -> m ForeignHValue
- compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue
- data Term
- = Term { }
- | Prim { }
- | Suspension {
- ctype :: ClosureType
- ty :: RttiType
- val :: ForeignHValue
- bound_to :: Maybe Name
- | NewtypeWrap { }
- | RefWrap {
- ty :: RttiType
- wrapped_term :: Term
- obtainTermFromId :: HscEnv -> Int -> Bool -> Id -> IO Term
- obtainTermFromVal :: HscEnv -> Int -> Bool -> Type -> a -> IO Term
- reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type)
Documentation
:: GhcMonad m | |
=> String | a statement (bind or expression) |
-> ExecOptions | |
-> m ExecResult |
Run a statement in the current interactive context.
execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult Source #
Like execStmt
, but takes a parsed statement as argument. Useful when
doing preprocessing on the AST before execution, e.g. in GHCi (see
GHCi.UI.runStmt).
data ExecOptions Source #
ExecOptions | |
|
execOptions :: ExecOptions Source #
default ExecOptions
data ExecResult Source #
resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> Maybe Int -> m ExecResult Source #
runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name] Source #
Run some declarations and return any user-visible names that were brought into scope.
runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name] Source #
Like runDeclsWithLocation
, but takes parsed declarations as argument.
Useful when doing preprocessing on the AST before execution, e.g. in GHCi
(see GHCi.UI.runStmt).
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) Source #
abandonAll :: GhcMonad m => m Bool Source #
getResumeContext :: GhcMonad m => m [Resume] Source #
getModBreaks :: HomeModInfo -> ModBreaks Source #
getHistoryModule :: History -> Module Source #
setContext :: GhcMonad m => [InteractiveImport] -> m () Source #
Set the interactive evaluation context.
(setContext imports) sets the ic_imports field (which in turn
determines what is in scope at the prompt) to imports
, and
updates the icReaderEnv environment to reflect it.
We retain in scope all the things defined at the prompt, and kept in ic_tythings. (Indeed, they shadow stuff from ic_imports.)
getContext :: GhcMonad m => m [InteractiveImport] Source #
Get the interactive evaluation context, consisting of a pair of the set of modules from which we take the full top-level scope, and the set of modules from which we take just the exports respectively.
getNamesInScope :: GhcMonad m => m [Name] Source #
Returns all names in scope in the current interactive context
getRdrNamesInScope :: GhcMonad m => m [RdrName] Source #
Returns all RdrName
s in scope in the current interactive
context, excluding any that are internally-generated.
moduleIsInterpreted :: GhcMonad m => Module -> m Bool Source #
Returns True
if the specified module is interpreted, and hence has
its full top-level scope available.
getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)) Source #
Looks up an identifier in the current interactive context (for :info) Filter the instances by the ones whose tycons (or classes resp) are in scope (qualified or otherwise). Otherwise we list a whole lot too many! The exact choice of which ones to show, and which to hide, is a judgement call. (see #1581)
exprType :: GhcMonad m => TcRnExprMode -> String -> m Type Source #
Get the type of an expression
Returns the type as described by TcRnExprMode
parseName :: GhcMonad m => String -> m (NonEmpty Name) Source #
Parses a string as an identifier, and returns the list of Name
s that
the identifier can refer to in the current interactive context.
getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe [HsDoc GhcRn], IntMap (HsDoc GhcRn))) Source #
data GetDocsFailure Source #
Failure modes for getDocs
.
NameHasNoModule Name |
|
NoDocsInIface | The module was loaded without |
InteractiveName | The |
Instances
Outputable GetDocsFailure Source # | |
Defined in GHC.Runtime.Eval ppr :: GetDocsFailure -> SDoc Source # |
showModule :: GhcMonad m => ModSummary -> m String Source #
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool Source #
parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs) Source #
Parse an expression, the parsed expression can be further processed and passed to compileParsedExpr.
compileExpr :: GhcMonad m => String -> m HValue Source #
Compile an expression, run it, and deliver the resulting HValue.
dynCompileExpr :: GhcMonad m => String -> m Dynamic Source #
Compile an expression, run it and return the result as a Dynamic.
compileExprRemote :: GhcMonad m => String -> m ForeignHValue Source #
Compile an expression, run it, and deliver the resulting HValue.
compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue Source #
Compile a parsed expression (before renaming), run it, and deliver the resulting HValue.
Term | |
Prim | |
Suspension | |
| |
NewtypeWrap | |
RefWrap | |
|