Safe Haskell | None |
---|---|
Language | Haskell98 |
- data RunResult
- = RunOk [Name]
- | RunException SomeException
- | RunBreak ThreadId [Name] (Maybe BreakInfo)
- data Status
- data Resume = Resume {
- resumeStmt :: String
- resumeThreadId :: ThreadId
- resumeBreakMVar :: MVar ()
- resumeStatMVar :: MVar Status
- resumeBindings :: ([TyThing], GlobalRdrEnv)
- resumeFinalIds :: [Id]
- resumeApStack :: HValue
- resumeBreakInfo :: Maybe BreakInfo
- resumeSpan :: SrcSpan
- resumeHistory :: [History]
- resumeHistoryIx :: Int
- data History = History {}
- runStmt :: GhcMonad m => String -> SingleStep -> m RunResult
- runStmtWithLocation :: GhcMonad m => String -> Int -> String -> SingleStep -> m RunResult
- runDecls :: GhcMonad m => String -> m [Name]
- runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
- 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 => [InteractiveImport] -> m ()
- getContext :: GhcMonad m => m [InteractiveImport]
- availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv
- 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]))
- exprType :: GhcMonad m => String -> m Type
- typeKind :: GhcMonad m => Bool -> String -> m (Type, 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 |
RunException SomeException | statement raised an exception |
RunBreak ThreadId [Name] (Maybe BreakInfo) |
Resume | |
|
runStmt :: GhcMonad m => String -> SingleStep -> m RunResult Source
Run a statement in the current interactive context. Statement may bind multple values.
runStmtWithLocation :: GhcMonad m => String -> Int -> String -> SingleStep -> m RunResult Source
Run a statement in the current interactive context. Passing debug information Statement may bind multple values.
parseImportDecl :: GhcMonad m => String -> m (ImportDecl RdrName) Source
abandonAll :: GhcMonad m => m Bool Source
getResumeContext :: GhcMonad m => m [Resume] Source
getHistorySpan :: HscEnv -> History -> SrcSpan 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
constructs the ic_rn_glb_env 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.
availsToGlobalRdrEnv :: ModuleName -> [AvailInfo] -> GlobalRdrEnv Source
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 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])) 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)
exprType :: GhcMonad m => String -> m Type Source
Get the type of an expression Returns its most general type
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 String Source
isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool Source
compileExpr :: GhcMonad m => String -> m HValue Source
dynCompileExpr :: GhcMonad m => String -> m Dynamic Source
Term | |
Prim | |
Suspension | |
NewtypeWrap | |
RefWrap | |
|