ghc-lib-9.8.2.20240223: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Runtime.Interpreter.Process

Synopsis

Low-level API

callInterpProcess :: Binary a => InterpProcess -> Message a -> IO a Source #

Send a Message and receive the response from the interpreter process

readInterpProcess :: InterpProcess -> Get a -> IO a Source #

Read a value from the interpreter process

writeInterpProcess :: InterpProcess -> Put -> IO () Source #

Send a value to the interpreter process

Message API

data Message a where #

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

Methods

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

show :: Message a -> String #

showList :: [Message a] -> ShowS #

sendMessage :: Binary a => ExtInterpInstance d -> Message a -> IO a Source #

Send a message to the interpreter that excepts a response

sendMessageNoResponse :: ExtInterpInstance d -> Message () -> IO () Source #

Send a message to the interpreter process that doesn't expect a response

sendMessageDelayedResponse :: ExtInterpInstance d -> Message a -> IO (DelayedResponse a) Source #

Send a message to the interpreter process whose response is expected later

This is useful to avoid forgetting to receive the value and to ensure that the type of the response isn't lost. Use receiveDelayedResponse to read it.

sendAnyValue :: Binary a => ExtInterpInstance d -> a -> IO () Source #

Send any value

receiveAnyValue :: ExtInterpInstance d -> Get a -> IO a Source #

Expect a value to be received

receiveDelayedResponse :: Binary a => ExtInterpInstance d -> DelayedResponse a -> IO a Source #

Expect a delayed result to be received now

receiveTHMessage :: ExtInterpInstance d -> IO THMsg Source #

Expect a value to be received