Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data Message a where
- Shutdown :: Message ()
- RtsRevertCAFs :: Message ()
- InitLinker :: Message ()
- LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
- LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
- LookupClosure :: String -> Message (Maybe HValueRef)
- LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
- 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 :: [ResolvedBCO] -> Message [HValueRef]
- FreeHValueRefs :: [HValueRef] -> Message ()
- AddSptEntry :: Fingerprint -> HValueRef -> Message ()
- MallocData :: ByteString -> Message (RemotePtr ())
- MallocStrings :: [ByteString] -> Message [RemotePtr ()]
- PrepFFI :: [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)
- SetupBreakpoint :: RemoteRef BreakArray -> Int -> Int -> 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_ () ())
- NewBreakModule :: String -> Message (RemotePtr BreakModule)
- data DelayedResponse (a :: k) = DelayedResponse
- sendMessage :: Binary a => ExtInterpInstance d -> Message a -> IO a
- sendMessageNoResponse :: ExtInterpInstance d -> Message () -> IO ()
- sendMessageDelayedResponse :: ExtInterpInstance d -> Message a -> IO (DelayedResponse a)
- receiveDelayedResponse :: Binary a => ExtInterpInstance d -> DelayedResponse a -> IO a
- sendAnyValue :: Binary a => ExtInterpInstance d -> a -> IO ()
- receiveAnyValue :: ExtInterpInstance d -> Get a -> IO a
- receiveTHMessage :: ExtInterpInstance d -> IO THMsg
Message API
A Message a
is a message that returns a value of type a
.
These are requests sent from GHC to the server.
Shutdown :: Message () | Exit the iserv process |
RtsRevertCAFs :: Message () | |
InitLinker :: Message () | |
LookupSymbol :: String -> Message (Maybe (RemotePtr ())) | |
LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ())) | |
LookupClosure :: String -> Message (Maybe HValueRef) | |
LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL)) | |
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 :: [ResolvedBCO] -> Message [HValueRef] | Create a set of BCO objects, and return HValueRefs to them
See |
FreeHValueRefs :: [HValueRef] -> Message () | Release |
AddSptEntry :: Fingerprint -> HValueRef -> Message () | Add entries to the Static Pointer Table |
MallocData :: ByteString -> Message (RemotePtr ()) | Malloc some data and return a |
MallocStrings :: [ByteString] -> Message [RemotePtr ()] | |
PrepFFI :: [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif) | Calls |
FreeFFI :: RemotePtr C_ffi_cif -> Message () | Free data previously created by |
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 |
EvalStringToString :: HValueRef -> String -> Message (EvalResult String) | Evaluate something of type |
EvalIO :: HValueRef -> Message (EvalResult ()) | Evaluate something of type |
MkCostCentres :: String -> [(String, String)] -> Message [RemotePtr CostCentre] | Create a set of CostCentres with the same module name |
CostCentreStackInfo :: RemotePtr CostCentreStack -> Message [String] | Show a |
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) |
NewBreakModule :: String -> Message (RemotePtr BreakModule) | Allocate a string for a breakpoint module name.
This uses an empty dummy type because |
data DelayedResponse (a :: k) Source #
Top-level message API (these acquire/release a lock)
sendMessage :: Binary a => ExtInterpInstance d -> Message a -> IO a Source #
Send a message to the interpreter that expects a response (locks the interpreter while until the response is received)
sendMessageNoResponse :: ExtInterpInstance d -> Message () -> IO () Source #
Send a message to the interpreter process that doesn't expect a response (locks the interpreter while sending)
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.
(locks the interpreter until the response is received using
receiveDelayedResponse
)
receiveDelayedResponse :: Binary a => ExtInterpInstance d -> DelayedResponse a -> IO a Source #
Expect a delayed result to be received now
Nested message API (these require the interpreter to already be locked)
sendAnyValue :: Binary a => ExtInterpInstance d -> a -> IO () Source #
Send any value (requires locked interpreter)
receiveAnyValue :: ExtInterpInstance d -> Get a -> IO a Source #
Expect a value to be received (requires locked interpreter)
receiveTHMessage :: ExtInterpInstance d -> IO THMsg Source #
Wait for a Template Haskell message (requires locked interpreter)