{-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables,
GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-}
module GHCi.Message
( Message(..), Msg(..)
, THMessage(..), THMsg(..)
, QResult(..)
, EvalStatus_(..), EvalStatus, EvalResult(..), EvalOpts(..), EvalExpr(..)
, SerializableException(..)
, toSerializableException, fromSerializableException
, THResult(..), THResultType(..)
, ResumeContext(..)
, QState(..)
, getMessage, putMessage, getTHMessage, putTHMessage
, Pipe(..), remoteCall, remoteTHCall, readPipe, writePipe
) where
import Prelude
import GHCi.RemoteTypes
import GHCi.FFI
import GHCi.TH.Binary ()
import GHCi.BreakArray
import GHC.LanguageExtensions
import GHC.Exts.Heap
import GHC.ForeignSrcLang
import GHC.Fingerprint
import Control.Concurrent
import Control.Exception
import Data.Binary
import Data.Binary.Get
import Data.Binary.Put
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import Data.Dynamic
import Data.Typeable (TypeRep)
import Data.IORef
import Data.Map (Map)
import Foreign
import GHC.Generics
import GHC.Stack.CCS
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
import System.Exit
import System.IO
import System.IO.Error
data Message a where
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 :: [LB.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])
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 TH.Loc
-> Message (QResult ByteString)
RunModFinalizers :: RemoteRef (IORef QState)
-> [RemoteRef (TH.Q ())]
-> Message (QResult ())
GetClosure
:: HValueRef
-> Message (GenClosure HValueRef)
Seq
:: HValueRef
-> Message (EvalStatus ())
ResumeSeq
:: RemoteRef (ResumeContext ())
-> Message (EvalStatus ())
deriving instance Show (Message a)
data QResult a
= QDone a
| QException String
| QFail String
deriving ((forall x. QResult a -> Rep (QResult a) x)
-> (forall x. Rep (QResult a) x -> QResult a)
-> Generic (QResult a)
forall x. Rep (QResult a) x -> QResult a
forall x. QResult a -> Rep (QResult a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (QResult a) x -> QResult a
forall a x. QResult a -> Rep (QResult a) x
$cto :: forall a x. Rep (QResult a) x -> QResult a
$cfrom :: forall a x. QResult a -> Rep (QResult a) x
Generic, Int -> QResult a -> ShowS
[QResult a] -> ShowS
QResult a -> String
(Int -> QResult a -> ShowS)
-> (QResult a -> String)
-> ([QResult a] -> ShowS)
-> Show (QResult a)
forall a. Show a => Int -> QResult a -> ShowS
forall a. Show a => [QResult a] -> ShowS
forall a. Show a => QResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QResult a] -> ShowS
$cshowList :: forall a. Show a => [QResult a] -> ShowS
show :: QResult a -> String
$cshow :: forall a. Show a => QResult a -> String
showsPrec :: Int -> QResult a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> QResult a -> ShowS
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show a
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
Show)
instance Binary a => Binary (QResult a)
data THMessage a where
NewName :: String -> THMessage (THResult TH.Name)
Report :: Bool -> String -> THMessage (THResult ())
LookupName :: Bool -> String -> THMessage (THResult (Maybe TH.Name))
Reify :: TH.Name -> THMessage (THResult TH.Info)
ReifyFixity :: TH.Name -> THMessage (THResult (Maybe TH.Fixity))
ReifyType :: TH.Name -> THMessage (THResult TH.Type)
ReifyInstances :: TH.Name -> [TH.Type] -> THMessage (THResult [TH.Dec])
ReifyRoles :: TH.Name -> THMessage (THResult [TH.Role])
ReifyAnnotations :: TH.AnnLookup -> TypeRep
-> THMessage (THResult [ByteString])
ReifyModule :: TH.Module -> THMessage (THResult TH.ModuleInfo)
ReifyConStrictness :: TH.Name -> THMessage (THResult [TH.DecidedStrictness])
AddDependentFile :: FilePath -> THMessage (THResult ())
AddTempFile :: String -> THMessage (THResult FilePath)
AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ())
AddCorePlugin :: String -> THMessage (THResult ())
AddTopDecls :: [TH.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 ()
deriving instance Show (THMessage a)
data THMsg = forall a . (Binary a, Show a) => THMsg (THMessage a)
getTHMessage :: Get THMsg
getTHMessage :: Get THMsg
getTHMessage = do
Word8
b <- Get Word8
getWord8
case Word8
b of
Word8
0 -> THMessage (THResult Name) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show Name
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary Name
THMsg (THMessage (THResult Name) -> THMsg)
-> (String -> THMessage (THResult Name)) -> String -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> THMessage (THResult Name)
NewName (String -> THMsg) -> Get String -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
1 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> Get (THMessage (THResult ())) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Bool -> String -> THMessage (THResult ())
Report (Bool -> String -> THMessage (THResult ()))
-> Get Bool -> Get (String -> THMessage (THResult ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get Get (String -> THMessage (THResult ()))
-> Get String -> Get (THMessage (THResult ()))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get)
Word8
2 -> THMessage (THResult (Maybe Name)) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show Name
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Name
THMsg (THMessage (THResult (Maybe Name)) -> THMsg)
-> Get (THMessage (THResult (Maybe Name))) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Bool -> String -> THMessage (THResult (Maybe Name))
LookupName (Bool -> String -> THMessage (THResult (Maybe Name)))
-> Get Bool -> Get (String -> THMessage (THResult (Maybe Name)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get Get (String -> THMessage (THResult (Maybe Name)))
-> Get String -> Get (THMessage (THResult (Maybe Name)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get)
Word8
3 -> THMessage (THResult Info) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show Info
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary Info
THMsg (THMessage (THResult Info) -> THMsg)
-> (Name -> THMessage (THResult Info)) -> Name -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Name -> THMessage (THResult Info)
Reify (Name -> THMsg) -> Get Name -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get
Word8
4 -> THMessage (THResult (Maybe Fixity)) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show Fixity
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Fixity
THMsg (THMessage (THResult (Maybe Fixity)) -> THMsg)
-> (Name -> THMessage (THResult (Maybe Fixity))) -> Name -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Name -> THMessage (THResult (Maybe Fixity))
ReifyFixity (Name -> THMsg) -> Get Name -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get
Word8
5 -> THMessage (THResult [Dec]) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Dec
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Dec
THMsg (THMessage (THResult [Dec]) -> THMsg)
-> Get (THMessage (THResult [Dec])) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Name -> [Type] -> THMessage (THResult [Dec])
ReifyInstances (Name -> [Type] -> THMessage (THResult [Dec]))
-> Get Name -> Get ([Type] -> THMessage (THResult [Dec]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get Get ([Type] -> THMessage (THResult [Dec]))
-> Get [Type] -> Get (THMessage (THResult [Dec]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get [Type]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Type
get)
Word8
6 -> THMessage (THResult [Role]) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Role
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Role
THMsg (THMessage (THResult [Role]) -> THMsg)
-> (Name -> THMessage (THResult [Role])) -> Name -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Name -> THMessage (THResult [Role])
ReifyRoles (Name -> THMsg) -> Get Name -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get
Word8
7 -> THMessage (THResult [ByteString]) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show ByteString
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
THMsg (THMessage (THResult [ByteString]) -> THMsg)
-> Get (THMessage (THResult [ByteString])) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (AnnLookup -> TypeRep -> THMessage (THResult [ByteString])
ReifyAnnotations (AnnLookup -> TypeRep -> THMessage (THResult [ByteString]))
-> Get AnnLookup
-> Get (TypeRep -> THMessage (THResult [ByteString]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get AnnLookup
forall t. Binary t => Get t
External instance of the constraint type Binary AnnLookup
get Get (TypeRep -> THMessage (THResult [ByteString]))
-> Get TypeRep -> Get (THMessage (THResult [ByteString]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get TypeRep
forall t. Binary t => Get t
External instance of the constraint type Binary TypeRep
get)
Word8
8 -> THMessage (THResult ModuleInfo) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ModuleInfo
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ModuleInfo
THMsg (THMessage (THResult ModuleInfo) -> THMsg)
-> (Module -> THMessage (THResult ModuleInfo)) -> Module -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Module -> THMessage (THResult ModuleInfo)
ReifyModule (Module -> THMsg) -> Get Module -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Module
forall t. Binary t => Get t
External instance of the constraint type Binary Module
get
Word8
9 -> THMessage (THResult [DecidedStrictness]) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show DecidedStrictness
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary DecidedStrictness
THMsg (THMessage (THResult [DecidedStrictness]) -> THMsg)
-> (Name -> THMessage (THResult [DecidedStrictness]))
-> Name
-> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Name -> THMessage (THResult [DecidedStrictness])
ReifyConStrictness (Name -> THMsg) -> Get Name -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get
Word8
10 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> (String -> THMessage (THResult ())) -> String -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> THMessage (THResult ())
AddDependentFile (String -> THMsg) -> Get String -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
11 -> THMessage (THResult String) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
THMsg (THMessage (THResult String) -> THMsg)
-> (String -> THMessage (THResult String)) -> String -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> THMessage (THResult String)
AddTempFile (String -> THMsg) -> Get String -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
12 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> ([Dec] -> THMessage (THResult ())) -> [Dec] -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> [Dec] -> THMessage (THResult ())
AddTopDecls ([Dec] -> THMsg) -> Get [Dec] -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get [Dec]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Dec
get
Word8
13 -> THMessage (THResult Bool) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show Bool
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary Bool
THMsg (THMessage (THResult Bool) -> THMsg)
-> Get (THMessage (THResult Bool)) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Extension -> THMessage (THResult Bool)
IsExtEnabled (Extension -> THMessage (THResult Bool))
-> Get Extension -> Get (THMessage (THResult Bool))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Extension
forall t. Binary t => Get t
External instance of the constraint type Binary Extension
get)
Word8
14 -> THMessage (THResult [Extension]) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Extension
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Extension
THMsg (THMessage (THResult [Extension]) -> THMsg)
-> Get (THMessage (THResult [Extension])) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> THMessage (THResult [Extension])
-> Get (THMessage (THResult [Extension]))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return THMessage (THResult [Extension])
ExtsEnabled
Word8
15 -> THMessage () -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
THMsg (THMessage () -> THMsg) -> Get (THMessage ()) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> THMessage () -> Get (THMessage ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return THMessage ()
StartRecover
Word8
16 -> THMessage () -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
THMsg (THMessage () -> THMsg) -> (Bool -> THMessage ()) -> Bool -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Bool -> THMessage ()
EndRecover (Bool -> THMsg) -> Get Bool -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get
Word8
17 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> Get (THMessage (THResult ())) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> THMessage (THResult ()) -> Get (THMessage (THResult ()))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return THMessage (THResult ())
FailIfErrs
Word8
18 -> THMsg -> Get THMsg
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return (THMessage () -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
THMsg THMessage ()
RunTHDone)
Word8
19 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> (RemoteRef (Q ()) -> THMessage (THResult ()))
-> RemoteRef (Q ())
-> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> RemoteRef (Q ()) -> THMessage (THResult ())
AddModFinalizer (RemoteRef (Q ()) -> THMsg) -> Get (RemoteRef (Q ())) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef (Q ()))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get
Word8
20 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> Get (THMessage (THResult ())) -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (ForeignSrcLang -> String -> THMessage (THResult ())
AddForeignFilePath (ForeignSrcLang -> String -> THMessage (THResult ()))
-> Get ForeignSrcLang -> Get (String -> THMessage (THResult ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get ForeignSrcLang
forall t. Binary t => Get t
External instance of the constraint type Binary ForeignSrcLang
get Get (String -> THMessage (THResult ()))
-> Get String -> Get (THMessage (THResult ()))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get)
Word8
21 -> THMessage (THResult ()) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary ()
THMsg (THMessage (THResult ()) -> THMsg)
-> (String -> THMessage (THResult ())) -> String -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> THMessage (THResult ())
AddCorePlugin (String -> THMsg) -> Get String -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
22 -> THMessage (THResult Type) -> THMsg
forall a. (Binary a, Show a) => THMessage a -> THMsg
Instance of class: Show of the constraint type forall a. Show a => Show (THResult a)
External instance of the constraint type Show Type
Instance of class: Binary of the constraint type forall a. Binary a => Binary (THResult a)
External instance of the constraint type Binary Type
THMsg (THMessage (THResult Type) -> THMsg)
-> (Name -> THMessage (THResult Type)) -> Name -> THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> Name -> THMessage (THResult Type)
ReifyType (Name -> THMsg) -> Get Name -> Get THMsg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Name
forall t. Binary t => Get t
External instance of the constraint type Binary Name
get
Word8
n -> String -> Get THMsg
forall a. HasCallStack => String -> a
error (String
"getTHMessage: unknown message " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
External instance of the constraint type Show Word8
show Word8
n)
putTHMessage :: THMessage a -> Put
putTHMessage :: THMessage a -> Put
putTHMessage THMessage a
m = case THMessage a
m of
NewName String
a -> Word8 -> Put
putWord8 Word8
0 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
a
Report Bool
a String
b -> Word8 -> Put
putWord8 Word8
1 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
b
LookupName Bool
a String
b -> Word8 -> Put
putWord8 Word8
2 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
b
Reify Name
a -> Word8 -> Put
putWord8 Word8
3 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a
ReifyFixity Name
a -> Word8 -> Put
putWord8 Word8
4 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a
ReifyInstances Name
a [Type]
b -> Word8 -> Put
putWord8 Word8
5 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [Type] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Type
put [Type]
b
ReifyRoles Name
a -> Word8 -> Put
putWord8 Word8
6 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a
ReifyAnnotations AnnLookup
a TypeRep
b -> Word8 -> Put
putWord8 Word8
7 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> AnnLookup -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary AnnLookup
put AnnLookup
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> TypeRep -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary TypeRep
put TypeRep
b
ReifyModule Module
a -> Word8 -> Put
putWord8 Word8
8 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Module -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Module
put Module
a
ReifyConStrictness Name
a -> Word8 -> Put
putWord8 Word8
9 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a
AddDependentFile String
a -> Word8 -> Put
putWord8 Word8
10 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
a
AddTempFile String
a -> Word8 -> Put
putWord8 Word8
11 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
a
AddTopDecls [Dec]
a -> Word8 -> Put
putWord8 Word8
12 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [Dec] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Dec
put [Dec]
a
IsExtEnabled Extension
a -> Word8 -> Put
putWord8 Word8
13 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Extension -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Extension
put Extension
a
THMessage a
External instance of the constraint type Num Word8
ExtsEnabled -> Word8 -> Put
putWord8 Word8
14
THMessage a
External instance of the constraint type Num Word8
StartRecover -> Word8 -> Put
putWord8 Word8
15
EndRecover Bool
a -> Word8 -> Put
putWord8 Word8
16 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
a
THMessage a
External instance of the constraint type Num Word8
FailIfErrs -> Word8 -> Put
putWord8 Word8
17
THMessage a
External instance of the constraint type Num Word8
RunTHDone -> Word8 -> Put
putWord8 Word8
18
AddModFinalizer RemoteRef (Q ())
a -> Word8 -> Put
putWord8 Word8
19 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (Q ()) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (Q ())
a
AddForeignFilePath ForeignSrcLang
lang String
a -> Word8 -> Put
putWord8 Word8
20 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> ForeignSrcLang -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ForeignSrcLang
put ForeignSrcLang
lang Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
a
AddCorePlugin String
a -> Word8 -> Put
putWord8 Word8
21 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
a
ReifyType Name
a -> Word8 -> Put
putWord8 Word8
22 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Name -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Name
put Name
a
data EvalOpts = EvalOpts
{ EvalOpts -> Bool
useSandboxThread :: Bool
, EvalOpts -> Bool
singleStep :: Bool
, EvalOpts -> Bool
breakOnException :: Bool
, EvalOpts -> Bool
breakOnError :: Bool
}
deriving ((forall x. EvalOpts -> Rep EvalOpts x)
-> (forall x. Rep EvalOpts x -> EvalOpts) -> Generic EvalOpts
forall x. Rep EvalOpts x -> EvalOpts
forall x. EvalOpts -> Rep EvalOpts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvalOpts x -> EvalOpts
$cfrom :: forall x. EvalOpts -> Rep EvalOpts x
Generic, Int -> EvalOpts -> ShowS
[EvalOpts] -> ShowS
EvalOpts -> String
(Int -> EvalOpts -> ShowS)
-> (EvalOpts -> String) -> ([EvalOpts] -> ShowS) -> Show EvalOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvalOpts] -> ShowS
$cshowList :: [EvalOpts] -> ShowS
show :: EvalOpts -> String
$cshow :: EvalOpts -> String
showsPrec :: Int -> EvalOpts -> ShowS
$cshowsPrec :: Int -> EvalOpts -> ShowS
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
Show)
instance Binary EvalOpts
data ResumeContext a = ResumeContext
{ ResumeContext a -> MVar ()
resumeBreakMVar :: MVar ()
, ResumeContext a -> MVar (EvalStatus a)
resumeStatusMVar :: MVar (EvalStatus a)
, ResumeContext a -> ThreadId
resumeThreadId :: ThreadId
}
data EvalExpr a
= EvalThis a
| EvalApp (EvalExpr a) (EvalExpr a)
deriving ((forall x. EvalExpr a -> Rep (EvalExpr a) x)
-> (forall x. Rep (EvalExpr a) x -> EvalExpr a)
-> Generic (EvalExpr a)
forall x. Rep (EvalExpr a) x -> EvalExpr a
forall x. EvalExpr a -> Rep (EvalExpr a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (EvalExpr a) x -> EvalExpr a
forall a x. EvalExpr a -> Rep (EvalExpr a) x
$cto :: forall a x. Rep (EvalExpr a) x -> EvalExpr a
$cfrom :: forall a x. EvalExpr a -> Rep (EvalExpr a) x
Generic, Int -> EvalExpr a -> ShowS
[EvalExpr a] -> ShowS
EvalExpr a -> String
(Int -> EvalExpr a -> ShowS)
-> (EvalExpr a -> String)
-> ([EvalExpr a] -> ShowS)
-> Show (EvalExpr a)
forall a. Show a => Int -> EvalExpr a -> ShowS
forall a. Show a => [EvalExpr a] -> ShowS
forall a. Show a => EvalExpr a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvalExpr a] -> ShowS
$cshowList :: forall a. Show a => [EvalExpr a] -> ShowS
show :: EvalExpr a -> String
$cshow :: forall a. Show a => EvalExpr a -> String
showsPrec :: Int -> EvalExpr a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EvalExpr a -> ShowS
Instance of class: Show of the constraint type forall a. Show a => Show (EvalExpr a)
Evidence bound by a type signature of the constraint type Show a
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show a
Instance of class: Show of the constraint type forall a. Show a => Show (EvalExpr a)
External instance of the constraint type Ord Int
Show)
instance Binary a => Binary (EvalExpr a)
type EvalStatus a = EvalStatus_ a a
data EvalStatus_ a b
= EvalComplete Word64 (EvalResult a)
| EvalBreak Bool
HValueRef
Int
Int
(RemoteRef (ResumeContext b))
(RemotePtr CostCentreStack)
deriving ((forall x. EvalStatus_ a b -> Rep (EvalStatus_ a b) x)
-> (forall x. Rep (EvalStatus_ a b) x -> EvalStatus_ a b)
-> Generic (EvalStatus_ a b)
forall x. Rep (EvalStatus_ a b) x -> EvalStatus_ a b
forall x. EvalStatus_ a b -> Rep (EvalStatus_ a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b x. Rep (EvalStatus_ a b) x -> EvalStatus_ a b
forall a b x. EvalStatus_ a b -> Rep (EvalStatus_ a b) x
$cto :: forall a b x. Rep (EvalStatus_ a b) x -> EvalStatus_ a b
$cfrom :: forall a b x. EvalStatus_ a b -> Rep (EvalStatus_ a b) x
Generic, Int -> EvalStatus_ a b -> ShowS
[EvalStatus_ a b] -> ShowS
EvalStatus_ a b -> String
(Int -> EvalStatus_ a b -> ShowS)
-> (EvalStatus_ a b -> String)
-> ([EvalStatus_ a b] -> ShowS)
-> Show (EvalStatus_ a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. Show a => Int -> EvalStatus_ a b -> ShowS
forall a b. Show a => [EvalStatus_ a b] -> ShowS
forall a b. Show a => EvalStatus_ a b -> String
showList :: [EvalStatus_ a b] -> ShowS
$cshowList :: forall a b. Show a => [EvalStatus_ a b] -> ShowS
show :: EvalStatus_ a b -> String
$cshow :: forall a b. Show a => EvalStatus_ a b -> String
showsPrec :: Int -> EvalStatus_ a b -> ShowS
$cshowsPrec :: forall a b. Show a => Int -> EvalStatus_ a b -> ShowS
External instance of the constraint type Show Int
External instance of the constraint type Show Word64
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type forall a. Show a => Show (EvalResult a)
Evidence bound by a type signature of the constraint type Show a
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type Show Int
External instance of the constraint type forall a. Show (RemoteRef a)
External instance of the constraint type forall a. Show (RemoteRef a)
External instance of the constraint type Show Bool
External instance of the constraint type Ord Int
Show)
instance Binary a => Binary (EvalStatus_ a b)
data EvalResult a
= EvalException SerializableException
| EvalSuccess a
deriving ((forall x. EvalResult a -> Rep (EvalResult a) x)
-> (forall x. Rep (EvalResult a) x -> EvalResult a)
-> Generic (EvalResult a)
forall x. Rep (EvalResult a) x -> EvalResult a
forall x. EvalResult a -> Rep (EvalResult a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (EvalResult a) x -> EvalResult a
forall a x. EvalResult a -> Rep (EvalResult a) x
$cto :: forall a x. Rep (EvalResult a) x -> EvalResult a
$cfrom :: forall a x. EvalResult a -> Rep (EvalResult a) x
Generic, Int -> EvalResult a -> ShowS
[EvalResult a] -> ShowS
EvalResult a -> String
(Int -> EvalResult a -> ShowS)
-> (EvalResult a -> String)
-> ([EvalResult a] -> ShowS)
-> Show (EvalResult a)
forall a. Show a => Int -> EvalResult a -> ShowS
forall a. Show a => [EvalResult a] -> ShowS
forall a. Show a => EvalResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvalResult a] -> ShowS
$cshowList :: forall a. Show a => [EvalResult a] -> ShowS
show :: EvalResult a -> String
$cshow :: forall a. Show a => EvalResult a -> String
showsPrec :: Int -> EvalResult a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> EvalResult a -> ShowS
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show SerializableException
Evidence bound by a type signature of the constraint type Show a
External instance of the constraint type Ord Int
Show)
instance Binary a => Binary (EvalResult a)
data SerializableException
= EUserInterrupt
| EExitCode ExitCode
| EOtherException String
deriving ((forall x. SerializableException -> Rep SerializableException x)
-> (forall x. Rep SerializableException x -> SerializableException)
-> Generic SerializableException
forall x. Rep SerializableException x -> SerializableException
forall x. SerializableException -> Rep SerializableException x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SerializableException x -> SerializableException
$cfrom :: forall x. SerializableException -> Rep SerializableException x
Generic, Int -> SerializableException -> ShowS
[SerializableException] -> ShowS
SerializableException -> String
(Int -> SerializableException -> ShowS)
-> (SerializableException -> String)
-> ([SerializableException] -> ShowS)
-> Show SerializableException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SerializableException] -> ShowS
$cshowList :: [SerializableException] -> ShowS
show :: SerializableException -> String
$cshow :: SerializableException -> String
showsPrec :: Int -> SerializableException -> ShowS
$cshowsPrec :: Int -> SerializableException -> ShowS
External instance of the constraint type Show ExitCode
External instance of the constraint type Ord Int
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
Show)
toSerializableException :: SomeException -> SerializableException
toSerializableException :: SomeException -> SerializableException
toSerializableException SomeException
ex
| Just AsyncException
UserInterrupt <- SomeException -> Maybe AsyncException
forall e. Exception e => SomeException -> Maybe e
External instance of the constraint type Exception AsyncException
fromException SomeException
ex = SerializableException
EUserInterrupt
| Just (ExitCode
ec::ExitCode) <- SomeException -> Maybe ExitCode
forall e. Exception e => SomeException -> Maybe e
External instance of the constraint type Exception ExitCode
fromException SomeException
ex = (ExitCode -> SerializableException
EExitCode ExitCode
ec)
| Bool
otherwise = String -> SerializableException
EOtherException (SomeException -> String
forall a. Show a => a -> String
External instance of the constraint type Show SomeException
show (SomeException
ex :: SomeException))
fromSerializableException :: SerializableException -> SomeException
fromSerializableException :: SerializableException -> SomeException
fromSerializableException SerializableException
EUserInterrupt = AsyncException -> SomeException
forall e. Exception e => e -> SomeException
External instance of the constraint type Exception AsyncException
toException AsyncException
UserInterrupt
fromSerializableException (EExitCode ExitCode
c) = ExitCode -> SomeException
forall e. Exception e => e -> SomeException
External instance of the constraint type Exception ExitCode
toException ExitCode
c
fromSerializableException (EOtherException String
str) = ErrorCall -> SomeException
forall e. Exception e => e -> SomeException
External instance of the constraint type Exception ErrorCall
toException (String -> ErrorCall
ErrorCall String
str)
instance Binary ExitCode
instance Binary SerializableException
data THResult a
= THException String
| THComplete a
deriving ((forall x. THResult a -> Rep (THResult a) x)
-> (forall x. Rep (THResult a) x -> THResult a)
-> Generic (THResult a)
forall x. Rep (THResult a) x -> THResult a
forall x. THResult a -> Rep (THResult a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (THResult a) x -> THResult a
forall a x. THResult a -> Rep (THResult a) x
$cto :: forall a x. Rep (THResult a) x -> THResult a
$cfrom :: forall a x. THResult a -> Rep (THResult a) x
Generic, Int -> THResult a -> ShowS
[THResult a] -> ShowS
THResult a -> String
(Int -> THResult a -> ShowS)
-> (THResult a -> String)
-> ([THResult a] -> ShowS)
-> Show (THResult a)
forall a. Show a => Int -> THResult a -> ShowS
forall a. Show a => [THResult a] -> ShowS
forall a. Show a => THResult a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [THResult a] -> ShowS
$cshowList :: forall a. Show a => [THResult a] -> ShowS
show :: THResult a -> String
$cshow :: forall a. Show a => THResult a -> String
showsPrec :: Int -> THResult a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> THResult a -> ShowS
External instance of the constraint type Ord Int
Evidence bound by a type signature of the constraint type Show a
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
Show)
instance Binary a => Binary (THResult a)
data THResultType = THExp | THPat | THType | THDec | THAnnWrapper
deriving (Int -> THResultType
THResultType -> Int
THResultType -> [THResultType]
THResultType -> THResultType
THResultType -> THResultType -> [THResultType]
THResultType -> THResultType -> THResultType -> [THResultType]
(THResultType -> THResultType)
-> (THResultType -> THResultType)
-> (Int -> THResultType)
-> (THResultType -> Int)
-> (THResultType -> [THResultType])
-> (THResultType -> THResultType -> [THResultType])
-> (THResultType -> THResultType -> [THResultType])
-> (THResultType -> THResultType -> THResultType -> [THResultType])
-> Enum THResultType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: THResultType -> THResultType -> THResultType -> [THResultType]
$cenumFromThenTo :: THResultType -> THResultType -> THResultType -> [THResultType]
enumFromTo :: THResultType -> THResultType -> [THResultType]
$cenumFromTo :: THResultType -> THResultType -> [THResultType]
enumFromThen :: THResultType -> THResultType -> [THResultType]
$cenumFromThen :: THResultType -> THResultType -> [THResultType]
enumFrom :: THResultType -> [THResultType]
$cenumFrom :: THResultType -> [THResultType]
fromEnum :: THResultType -> Int
$cfromEnum :: THResultType -> Int
toEnum :: Int -> THResultType
$ctoEnum :: Int -> THResultType
pred :: THResultType -> THResultType
$cpred :: THResultType -> THResultType
succ :: THResultType -> THResultType
$csucc :: THResultType -> THResultType
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
Enum, Int -> THResultType -> ShowS
[THResultType] -> ShowS
THResultType -> String
(Int -> THResultType -> ShowS)
-> (THResultType -> String)
-> ([THResultType] -> ShowS)
-> Show THResultType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [THResultType] -> ShowS
$cshowList :: [THResultType] -> ShowS
show :: THResultType -> String
$cshow :: THResultType -> String
showsPrec :: Int -> THResultType -> ShowS
$cshowsPrec :: Int -> THResultType -> ShowS
Show, (forall x. THResultType -> Rep THResultType x)
-> (forall x. Rep THResultType x -> THResultType)
-> Generic THResultType
forall x. Rep THResultType x -> THResultType
forall x. THResultType -> Rep THResultType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep THResultType x -> THResultType
$cfrom :: forall x. THResultType -> Rep THResultType x
Generic)
instance Binary THResultType
data QState = QState
{ QState -> Map TypeRep Dynamic
qsMap :: Map TypeRep Dynamic
, QState -> Maybe Loc
qsLocation :: Maybe TH.Loc
, QState -> Pipe
qsPipe :: Pipe
}
instance Show QState where show :: QState -> String
show QState
_ = String
"<QState>"
instance Binary (Ptr a) where
put :: Ptr a -> Put
put Ptr a
p = Word64 -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Word64
put (WordPtr -> Word64
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Word64
External instance of the constraint type Integral WordPtr
fromIntegral (Ptr a -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr Ptr a
p) :: Word64)
get :: Get (Ptr a)
get = (WordPtr -> Ptr a
forall a. WordPtr -> Ptr a
wordPtrToPtr (WordPtr -> Ptr a) -> (Word64 -> WordPtr) -> Word64 -> Ptr a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> WordPtr
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num WordPtr
External instance of the constraint type Integral Word64
fromIntegral) (Word64 -> Ptr a) -> Get Word64 -> Get (Ptr a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Get Word64
forall t. Binary t => Get t
External instance of the constraint type Binary Word64
get :: Get Word64)
instance Binary (FunPtr a) where
put :: FunPtr a -> Put
put = Ptr Any -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type forall a. Binary (Ptr a)
put (Ptr Any -> Put) -> (FunPtr a -> Ptr Any) -> FunPtr a -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunPtr a -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr
get :: Get (FunPtr a)
get = Ptr Any -> FunPtr a
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr (Ptr Any -> FunPtr a) -> Get (Ptr Any) -> Get (FunPtr a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (Ptr Any)
forall t. Binary t => Get t
Instance of class: Binary of the constraint type forall a. Binary (Ptr a)
get
instance Binary StgInfoTable
instance Binary ClosureType
instance Binary PrimType
instance Binary a => Binary (GenClosure a)
data Msg = forall a . (Binary a, Show a) => Msg (Message a)
getMessage :: Get Msg
getMessage :: Get Msg
getMessage = do
Word8
b <- Get Word8
getWord8
case Word8
b of
Word8
0 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Message () -> Get (Message ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return Message ()
Shutdown
Word8
1 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Message () -> Get (Message ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return Message ()
InitLinker
Word8
2 -> Message (Maybe (RemotePtr ())) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message (Maybe (RemotePtr ())) -> Msg)
-> (String -> Message (Maybe (RemotePtr ()))) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message (Maybe (RemotePtr ()))
LookupSymbol (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
3 -> Message (Maybe HValueRef) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show (RemoteRef a)
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type forall a. Binary (RemoteRef a)
Msg (Message (Maybe HValueRef) -> Msg)
-> (String -> Message (Maybe HValueRef)) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message (Maybe HValueRef)
LookupClosure (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
4 -> Message (Maybe String) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
Msg (Message (Maybe String) -> Msg)
-> (String -> Message (Maybe String)) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message (Maybe String)
LoadDLL (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
5 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> (String -> Message ()) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message ()
LoadArchive (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
6 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> (String -> Message ()) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message ()
LoadObj (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
7 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> (String -> Message ()) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message ()
UnloadObj (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
8 -> Message (RemotePtr ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message (RemotePtr ()) -> Msg)
-> (String -> Message (RemotePtr ())) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message (RemotePtr ())
AddLibrarySearchPath (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
9 -> Message Bool -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Binary Bool
External instance of the constraint type Show Bool
Msg (Message Bool -> Msg)
-> (RemotePtr () -> Message Bool) -> RemotePtr () -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> RemotePtr () -> Message Bool
RemoveLibrarySearchPath (RemotePtr () -> Msg) -> Get (RemotePtr ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemotePtr ())
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemotePtr a)
get
Word8
10 -> Message Bool -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show Bool
External instance of the constraint type Binary Bool
Msg (Message Bool -> Msg) -> Get (Message Bool) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Message Bool -> Get (Message Bool)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return Message Bool
ResolveObjs
Word8
11 -> Message (Maybe String) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
Msg (Message (Maybe String) -> Msg)
-> (String -> Message (Maybe String)) -> String -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> String -> Message (Maybe String)
FindSystemLibrary (String -> Msg) -> Get String -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get
Word8
12 -> Message [HValueRef] -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show (RemoteRef a)
Msg (Message [HValueRef] -> Msg)
-> ([ByteString] -> Message [HValueRef]) -> [ByteString] -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> [ByteString] -> Message [HValueRef]
CreateBCOs ([ByteString] -> Msg) -> Get [ByteString] -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get [ByteString]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
get
Word8
13 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg)
-> ([HValueRef] -> Message ()) -> [HValueRef] -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> [HValueRef] -> Message ()
FreeHValueRefs ([HValueRef] -> Msg) -> Get [HValueRef] -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get [HValueRef]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
get
Word8
14 -> Message (RemotePtr ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message (RemotePtr ()) -> Msg)
-> (ByteString -> Message (RemotePtr ())) -> ByteString -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> ByteString -> Message (RemotePtr ())
MallocData (ByteString -> Msg) -> Get ByteString -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get
Word8
15 -> Message [RemotePtr ()] -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message [RemotePtr ()] -> Msg)
-> ([ByteString] -> Message [RemotePtr ()]) -> [ByteString] -> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> [ByteString] -> Message [RemotePtr ()]
MallocStrings ([ByteString] -> Msg) -> Get [ByteString] -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get [ByteString]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
get
Word8
16 -> Message (RemotePtr C_ffi_cif) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Binary (RemotePtr a)
External instance of the constraint type forall a. Show (RemotePtr a)
Msg (Message (RemotePtr C_ffi_cif) -> Msg)
-> Get (Message (RemotePtr C_ffi_cif)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif)
PrepFFI (FFIConv -> [FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif))
-> Get FFIConv
-> Get ([FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get FFIConv
forall t. Binary t => Get t
External instance of the constraint type Binary FFIConv
get Get ([FFIType] -> FFIType -> Message (RemotePtr C_ffi_cif))
-> Get [FFIType] -> Get (FFIType -> Message (RemotePtr C_ffi_cif))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get [FFIType]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary FFIType
get Get (FFIType -> Message (RemotePtr C_ffi_cif))
-> Get FFIType -> Get (Message (RemotePtr C_ffi_cif))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get FFIType
forall t. Binary t => Get t
External instance of the constraint type Binary FFIType
get)
Word8
17 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg)
-> (RemotePtr C_ffi_cif -> Message ())
-> RemotePtr C_ffi_cif
-> Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall r. Functor ((->) r)
<$> RemotePtr C_ffi_cif -> Message ()
FreeFFI (RemotePtr C_ffi_cif -> Msg)
-> Get (RemotePtr C_ffi_cif) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemotePtr C_ffi_cif)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemotePtr a)
get
Word8
18 -> Message (RemotePtr StgInfoTable) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message (RemotePtr StgInfoTable) -> Msg)
-> Get (Message (RemotePtr StgInfoTable)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Bool
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> Message (RemotePtr StgInfoTable)
MkConInfoTable (Bool
-> Int
-> Int
-> Int
-> Int
-> ByteString
-> Message (RemotePtr StgInfoTable))
-> Get Bool
-> Get
(Int
-> Int
-> Int
-> Int
-> ByteString
-> Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get Get
(Int
-> Int
-> Int
-> Int
-> ByteString
-> Message (RemotePtr StgInfoTable))
-> Get Int
-> Get
(Int
-> Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get
(Int
-> Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable))
-> Get Int
-> Get
(Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get (Int -> Int -> ByteString -> Message (RemotePtr StgInfoTable))
-> Get Int
-> Get (Int -> ByteString -> Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get (Int -> ByteString -> Message (RemotePtr StgInfoTable))
-> Get Int -> Get (ByteString -> Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get (ByteString -> Message (RemotePtr StgInfoTable))
-> Get ByteString -> Get (Message (RemotePtr StgInfoTable))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get ByteString
forall t. Binary t => Get t
External instance of the constraint type Binary ByteString
get)
Word8
19 -> Message (EvalStatus_ [HValueRef] [HValueRef]) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a b. Show a => Show (EvalStatus_ a b)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show (RemoteRef a)
Instance of class: Binary of the constraint type forall a b. Binary a => Binary (EvalStatus_ a b)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
Msg (Message (EvalStatus_ [HValueRef] [HValueRef]) -> Msg)
-> Get (Message (EvalStatus_ [HValueRef] [HValueRef])) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (EvalOpts
-> EvalExpr HValueRef
-> Message (EvalStatus_ [HValueRef] [HValueRef])
EvalStmt (EvalOpts
-> EvalExpr HValueRef
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
-> Get EvalOpts
-> Get
(EvalExpr HValueRef
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get EvalOpts
forall t. Binary t => Get t
Instance of class: Binary of the constraint type Binary EvalOpts
get Get
(EvalExpr HValueRef
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
-> Get (EvalExpr HValueRef)
-> Get (Message (EvalStatus_ [HValueRef] [HValueRef]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (EvalExpr HValueRef)
forall t. Binary t => Get t
Instance of class: Binary of the constraint type forall a. Binary a => Binary (EvalExpr a)
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
20 -> Message (EvalStatus_ [HValueRef] [HValueRef]) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a b. Show a => Show (EvalStatus_ a b)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show (RemoteRef a)
Instance of class: Binary of the constraint type forall a b. Binary a => Binary (EvalStatus_ a b)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
Msg (Message (EvalStatus_ [HValueRef] [HValueRef]) -> Msg)
-> Get (Message (EvalStatus_ [HValueRef] [HValueRef])) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (EvalOpts
-> RemoteRef (ResumeContext [HValueRef])
-> Message (EvalStatus_ [HValueRef] [HValueRef])
ResumeStmt (EvalOpts
-> RemoteRef (ResumeContext [HValueRef])
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
-> Get EvalOpts
-> Get
(RemoteRef (ResumeContext [HValueRef])
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get EvalOpts
forall t. Binary t => Get t
Instance of class: Binary of the constraint type Binary EvalOpts
get Get
(RemoteRef (ResumeContext [HValueRef])
-> Message (EvalStatus_ [HValueRef] [HValueRef]))
-> Get (RemoteRef (ResumeContext [HValueRef]))
-> Get (Message (EvalStatus_ [HValueRef] [HValueRef]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (RemoteRef (ResumeContext [HValueRef]))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
21 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef (ResumeContext [HValueRef]) -> Message ()
AbandonStmt (RemoteRef (ResumeContext [HValueRef]) -> Message ())
-> Get (RemoteRef (ResumeContext [HValueRef])) -> Get (Message ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef (ResumeContext [HValueRef]))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
22 -> Message (EvalResult String) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a. Show a => Show (EvalResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
Instance of class: Binary of the constraint type forall a. Binary a => Binary (EvalResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
Msg (Message (EvalResult String) -> Msg)
-> Get (Message (EvalResult String)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> Message (EvalResult String)
EvalString (HValueRef -> Message (EvalResult String))
-> Get HValueRef -> Get (Message (EvalResult String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
23 -> Message (EvalResult String) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a. Show a => Show (EvalResult a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
Instance of class: Binary of the constraint type forall a. Binary a => Binary (EvalResult a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
Msg (Message (EvalResult String) -> Msg)
-> Get (Message (EvalResult String)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> String -> Message (EvalResult String)
EvalStringToString (HValueRef -> String -> Message (EvalResult String))
-> Get HValueRef -> Get (String -> Message (EvalResult String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get (String -> Message (EvalResult String))
-> Get String -> Get (Message (EvalResult String))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get)
Word8
24 -> Message (EvalResult ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a. Show a => Show (EvalResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (EvalResult a)
External instance of the constraint type Binary ()
Msg (Message (EvalResult ()) -> Msg)
-> Get (Message (EvalResult ())) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> Message (EvalResult ())
EvalIO (HValueRef -> Message (EvalResult ()))
-> Get HValueRef -> Get (Message (EvalResult ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
25 -> Message [RemotePtr CostCentre] -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show (RemotePtr a)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemotePtr a)
Msg (Message [RemotePtr CostCentre] -> Msg)
-> Get (Message [RemotePtr CostCentre]) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (String -> [(String, String)] -> Message [RemotePtr CostCentre]
MkCostCentres (String -> [(String, String)] -> Message [RemotePtr CostCentre])
-> Get String
-> Get ([(String, String)] -> Message [RemotePtr CostCentre])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get String
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get Get ([(String, String)] -> Message [RemotePtr CostCentre])
-> Get [(String, String)] -> Get (Message [RemotePtr CostCentre])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get [(String, String)]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
get)
Word8
26 -> Message [String] -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
Msg (Message [String] -> Msg) -> Get (Message [String]) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemotePtr CostCentreStack -> Message [String]
CostCentreStackInfo (RemotePtr CostCentreStack -> Message [String])
-> Get (RemotePtr CostCentreStack) -> Get (Message [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemotePtr CostCentreStack)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemotePtr a)
get)
Word8
27 -> Message (RemoteRef BreakArray) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Binary (RemoteRef a)
External instance of the constraint type forall a. Show (RemoteRef a)
Msg (Message (RemoteRef BreakArray) -> Msg)
-> Get (Message (RemoteRef BreakArray)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Int -> Message (RemoteRef BreakArray)
NewBreakArray (Int -> Message (RemoteRef BreakArray))
-> Get Int -> Get (Message (RemoteRef BreakArray))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get)
Word8
28 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef BreakArray -> Int -> Bool -> Message ()
EnableBreakpoint (RemoteRef BreakArray -> Int -> Bool -> Message ())
-> Get (RemoteRef BreakArray) -> Get (Int -> Bool -> Message ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef BreakArray)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get (Int -> Bool -> Message ())
-> Get Int -> Get (Bool -> Message ())
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get Get (Bool -> Message ()) -> Get Bool -> Get (Message ())
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Bool
forall t. Binary t => Get t
External instance of the constraint type Binary Bool
get)
Word8
29 -> Message Bool -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show Bool
External instance of the constraint type Binary Bool
Msg (Message Bool -> Msg) -> Get (Message Bool) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef BreakArray -> Int -> Message Bool
BreakpointStatus (RemoteRef BreakArray -> Int -> Message Bool)
-> Get (RemoteRef BreakArray) -> Get (Int -> Message Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef BreakArray)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get (Int -> Message Bool) -> Get Int -> Get (Message Bool)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get)
Word8
30 -> Message (Maybe HValueRef) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show (RemoteRef a)
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type forall a. Binary (RemoteRef a)
Msg (Message (Maybe HValueRef) -> Msg)
-> Get (Message (Maybe HValueRef)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> Int -> Message (Maybe HValueRef)
GetBreakpointVar (HValueRef -> Int -> Message (Maybe HValueRef))
-> Get HValueRef -> Get (Int -> Message (Maybe HValueRef))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get (Int -> Message (Maybe HValueRef))
-> Get Int -> Get (Message (Maybe HValueRef))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get Int
forall t. Binary t => Get t
External instance of the constraint type Binary Int
get)
Word8
31 -> Message (RemoteRef (IORef QState)) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall a. Binary (RemoteRef a)
External instance of the constraint type forall a. Show (RemoteRef a)
Msg (Message (RemoteRef (IORef QState)) -> Msg)
-> Get (Message (RemoteRef (IORef QState))) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Message (RemoteRef (IORef QState))
-> Get (Message (RemoteRef (IORef QState)))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return Message (RemoteRef (IORef QState))
StartTH
Word8
32 -> Message (QResult ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a. Show a => Show (QResult a)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a. Binary a => Binary (QResult a)
External instance of the constraint type Binary ()
Msg (Message (QResult ()) -> Msg)
-> Get (Message (QResult ())) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef (IORef QState)
-> [RemoteRef (Q ())] -> Message (QResult ())
RunModFinalizers (RemoteRef (IORef QState)
-> [RemoteRef (Q ())] -> Message (QResult ()))
-> Get (RemoteRef (IORef QState))
-> Get ([RemoteRef (Q ())] -> Message (QResult ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef (IORef QState))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get ([RemoteRef (Q ())] -> Message (QResult ()))
-> Get [RemoteRef (Q ())] -> Get (Message (QResult ()))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get [RemoteRef (Q ())]
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
33 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (Fingerprint -> HValueRef -> Message ()
AddSptEntry (Fingerprint -> HValueRef -> Message ())
-> Get Fingerprint -> Get (HValueRef -> Message ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get Fingerprint
forall t. Binary t => Get t
External instance of the constraint type Binary Fingerprint
get Get (HValueRef -> Message ()) -> Get HValueRef -> Get (Message ())
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
34 -> Message (QResult ByteString) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a. Show a => Show (QResult a)
External instance of the constraint type Show ByteString
Instance of class: Binary of the constraint type forall a. Binary a => Binary (QResult a)
External instance of the constraint type Binary ByteString
Msg (Message (QResult ByteString) -> Msg)
-> Get (Message (QResult ByteString)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef (IORef QState)
-> HValueRef
-> THResultType
-> Maybe Loc
-> Message (QResult ByteString)
RunTH (RemoteRef (IORef QState)
-> HValueRef
-> THResultType
-> Maybe Loc
-> Message (QResult ByteString))
-> Get (RemoteRef (IORef QState))
-> Get
(HValueRef
-> THResultType -> Maybe Loc -> Message (QResult ByteString))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef (IORef QState))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get
(HValueRef
-> THResultType -> Maybe Loc -> Message (QResult ByteString))
-> Get HValueRef
-> Get (THResultType -> Maybe Loc -> Message (QResult ByteString))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get Get (THResultType -> Maybe Loc -> Message (QResult ByteString))
-> Get THResultType
-> Get (Maybe Loc -> Message (QResult ByteString))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get THResultType
forall t. Binary t => Get t
Instance of class: Binary of the constraint type Binary THResultType
get Get (Maybe Loc -> Message (QResult ByteString))
-> Get (Maybe Loc) -> Get (Message (QResult ByteString))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
External instance of the constraint type Applicative Get
<*> Get (Maybe Loc)
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Loc
get)
Word8
35 -> Message (GenClosure HValueRef) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type forall b. Show b => Show (GenClosure b)
External instance of the constraint type forall a. Show (RemoteRef a)
Instance of class: Binary of the constraint type forall a. Binary a => Binary (GenClosure a)
External instance of the constraint type forall a. Binary (RemoteRef a)
Msg (Message (GenClosure HValueRef) -> Msg)
-> Get (Message (GenClosure HValueRef)) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> Message (GenClosure HValueRef)
GetClosure (HValueRef -> Message (GenClosure HValueRef))
-> Get HValueRef -> Get (Message (GenClosure HValueRef))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
36 -> Message (EvalStatus_ () ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a b. Show a => Show (EvalStatus_ a b)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a b. Binary a => Binary (EvalStatus_ a b)
External instance of the constraint type Binary ()
Msg (Message (EvalStatus_ () ()) -> Msg)
-> Get (Message (EvalStatus_ () ())) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (HValueRef -> Message (EvalStatus_ () ())
Seq (HValueRef -> Message (EvalStatus_ () ()))
-> Get HValueRef -> Get (Message (EvalStatus_ () ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get HValueRef
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
37 -> Message () -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
External instance of the constraint type Show ()
External instance of the constraint type Binary ()
Msg (Message () -> Msg) -> Get (Message ()) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Message () -> Get (Message ())
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad Get
return Message ()
RtsRevertCAFs
Word8
38 -> Message (EvalStatus_ () ()) -> Msg
forall a. (Binary a, Show a) => Message a -> Msg
Instance of class: Show of the constraint type forall a b. Show a => Show (EvalStatus_ a b)
External instance of the constraint type Show ()
Instance of class: Binary of the constraint type forall a b. Binary a => Binary (EvalStatus_ a b)
External instance of the constraint type Binary ()
Msg (Message (EvalStatus_ () ()) -> Msg)
-> Get (Message (EvalStatus_ () ())) -> Get Msg
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> (RemoteRef (ResumeContext ()) -> Message (EvalStatus_ () ())
ResumeSeq (RemoteRef (ResumeContext ()) -> Message (EvalStatus_ () ()))
-> Get (RemoteRef (ResumeContext ()))
-> Get (Message (EvalStatus_ () ()))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Get
<$> Get (RemoteRef (ResumeContext ()))
forall t. Binary t => Get t
External instance of the constraint type forall a. Binary (RemoteRef a)
get)
Word8
_ -> String -> Get Msg
forall a. HasCallStack => String -> a
error (String -> Get Msg) -> String -> Get Msg
forall a b. (a -> b) -> a -> b
$ String
"Unknown Message code " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Word8 -> String
forall a. Show a => a -> String
External instance of the constraint type Show Word8
show Word8
b)
putMessage :: Message a -> Put
putMessage :: Message a -> Put
putMessage Message a
m = case Message a
m of
Message a
External instance of the constraint type Num Word8
Shutdown -> Word8 -> Put
putWord8 Word8
0
Message a
External instance of the constraint type Num Word8
InitLinker -> Word8 -> Put
putWord8 Word8
1
LookupSymbol String
str -> Word8 -> Put
putWord8 Word8
2 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
LookupClosure String
str -> Word8 -> Put
putWord8 Word8
3 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
LoadDLL String
str -> Word8 -> Put
putWord8 Word8
4 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
LoadArchive String
str -> Word8 -> Put
putWord8 Word8
5 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
LoadObj String
str -> Word8 -> Put
putWord8 Word8
6 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
UnloadObj String
str -> Word8 -> Put
putWord8 Word8
7 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
AddLibrarySearchPath String
str -> Word8 -> Put
putWord8 Word8
8 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
RemoveLibrarySearchPath RemotePtr ()
ptr -> Word8 -> Put
putWord8 Word8
9 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemotePtr () -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemotePtr a)
put RemotePtr ()
ptr
Message a
External instance of the constraint type Num Word8
ResolveObjs -> Word8 -> Put
putWord8 Word8
10
FindSystemLibrary String
str -> Word8 -> Put
putWord8 Word8
11 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
str
CreateBCOs [ByteString]
bco -> Word8 -> Put
putWord8 Word8
12 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [ByteString] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
put [ByteString]
bco
FreeHValueRefs [HValueRef]
val -> Word8 -> Put
putWord8 Word8
13 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [HValueRef] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
put [HValueRef]
val
MallocData ByteString
bs -> Word8 -> Put
putWord8 Word8
14 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
bs
MallocStrings [ByteString]
bss -> Word8 -> Put
putWord8 Word8
15 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [ByteString] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary ByteString
put [ByteString]
bss
PrepFFI FFIConv
conv [FFIType]
args FFIType
res -> Word8 -> Put
putWord8 Word8
16 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> FFIConv -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary FFIConv
put FFIConv
conv Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [FFIType] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary FFIType
put [FFIType]
args Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> FFIType -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary FFIType
put FFIType
res
FreeFFI RemotePtr C_ffi_cif
p -> Word8 -> Put
putWord8 Word8
17 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemotePtr C_ffi_cif -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemotePtr a)
put RemotePtr C_ffi_cif
p
MkConInfoTable Bool
tc Int
p Int
n Int
t Int
pt ByteString
d -> Word8 -> Put
putWord8 Word8
18 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
tc Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
p Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
n Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
t Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
pt Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> ByteString -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary ByteString
put ByteString
d
EvalStmt EvalOpts
opts EvalExpr HValueRef
val -> Word8 -> Put
putWord8 Word8
19 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> EvalOpts -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type Binary EvalOpts
put EvalOpts
opts Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> EvalExpr HValueRef -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type forall a. Binary a => Binary (EvalExpr a)
External instance of the constraint type forall a. Binary (RemoteRef a)
put EvalExpr HValueRef
val
ResumeStmt EvalOpts
opts RemoteRef (ResumeContext [HValueRef])
val -> Word8 -> Put
putWord8 Word8
20 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> EvalOpts -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type Binary EvalOpts
put EvalOpts
opts Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (ResumeContext [HValueRef]) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (ResumeContext [HValueRef])
val
AbandonStmt RemoteRef (ResumeContext [HValueRef])
val -> Word8 -> Put
putWord8 Word8
21 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (ResumeContext [HValueRef]) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (ResumeContext [HValueRef])
val
EvalString HValueRef
val -> Word8 -> Put
putWord8 Word8
22 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
val
EvalStringToString HValueRef
str String
val -> Word8 -> Put
putWord8 Word8
23 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
str Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
val
EvalIO HValueRef
val -> Word8 -> Put
putWord8 Word8
24 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
val
MkCostCentres String
mod [(String, String)]
ccs -> Word8 -> Put
putWord8 Word8
25 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> String -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put String
mod Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [(String, String)] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a b. (Binary a, Binary b) => Binary (a, b)
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type Binary Char
put [(String, String)]
ccs
CostCentreStackInfo RemotePtr CostCentreStack
ptr -> Word8 -> Put
putWord8 Word8
26 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemotePtr CostCentreStack -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemotePtr a)
put RemotePtr CostCentreStack
ptr
NewBreakArray Int
sz -> Word8 -> Put
putWord8 Word8
27 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
sz
EnableBreakpoint RemoteRef BreakArray
arr Int
ix Bool
b -> Word8 -> Put
putWord8 Word8
28 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef BreakArray -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef BreakArray
arr Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
ix Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Bool -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Bool
put Bool
b
BreakpointStatus RemoteRef BreakArray
arr Int
ix -> Word8 -> Put
putWord8 Word8
29 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef BreakArray -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef BreakArray
arr Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
ix
GetBreakpointVar HValueRef
a Int
b -> Word8 -> Put
putWord8 Word8
30 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Int -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Int
put Int
b
Message a
External instance of the constraint type Num Word8
StartTH -> Word8 -> Put
putWord8 Word8
31
RunModFinalizers RemoteRef (IORef QState)
a [RemoteRef (Q ())]
b -> Word8 -> Put
putWord8 Word8
32 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (IORef QState) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (IORef QState)
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> [RemoteRef (Q ())] -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary [a]
External instance of the constraint type forall a. Binary (RemoteRef a)
put [RemoteRef (Q ())]
b
AddSptEntry Fingerprint
a HValueRef
b -> Word8 -> Put
putWord8 Word8
33 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Fingerprint -> Put
forall t. Binary t => t -> Put
External instance of the constraint type Binary Fingerprint
put Fingerprint
a Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
b
RunTH RemoteRef (IORef QState)
st HValueRef
q THResultType
loc Maybe Loc
ty -> Word8 -> Put
putWord8 Word8
34 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (IORef QState) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (IORef QState)
st Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
q Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> THResultType -> Put
forall t. Binary t => t -> Put
Instance of class: Binary of the constraint type Binary THResultType
put THResultType
loc Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> Maybe Loc -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary a => Binary (Maybe a)
External instance of the constraint type Binary Loc
put Maybe Loc
ty
GetClosure HValueRef
a -> Word8 -> Put
putWord8 Word8
35 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
a
Seq HValueRef
a -> Word8 -> Put
putWord8 Word8
36 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> HValueRef -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put HValueRef
a
Message a
External instance of the constraint type Num Word8
RtsRevertCAFs -> Word8 -> Put
putWord8 Word8
37
ResumeSeq RemoteRef (ResumeContext ())
a -> Word8 -> Put
putWord8 Word8
38 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type Monad PutM
>> RemoteRef (ResumeContext ()) -> Put
forall t. Binary t => t -> Put
External instance of the constraint type forall a. Binary (RemoteRef a)
put RemoteRef (ResumeContext ())
a
data Pipe = Pipe
{ Pipe -> Handle
pipeRead :: Handle
, Pipe -> Handle
pipeWrite :: Handle
, Pipe -> IORef (Maybe ByteString)
pipeLeftovers :: IORef (Maybe ByteString)
}
remoteCall :: Binary a => Pipe -> Message a -> IO a
remoteCall :: Pipe -> Message a -> IO a
remoteCall Pipe
pipe Message a
msg = do
Pipe -> Put -> IO ()
writePipe Pipe
pipe (Message a -> Put
forall a. Message a -> Put
putMessage Message a
msg)
Pipe -> Get a -> IO a
forall a. Pipe -> Get a -> IO a
readPipe Pipe
pipe Get a
forall t. Binary t => Get t
Evidence bound by a type signature of the constraint type Binary a
get
remoteTHCall :: Binary a => Pipe -> THMessage a -> IO a
remoteTHCall :: Pipe -> THMessage a -> IO a
remoteTHCall Pipe
pipe THMessage a
msg = do
Pipe -> Put -> IO ()
writePipe Pipe
pipe (THMessage a -> Put
forall a. THMessage a -> Put
putTHMessage THMessage a
msg)
Pipe -> Get a -> IO a
forall a. Pipe -> Get a -> IO a
readPipe Pipe
pipe Get a
forall t. Binary t => Get t
Evidence bound by a type signature of the constraint type Binary a
get
writePipe :: Pipe -> Put -> IO ()
writePipe :: Pipe -> Put -> IO ()
writePipe Pipe{Handle
IORef (Maybe ByteString)
pipeLeftovers :: IORef (Maybe ByteString)
pipeWrite :: Handle
pipeRead :: Handle
pipeLeftovers :: Pipe -> IORef (Maybe ByteString)
pipeWrite :: Pipe -> Handle
pipeRead :: Pipe -> Handle
..} Put
put
| ByteString -> Bool
LB.null ByteString
bs = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ()
| Bool
otherwise = do
Handle -> ByteString -> IO ()
LB.hPut Handle
pipeWrite ByteString
bs
Handle -> IO ()
hFlush Handle
pipeWrite
where
bs :: ByteString
bs = Put -> ByteString
runPut Put
put
readPipe :: Pipe -> Get a -> IO a
readPipe :: Pipe -> Get a -> IO a
readPipe Pipe{Handle
IORef (Maybe ByteString)
pipeLeftovers :: IORef (Maybe ByteString)
pipeWrite :: Handle
pipeRead :: Handle
pipeLeftovers :: Pipe -> IORef (Maybe ByteString)
pipeWrite :: Pipe -> Handle
pipeRead :: Pipe -> Handle
..} Get a
get = do
Maybe ByteString
leftovers <- IORef (Maybe ByteString) -> IO (Maybe ByteString)
forall a. IORef a -> IO a
readIORef IORef (Maybe ByteString)
pipeLeftovers
Maybe (a, Maybe ByteString)
m <- Handle
-> Get a -> Maybe ByteString -> IO (Maybe (a, Maybe ByteString))
forall a.
Handle
-> Get a -> Maybe ByteString -> IO (Maybe (a, Maybe ByteString))
getBin Handle
pipeRead Get a
get Maybe ByteString
leftovers
case Maybe (a, Maybe ByteString)
m of
Maybe (a, Maybe ByteString)
Nothing -> IOError -> IO a
forall a e. Exception e => e -> a
External instance of the constraint type Exception IOError
throw (IOError -> IO a) -> IOError -> IO a
forall a b. (a -> b) -> a -> b
$
IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
eofErrorType String
"GHCi.Message.remoteCall" (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
pipeRead) Maybe String
forall a. Maybe a
Nothing
Just (a
result, Maybe ByteString
new_leftovers) -> do
IORef (Maybe ByteString) -> Maybe ByteString -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe ByteString)
pipeLeftovers Maybe ByteString
new_leftovers
a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return a
result
getBin
:: Handle -> Get a -> Maybe ByteString
-> IO (Maybe (a, Maybe ByteString))
getBin :: Handle
-> Get a -> Maybe ByteString -> IO (Maybe (a, Maybe ByteString))
getBin Handle
h Get a
get Maybe ByteString
leftover = Maybe ByteString -> Decoder a -> IO (Maybe (a, Maybe ByteString))
go Maybe ByteString
leftover (Get a -> Decoder a
forall a. Get a -> Decoder a
runGetIncremental Get a
get)
where
go :: Maybe ByteString -> Decoder a -> IO (Maybe (a, Maybe ByteString))
go Maybe ByteString
Nothing (Done ByteString
leftover Int64
_ a
msg) =
Maybe (a, Maybe ByteString) -> IO (Maybe (a, Maybe ByteString))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ((a, Maybe ByteString) -> Maybe (a, Maybe ByteString)
forall a. a -> Maybe a
Just (a
msg, if ByteString -> Bool
B.null ByteString
leftover then Maybe ByteString
forall a. Maybe a
Nothing else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
leftover))
go Maybe ByteString
_ Done{} = ErrorCall -> IO (Maybe (a, Maybe ByteString))
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception ErrorCall
throwIO (String -> ErrorCall
ErrorCall String
"getBin: Done with leftovers")
go (Just ByteString
leftover) (Partial Maybe ByteString -> Decoder a
fun) = do
Maybe ByteString -> Decoder a -> IO (Maybe (a, Maybe ByteString))
go Maybe ByteString
forall a. Maybe a
Nothing (Maybe ByteString -> Decoder a
fun (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
leftover))
go Maybe ByteString
Nothing (Partial Maybe ByteString -> Decoder a
fun) = do
ByteString
b <- Handle -> Int -> IO ByteString
B.hGetSome Handle
h (Int
32Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
1024)
if ByteString -> Bool
B.null ByteString
b
then Maybe (a, Maybe ByteString) -> IO (Maybe (a, Maybe ByteString))
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Maybe (a, Maybe ByteString)
forall a. Maybe a
Nothing
else Maybe ByteString -> Decoder a -> IO (Maybe (a, Maybe ByteString))
go Maybe ByteString
forall a. Maybe a
Nothing (Maybe ByteString -> Decoder a
fun (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
b))
go Maybe ByteString
_lft (Fail ByteString
_rest Int64
_off String
str) =
ErrorCall -> IO (Maybe (a, Maybe ByteString))
forall e a. Exception e => e -> IO a
External instance of the constraint type Exception ErrorCall
throwIO (String -> ErrorCall
ErrorCall (String
"getBin: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str))