ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Runtime.Interpreter

Description

Interacting with the iserv interpreter, whether it is running on an external process or in the current process.

Synopsis

High-level interface to the interpreter

evalStmt :: HscEnv -> Bool -> EvalExpr ForeignHValue -> IO (EvalStatus_ [ForeignHValue] [HValueRef]) Source #

Execute an action of type IO [a], returning ForeignHValues for each of the results.

data EvalStatus_ a b #

Constructors

EvalComplete Word64 (EvalResult a) 
EvalBreak Bool HValueRef Int Int (RemoteRef (ResumeContext b)) (RemotePtr CostCentreStack) 

Instances

Instances details
Show a => Show (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Methods

showsPrec :: Int -> EvalStatus_ a b -> ShowS #

show :: EvalStatus_ a b -> String #

showList :: [EvalStatus_ a b] -> ShowS #

Generic (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalStatus_ a b) :: Type -> Type #

Methods

from :: EvalStatus_ a b -> Rep (EvalStatus_ a b) x #

to :: Rep (EvalStatus_ a b) x -> EvalStatus_ a b #

Binary a => Binary (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Methods

put :: EvalStatus_ a b -> Put #

get :: Get (EvalStatus_ a b) #

putList :: [EvalStatus_ a b] -> Put #

type Rep (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

type EvalStatus a = EvalStatus_ a a #

data EvalResult a #

Constructors

EvalException SerializableException 
EvalSuccess a 

Instances

Instances details
Show a => Show (EvalResult a) 
Instance details

Defined in GHCi.Message

Generic (EvalResult a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalResult a) :: Type -> Type #

Methods

from :: EvalResult a -> Rep (EvalResult a) x #

to :: Rep (EvalResult a) x -> EvalResult a #

Binary a => Binary (EvalResult a) 
Instance details

Defined in GHCi.Message

Methods

put :: EvalResult a -> Put #

get :: Get (EvalResult a) #

putList :: [EvalResult a] -> Put #

type Rep (EvalResult a) 
Instance details

Defined in GHCi.Message

type Rep (EvalResult a) = D1 ('MetaData "EvalResult" "GHCi.Message" "ghc-lib-parser-0.20201101-isyDBvgoNDKP6i3o2E3m7" 'False) (C1 ('MetaCons "EvalException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SerializableException)) :+: C1 ('MetaCons "EvalSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data EvalExpr a #

Constructors

EvalThis a 
EvalApp (EvalExpr a) (EvalExpr a) 

Instances

Instances details
Show a => Show (EvalExpr a) 
Instance details

Defined in GHCi.Message

Methods

showsPrec :: Int -> EvalExpr a -> ShowS #

show :: EvalExpr a -> String #

showList :: [EvalExpr a] -> ShowS #

Generic (EvalExpr a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalExpr a) :: Type -> Type #

Methods

from :: EvalExpr a -> Rep (EvalExpr a) x #

to :: Rep (EvalExpr a) x -> EvalExpr a #

Binary a => Binary (EvalExpr a) 
Instance details

Defined in GHCi.Message

Methods

put :: EvalExpr a -> Put #

get :: Get (EvalExpr a) #

putList :: [EvalExpr a] -> Put #

type Rep (EvalExpr a) 
Instance details

Defined in GHCi.Message

type Rep (EvalExpr a) = D1 ('MetaData "EvalExpr" "GHCi.Message" "ghc-lib-parser-0.20201101-isyDBvgoNDKP6i3o2E3m7" 'False) (C1 ('MetaCons "EvalThis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "EvalApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (EvalExpr a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (EvalExpr a))))

resumeStmt :: HscEnv -> Bool -> ForeignRef (ResumeContext [HValueRef]) -> IO (EvalStatus_ [ForeignHValue] [HValueRef]) Source #

abandonStmt :: HscEnv -> ForeignRef (ResumeContext [HValueRef]) -> IO () Source #

evalIO :: HscEnv -> ForeignHValue -> IO () Source #

Execute an action of type IO ()

evalString :: HscEnv -> ForeignHValue -> IO String Source #

Execute an action of type IO String

evalStringToIOString :: HscEnv -> ForeignHValue -> String -> IO String Source #

Execute an action of type String -> IO String

mallocData :: HscEnv -> ByteString -> IO (RemotePtr ()) Source #

Allocate and store the given bytes in memory, returning a pointer to the memory in the remote process.

createBCOs :: HscEnv -> [ResolvedBCO] -> IO [HValueRef] Source #

Create a set of BCOs that may be mutually recursive.

newBreakArray :: HscEnv -> Int -> IO (ForeignRef BreakArray) Source #

enableBreakpoint :: HscEnv -> ForeignRef BreakArray -> Int -> Bool -> IO () Source #

breakpointStatus :: HscEnv -> ForeignRef BreakArray -> Int -> IO Bool Source #

getModBreaks :: HomeModInfo -> ModBreaks Source #

seqHValue :: HscEnv -> ForeignHValue -> IO (EvalResult ()) Source #

Send a Seq message to the iserv process to force a value #2950

interpreterDynamic :: Interp -> Bool Source #

Interpreter uses Dynamic way

interpreterProfiled :: Interp -> Bool Source #

Interpreter uses Profiling way

The object-code linker

lookupSymbol :: HscEnv -> FastString -> IO (Maybe (Ptr ())) Source #

lookupClosure :: HscEnv -> String -> IO (Maybe HValueRef) Source #

loadDLL :: HscEnv -> String -> IO (Maybe String) Source #

loadDLL loads a dynamic library using the OS's native linker (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either an absolute pathname to the file, or a relative filename (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL searches the standard locations for the appropriate library.

Returns:

Nothing => success Just err_msg => failure

Lower-level API using messages

iservCmd :: Binary a => HscEnv -> Message a -> IO a Source #

Run a command in the interpreter's context. With -fexternal-interpreter, the command is serialized and sent to an external iserv process, and the response is deserialized (hence the Binary constraint). With -fno-external-interpreter we execute the command directly here.

data Message a where #

Constructors

Shutdown :: Message () 
RtsRevertCAFs :: Message () 
InitLinker :: Message () 
LookupSymbol :: String -> Message (Maybe (RemotePtr ())) 
LookupClosure :: String -> Message (Maybe HValueRef) 
LoadDLL :: String -> Message (Maybe String) 
LoadArchive :: String -> Message () 
LoadObj :: String -> Message () 
UnloadObj :: String -> Message () 
AddLibrarySearchPath :: String -> Message (RemotePtr ()) 
RemoveLibrarySearchPath :: RemotePtr () -> Message Bool 
ResolveObjs :: Message Bool 
FindSystemLibrary :: String -> Message (Maybe String) 
CreateBCOs :: [ByteString] -> Message [HValueRef] 
FreeHValueRefs :: [HValueRef] -> Message () 
AddSptEntry :: Fingerprint -> HValueRef -> Message () 
MallocData :: ByteString -> Message (RemotePtr ()) 
MallocStrings :: [ByteString] -> Message [RemotePtr ()] 
PrepFFI :: FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif) 
FreeFFI :: RemotePtr C_ffi_cif -> Message () 
MkConInfoTable :: Bool -> Int -> Int -> Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable) 
EvalStmt :: EvalOpts -> EvalExpr HValueRef -> Message (EvalStatus_ [HValueRef] [HValueRef]) 
ResumeStmt :: EvalOpts -> RemoteRef (ResumeContext [HValueRef]) -> Message (EvalStatus_ [HValueRef] [HValueRef]) 
AbandonStmt :: RemoteRef (ResumeContext [HValueRef]) -> Message () 
EvalString :: HValueRef -> Message (EvalResult String) 
EvalStringToString :: HValueRef -> String -> Message (EvalResult String) 
EvalIO :: HValueRef -> Message (EvalResult ()) 
MkCostCentres :: String -> [(String, String)] -> Message [RemotePtr CostCentre] 
CostCentreStackInfo :: RemotePtr CostCentreStack -> Message [String] 
NewBreakArray :: Int -> Message (RemoteRef BreakArray) 
EnableBreakpoint :: RemoteRef BreakArray -> Int -> Bool -> Message () 
BreakpointStatus :: RemoteRef BreakArray -> Int -> Message Bool 
GetBreakpointVar :: HValueRef -> Int -> Message (Maybe HValueRef) 
StartTH :: Message (RemoteRef (IORef QState)) 
RunTH :: RemoteRef (IORef QState) -> HValueRef -> THResultType -> Maybe Loc -> Message (QResult ByteString) 
RunModFinalizers :: RemoteRef (IORef QState) -> [RemoteRef (Q ())] -> Message (QResult ()) 
GetClosure :: HValueRef -> Message (GenClosure HValueRef) 
Seq :: HValueRef -> Message (EvalStatus_ () ()) 
ResumeSeq :: RemoteRef (ResumeContext ()) -> Message (EvalStatus_ () ()) 

Instances

Instances details
Show (Message a) 
Instance details

Defined in GHCi.Message

Methods

showsPrec :: Int -> Message a -> ShowS #

show :: Message a -> String #

showList :: [Message a] -> ShowS #

withIServ :: ExceptionMonad m => IServConfig -> IServ -> (IServInstance -> m (IServInstance, a)) -> m a Source #

Grab a lock on the IServ and do something with it. Overloaded because this is used from TcM as well as IO.

withIServ_ :: (MonadIO m, ExceptionMonad m) => IServConfig -> IServ -> (IServInstance -> m a) -> m a Source #

withInterp :: HscEnv -> (Interp -> IO a) -> IO a Source #

Execute an action with the interpreter

Fails if no target code interpreter is available

hscInterp :: HscEnv -> Interp Source #

Retreive the targe code interpreter

Fails if no target code interpreter is available

stopInterp :: HscEnv -> IO () Source #

Stop the interpreter

iservCall :: Binary a => IServInstance -> Message a -> IO a Source #

Send a Message and receive the response from the iserv process

readIServ :: IServInstance -> Get a -> IO a Source #

Read a value from the iserv process

writeIServ :: IServInstance -> Put -> IO () Source #

Send a value to the iserv process

freeHValueRefs :: HscEnv -> [HValueRef] -> IO () Source #

mkFinalizedHValue :: HscEnv -> RemoteRef a -> IO (ForeignRef a) Source #

Creates a ForeignRef that will automatically release the RemoteRef when it is no longer referenced.

wormhole :: Interp -> ForeignRef a -> IO a Source #

Convert a ForeignRef to the value it references directly. This only works when the interpreter is running in the same process as the compiler, so it fails when -fexternal-interpreter is on.

wormholeRef :: Interp -> RemoteRef a -> IO a Source #

Convert an RemoteRef to the value it references directly. This only works when the interpreter is running in the same process as the compiler, so it fails when -fexternal-interpreter is on.

mkEvalOpts :: DynFlags -> Bool -> EvalOpts Source #