ghc-9.2.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Runtime.Interpreter

Description

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

Synopsis

Documentation

High-level interface to the interpreter

evalStmt :: Interp -> DynFlags -> 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 Source #

Instances

Instances details
Generic (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

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

Defined in GHCi.Message

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

Defined in GHCi.Message

type Rep (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

data EvalResult a Source #

Instances

Instances details
Generic (EvalResult a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Show a => Show (EvalResult a) 
Instance details

Defined in GHCi.Message

Binary a => Binary (EvalResult a) 
Instance details

Defined in GHCi.Message

type Rep (EvalResult a) 
Instance details

Defined in GHCi.Message

data EvalExpr a Source #

We can pass simple expressions to EvalStmt, consisting of values and application. This allows us to wrap the statement to be executed in another function, which is used by GHCi to implement :set args and :set prog. It might be worthwhile to extend this little language in the future.

Constructors

EvalThis a 
EvalApp (EvalExpr a) (EvalExpr a) 

Instances

Instances details
Generic (EvalExpr a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Show a => Show (EvalExpr a) 
Instance details

Defined in GHCi.Message

Binary a => Binary (EvalExpr a) 
Instance details

Defined in GHCi.Message

type Rep (EvalExpr a) 
Instance details

Defined in GHCi.Message

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

Execute an action of type IO ()

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

Execute an action of type IO String

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

Execute an action of type String -> IO String

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

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

createBCOs :: Interp -> DynFlags -> [ResolvedBCO] -> IO [HValueRef] Source #

Create a set of BCOs that may be mutually recursive.

seqHValue :: Interp -> 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

loadDLL :: Interp -> 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

interpCmd :: Binary a => Interp -> 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 Source #

A Message a is a message that returns a value of type a. These are requests sent from GHC to the server.

Constructors

Shutdown :: Message ()

Exit the iserv process

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]

Create a set of BCO objects, and return HValueRefs to them Note: Each ByteString contains a Binary-encoded [ResolvedBCO], not a ResolvedBCO. The list is to allow us to serialise the ResolvedBCOs in parallel. See createBCOs in compilerGHCRuntime/Interpreter.hs.

FreeHValueRefs :: [HValueRef] -> Message ()

Release HValueRefs

AddSptEntry :: Fingerprint -> HValueRef -> Message ()

Add entries to the Static Pointer Table

MallocData :: ByteString -> Message (RemotePtr ())

Malloc some data and return a RemotePtr to it

MallocStrings :: [ByteString] -> Message [RemotePtr ()] 
PrepFFI :: FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif)

Calls prepareForeignCall

FreeFFI :: RemotePtr C_ffi_cif -> Message ()

Free data previously created by PrepFFI

MkConInfoTable :: Bool -> Int -> Int -> Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable)

Create an info table for a constructor

EvalStmt :: EvalOpts -> EvalExpr HValueRef -> Message (EvalStatus_ [HValueRef] [HValueRef])

Evaluate a statement

ResumeStmt :: EvalOpts -> RemoteRef (ResumeContext [HValueRef]) -> Message (EvalStatus_ [HValueRef] [HValueRef])

Resume evaluation of a statement after a breakpoint

AbandonStmt :: RemoteRef (ResumeContext [HValueRef]) -> Message ()

Abandon evaluation of a statement after a breakpoint

EvalString :: HValueRef -> Message (EvalResult String)

Evaluate something of type IO String

EvalStringToString :: HValueRef -> String -> Message (EvalResult String)

Evaluate something of type String -> IO String

EvalIO :: HValueRef -> Message (EvalResult ())

Evaluate something of type IO ()

MkCostCentres :: String -> [(String, String)] -> Message [RemotePtr CostCentre]

Create a set of CostCentres with the same module name

CostCentreStackInfo :: RemotePtr CostCentreStack -> Message [String]

Show a CostCentreStack as a [String]

NewBreakArray :: Int -> Message (RemoteRef BreakArray)

Create a new array of breakpoint flags

SetupBreakpoint :: RemoteRef BreakArray -> Int -> Int -> Message ()

Set how many times a breakpoint should be ignored also used for enable/disable

BreakpointStatus :: RemoteRef BreakArray -> Int -> Message Bool

Query the status of a breakpoint (True = enabled)

GetBreakpointVar :: HValueRef -> Int -> Message (Maybe HValueRef)

Get a reference to a free variable at a breakpoint

StartTH :: Message (RemoteRef (IORef QState))

Start a new TH module, return a state token that should be

RunTH :: RemoteRef (IORef QState) -> HValueRef -> THResultType -> Maybe Loc -> Message (QResult ByteString)

Evaluate a TH computation.

Returns a ByteString, because we have to force the result before returning it to ensure there are no errors lurking in it. The TH types don't have NFData instances, and even if they did, we have to serialize the value anyway, so we might as well serialize it to force it.

RunModFinalizers :: RemoteRef (IORef QState) -> [RemoteRef (Q ())] -> Message (QResult ())

Run the given mod finalizers.

GetClosure :: HValueRef -> Message (GenClosure HValueRef)

Remote interface to GHC.Exts.Heap.getClosureData. This is used by the GHCi debugger to inspect values in the heap for :print and type reconstruction.

Seq :: HValueRef -> Message (EvalStatus_ () ())

Evaluate something. This is used to support :force in GHCi.

ResumeSeq :: RemoteRef (ResumeContext ()) -> Message (EvalStatus_ () ())

Resume forcing a free variable in a breakpoint (#2950)

Instances

Instances details
Show (Message a) 
Instance details

Defined in GHCi.Message

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.

hscInterp :: HscEnv -> Interp Source #

Retrieve the target code interpreter

Fails if no target code interpreter is available

stopInterp :: Interp -> 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

mkFinalizedHValue :: Interp -> 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.