ghc-6.10.2: The GHC APIContentsIndex
GhciMonad
Documentation
type Command = (String, String -> GHCi Bool, Maybe String, String -> IO [String])
data GHCiState
Constructors
GHCiState
progname :: String
args :: [String]
prompt :: String
editor :: String
stop :: String
options :: [GHCiOption]
prelude :: Module
break_ctr :: !Int
breaks :: ![(Int, BreakLocation)]
tickarrays :: ModuleEnv TickArray
last_command :: Maybe Command
cmdqueue :: [String]
remembered_ctx :: [(CtxtCmd, [String], [String])]
ghc_e :: Bool
data CtxtCmd
Constructors
SetContext
AddModules
RemModules
type TickArray = Array Int [(BreakIndex, SrcSpan)]
data GHCiOption
Constructors
ShowTiming
ShowType
RevertCAFs
show/hide Instances
data BreakLocation
Constructors
BreakLocation
breakModule :: !Module
breakLoc :: !SrcSpan
breakTick :: !Int
onBreakCmd :: String
show/hide Instances
prettyLocations :: [(Int, BreakLocation)] -> SDoc
recordBreak :: BreakLocation -> GHCi (Bool, Int)
newtype GHCi a
Constructors
GHCi
unGHCi :: IORef GHCiState -> Ghc a
show/hide Instances
reflectGHCi :: (Session, IORef GHCiState) -> GHCi a -> IO a
reifyGHCi :: ((Session, IORef GHCiState) -> IO a) -> GHCi a
startGHCi :: GHCi a -> GHCiState -> Ghc a
ghciHandleGhcException :: (GhcException -> GHCi a) -> GHCi a -> GHCi a
getGHCiState :: GHCi GHCiState
setGHCiState :: GHCiState -> GHCi ()
liftGhc :: Ghc a -> GHCi a
getPrelude :: GHCi Module
saved_sess :: IORef Session
no_saved_sess :: Session
saveSession :: GHCi ()
splatSavedSession :: GHCi ()
withRestoredSession :: Ghc a -> IO a
getDynFlags :: GHCi DynFlags
setDynFlags :: DynFlags -> GHCi [PackageId]
isOptionSet :: GHCiOption -> GHCi Bool
setOption :: GHCiOption -> GHCi ()
unsetOption :: GHCiOption -> GHCi ()
io :: IO a -> GHCi a
printForUser :: SDoc -> GHCi ()
printForUserPartWay :: SDoc -> GHCi ()
runStmt :: String -> SingleStep -> GHCi RunResult
resume :: (SrcSpan -> Bool) -> SingleStep -> GHCi RunResult
timeIt :: GHCi a -> GHCi a
getAllocations :: IO Int64
printTimes :: Integer -> Integer -> IO ()
revertCAFs :: GHCi ()
rts_revertCAFs :: IO ()
stdin_ptr :: IORef (Ptr ())
stdout_ptr :: IORef (Ptr ())
stderr_ptr :: IORef (Ptr ())
initInterpBuffering :: Ghc ()
flushInterpBuffers :: GHCi ()
turnOffBuffering :: IO ()
getHandle :: IORef (Ptr ()) -> IO Handle
Produced by Haddock version 2.4.2