Safe Haskell | None |
---|---|
Language | Haskell2010 |
Remote GHCi message types and serialization.
For details on Remote GHCi, see Note [Remote GHCi] in compilerghciGHCi.hs.
Synopsis
- data Message a where
- Shutdown :: 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 :: Int -> Int -> Int -> Int -> [Word8] -> Message (RemotePtr StgInfoTable)
- EvalStmt :: EvalOpts -> EvalExpr HValueRef -> Message (EvalStatus [HValueRef])
- ResumeStmt :: EvalOpts -> RemoteRef (ResumeContext [HValueRef]) -> Message (EvalStatus [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 ())
- data Msg = (Binary a, Show a) => Msg (Message a)
- data THMessage a where
- NewName :: String -> THMessage (THResult Name)
- Report :: Bool -> String -> THMessage (THResult ())
- LookupName :: Bool -> String -> THMessage (THResult (Maybe Name))
- Reify :: Name -> THMessage (THResult Info)
- ReifyFixity :: Name -> THMessage (THResult (Maybe Fixity))
- ReifyInstances :: Name -> [Type] -> THMessage (THResult [Dec])
- ReifyRoles :: Name -> THMessage (THResult [Role])
- ReifyAnnotations :: AnnLookup -> TypeRep -> THMessage (THResult [ByteString])
- ReifyModule :: Module -> THMessage (THResult ModuleInfo)
- ReifyConStrictness :: Name -> THMessage (THResult [DecidedStrictness])
- AddDependentFile :: FilePath -> THMessage (THResult ())
- AddTempFile :: String -> THMessage (THResult FilePath)
- AddModFinalizer :: RemoteRef (Q ()) -> THMessage (THResult ())
- AddCorePlugin :: String -> THMessage (THResult ())
- AddTopDecls :: [Dec] -> THMessage (THResult ())
- AddForeignFilePath :: ForeignSrcLang -> FilePath -> THMessage (THResult ())
- IsExtEnabled :: Extension -> THMessage (THResult Bool)
- ExtsEnabled :: THMessage (THResult [Extension])
- StartRecover :: THMessage ()
- EndRecover :: Bool -> THMessage ()
- FailIfErrs :: THMessage (THResult ())
- RunTHDone :: THMessage ()
- data THMsg = (Binary a, Show a) => THMsg (THMessage a)
- data QResult a
- = QDone a
- | QException String
- | QFail String
- data EvalStatus_ a b
- = EvalComplete Word64 (EvalResult a)
- | EvalBreak Bool HValueRef Int Int (RemoteRef (ResumeContext b)) (RemotePtr CostCentreStack)
- type EvalStatus a = EvalStatus_ a a
- data EvalResult a
- data EvalOpts = EvalOpts {}
- data EvalExpr a
- data SerializableException
- toSerializableException :: SomeException -> SerializableException
- fromSerializableException :: SerializableException -> SomeException
- data THResult a
- = THException String
- | THComplete a
- data THResultType
- = THExp
- | THPat
- | THType
- | THDec
- | THAnnWrapper
- data ResumeContext a = ResumeContext {
- resumeBreakMVar :: MVar ()
- resumeStatusMVar :: MVar (EvalStatus a)
- resumeThreadId :: ThreadId
- data QState = QState {}
- getMessage :: Get Msg
- putMessage :: Message a -> Put
- getTHMessage :: Get THMsg
- putTHMessage :: THMessage a -> Put
- data Pipe = Pipe {
- pipeRead :: Handle
- pipeWrite :: Handle
- pipeLeftovers :: IORef (Maybe ByteString)
- remoteCall :: Binary a => Pipe -> Message a -> IO a
- remoteTHCall :: Binary a => Pipe -> THMessage a -> IO a
- readPipe :: Pipe -> Get a -> IO a
- writePipe :: Pipe -> Put -> IO ()
Documentation
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 |
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 |
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 :: FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif) | Calls |
FreeFFI :: RemotePtr C_ffi_cif -> Message () | Free data previously created by |
MkConInfoTable :: Int -> Int -> Int -> Int -> [Word8] -> Message (RemotePtr StgInfoTable) | Create an info table for a constructor |
EvalStmt :: EvalOpts -> EvalExpr HValueRef -> Message (EvalStatus [HValueRef]) | Evaluate a statement |
ResumeStmt :: EvalOpts -> RemoteRef (ResumeContext [HValueRef]) -> Message (EvalStatus [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 |
EnableBreakpoint :: RemoteRef BreakArray -> Int -> Bool -> Message () | Enable a breakpoint |
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. |
data THMessage a where Source #
Messages sent back to GHC from GHCi.TH, to implement the methods
of Quasi
. For an overview of how TH works with Remote GHCi, see
Note [Remote Template Haskell] in GHCi.TH.
Template Haskell return values
QDone a | RunTH finished successfully; return value follows |
QException String | RunTH threw an exception |
QFail String | RunTH called |
Instances
Show a => Show (QResult a) # | |
Generic (QResult a) # | |
Binary a => Binary (QResult a) # | |
type Rep (QResult a) # | |
Defined in GHCi.Message type Rep (QResult a) = D1 (MetaData "QResult" "GHCi.Message" "ghci-8.6.4" False) (C1 (MetaCons "QDone" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: (C1 (MetaCons "QException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "QFail" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
data EvalStatus_ a b Source #
EvalComplete Word64 (EvalResult a) | |
EvalBreak Bool HValueRef Int Int (RemoteRef (ResumeContext b)) (RemotePtr CostCentreStack) |
Instances
type EvalStatus a = EvalStatus_ a a Source #
data EvalResult a Source #
Instances
Show a => Show (EvalResult a) # | |
Defined in GHCi.Message | |
Generic (EvalResult a) # | |
Defined in GHCi.Message from :: EvalResult a -> Rep (EvalResult a) x Source # to :: Rep (EvalResult a) x -> EvalResult a Source # | |
Binary a => Binary (EvalResult a) # | |
Defined in GHCi.Message put :: EvalResult a -> Put Source # get :: Get (EvalResult a) Source # putList :: [EvalResult a] -> Put Source # | |
type Rep (EvalResult a) # | |
Defined in GHCi.Message type Rep (EvalResult a) = D1 (MetaData "EvalResult" "GHCi.Message" "ghci-8.6.4" 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))) |
EvalOpts | |
|
Instances
Show EvalOpts # | |
Generic EvalOpts # | |
Binary EvalOpts # | |
type Rep EvalOpts # | |
Defined in GHCi.Message type Rep EvalOpts = D1 (MetaData "EvalOpts" "GHCi.Message" "ghci-8.6.4" False) (C1 (MetaCons "EvalOpts" PrefixI True) ((S1 (MetaSel (Just "useSandboxThread") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "singleStep") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :*: (S1 (MetaSel (Just "breakOnException") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "breakOnError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |
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.
Instances
Show a => Show (EvalExpr a) # | |
Generic (EvalExpr a) # | |
Binary a => Binary (EvalExpr a) # | |
type Rep (EvalExpr a) # | |
Defined in GHCi.Message type Rep (EvalExpr a) = D1 (MetaData "EvalExpr" "GHCi.Message" "ghci-8.6.4" 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)))) |
data SerializableException Source #
Instances
Show SerializableException # | |
Defined in GHCi.Message | |
Generic SerializableException # | |
Defined in GHCi.Message | |
Binary SerializableException # | |
Defined in GHCi.Message put :: SerializableException -> Put Source # get :: Get SerializableException Source # putList :: [SerializableException] -> Put Source # | |
type Rep SerializableException # | |
Defined in GHCi.Message type Rep SerializableException = D1 (MetaData "SerializableException" "GHCi.Message" "ghci-8.6.4" False) (C1 (MetaCons "EUserInterrupt" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EExitCode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ExitCode)) :+: C1 (MetaCons "EOtherException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
Instances
Show a => Show (THResult a) # | |
Generic (THResult a) # | |
Binary a => Binary (THResult a) # | |
type Rep (THResult a) # | |
Defined in GHCi.Message type Rep (THResult a) = D1 (MetaData "THResult" "GHCi.Message" "ghci-8.6.4" False) (C1 (MetaCons "THException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "THComplete" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) |
data THResultType Source #
Instances
data ResumeContext a Source #
ResumeContext | |
|
The server-side Template Haskell state. This is created by the StartTH message. A new one is created per module that GHC typechecks.
getMessage :: Get Msg Source #
putMessage :: Message a -> Put Source #
getTHMessage :: Get THMsg Source #
putTHMessage :: THMessage a -> Put Source #
Pipe | |
|