- data RunResult
- = RunOk [Name]
- | RunFailed
- | RunException SomeException
- | RunBreak ThreadId [Name] (Maybe BreakInfo)
- data Status
- data Resume = Resume {
- resumeStmt :: String
- resumeThreadId :: ThreadId
- resumeBreakMVar :: MVar ()
- resumeStatMVar :: MVar Status
- resumeBindings :: [Id]
- resumeFinalIds :: [Id]
- resumeApStack :: HValue
- resumeBreakInfo :: Maybe BreakInfo
- resumeSpan :: SrcSpan
- resumeHistory :: [History]
- resumeHistoryIx :: Int
- data History = History {}
- runStmt :: GhcMonad m => String -> SingleStep -> m RunResult
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl RdrName)
- data SingleStep
- resume :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m RunResult
- 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
- back :: GhcMonad m => m ([Name], Int, SrcSpan)
- forward :: GhcMonad m => m ([Name], Int, SrcSpan)
- setContext :: GhcMonad m => [Module] -> [(Module, Maybe (ImportDecl RdrName))] -> m ()
- getContext :: GhcMonad m => m ([Module], [(Module, Maybe (ImportDecl RdrName))])
- availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
- getNamesInScope :: GhcMonad m => m [Name]
- getRdrNamesInScope :: GhcMonad m => m [RdrName]
- moduleIsInterpreted :: GhcMonad m => Module -> m Bool
- getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance]))
- exprType :: GhcMonad m => String -> m Type
- typeKind :: GhcMonad m => String -> m Kind
- parseName :: GhcMonad m => String -> m [Name]
- showModule :: GhcMonad m => ModSummary -> m String
- isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool
- compileExpr :: GhcMonad m => String -> m HValue
- dynCompileExpr :: GhcMonad m => String -> m Dynamic
- data Term
- = Term { }
- | Prim { }
- | Suspension { }
- | 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
RunOk [Name] | names bound by this evaluation |
RunFailed | statement failed compilation |
RunException SomeException | statement raised an exception |
RunBreak ThreadId [Name] (Maybe BreakInfo) |
Resume | |
|
History | |
|
runStmt :: GhcMonad m => String -> SingleStep -> m RunResultSource
Run a statement in the current interactive context. Statement may bind multple values.
parseImportDecl :: GhcMonad m => String -> m (ImportDecl RdrName)Source
abandonAll :: GhcMonad m => m BoolSource
getResumeContext :: GhcMonad m => m [Resume]Source
getHistorySpan :: HscEnv -> History -> SrcSpanSource
:: GhcMonad m | |
=> [Module] | entire top level scope of these modules |
-> [(Module, Maybe (ImportDecl RdrName))] | exports of these modules |
-> m () |
Set the interactive evaluation context.
Setting the context doesn't throw away any bindings; the bindings we've built up in the InteractiveContext simply move to the new module. They always shadow anything in scope in the current context.
getContext :: GhcMonad m => m ([Module], [(Module, Maybe (ImportDecl RdrName))])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
moduleIsInterpreted :: GhcMonad m => Module -> m BoolSource
Returns True
if the specified module is interpreted, and hence has
its full top-level scope available.
getInfo :: GhcMonad m => Name -> m (Maybe (TyThing, Fixity, [Instance]))Source
Looks up an identifier in the current interactive context (for :info) Filter the instances by the ones whose tycons (or clases 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 Trac #1581)
parseName :: GhcMonad m => String -> m [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.
showModule :: GhcMonad m => ModSummary -> m StringSource
isModuleInterpreted :: GhcMonad m => ModSummary -> m BoolSource
compileExpr :: GhcMonad m => String -> m HValueSource
dynCompileExpr :: GhcMonad m => String -> m DynamicSource
Term | |
Prim | |
Suspension | |
NewtypeWrap | |
RefWrap | |
|