Safe Haskell | None |
---|---|
Language | Haskell98 |
- remoteTable :: RemoteTable -> RemoteTable
- staticDecode :: Typeable a => Static (SerializableDict a) -> Static (ByteString -> a)
- sdictUnit :: Static (SerializableDict ())
- sdictProcessId :: Static (SerializableDict ProcessId)
- sdictSendPort :: Typeable a => Static (SerializableDict a) -> Static (SerializableDict (SendPort a))
- sdictStatic :: Typeable a => Static (TypeableDict a) -> Static (SerializableDict (Static a))
- sdictClosure :: Typeable a => Static (TypeableDict a) -> Static (SerializableDict (Closure a))
- sndStatic :: Static ((a, b) -> b)
- type CP a b = Closure (a -> Process b)
- idCP :: Typeable a => CP a a
- splitCP :: (Typeable a, Typeable b, Typeable c, Typeable d) => CP a c -> CP b d -> CP (a, b) (c, d)
- returnCP :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure (Process a)
- bindCP :: forall a b. (Typeable a, Typeable b) => Closure (Process a) -> CP a b -> Closure (Process b)
- seqCP :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (Process b) -> Closure (Process b)
- decodeProcessIdStatic :: Static (ByteString -> ProcessId)
- cpLink :: ProcessId -> Closure (Process ())
- cpUnlink :: ProcessId -> Closure (Process ())
- cpRelay :: ProcessId -> Closure (Process ())
- cpSend :: forall a. Typeable a => Static (SerializableDict a) -> ProcessId -> CP a ()
- cpExpect :: Typeable a => Static (SerializableDict a) -> Closure (Process a)
- cpNewChan :: Typeable a => Static (SerializableDict a) -> Closure (Process (SendPort a, ReceivePort a))
- cpDelayed :: ProcessId -> Closure (Process ()) -> Closure (Process ())
- cpEnableTraceRemote :: ProcessId -> Closure (Process ())
Remote table
Static dictionaries and associated operations
staticDecode :: Typeable a => Static (SerializableDict a) -> Static (ByteString -> a) Source
Static decoder, given a static serialization dictionary.
See module documentation of Control.Distributed.Process.Closure for an example.
sdictUnit :: Static (SerializableDict ()) Source
Serialization dictionary for '()'
sdictProcessId :: Static (SerializableDict ProcessId) Source
Serialization dictionary for ProcessId
sdictSendPort :: Typeable a => Static (SerializableDict a) -> Static (SerializableDict (SendPort a)) Source
Serialization dictionary for SendPort
sdictStatic :: Typeable a => Static (TypeableDict a) -> Static (SerializableDict (Static a)) Source
Serialization dictionary for Static
.
sdictClosure :: Typeable a => Static (TypeableDict a) -> Static (SerializableDict (Closure a)) Source
Serialization dictionary for Closure
.
Some static values
The CP type and associated combinators
type CP a b = Closure (a -> Process b) Source
CP a b
is a process with input of type a
and output of type b
splitCP :: (Typeable a, Typeable b, Typeable c, Typeable d) => CP a c -> CP b d -> CP (a, b) (c, d) Source
returnCP :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure (Process a) Source
bindCP :: forall a b. (Typeable a, Typeable b) => Closure (Process a) -> CP a b -> Closure (Process b) Source
seqCP :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (Process b) -> Closure (Process b) Source
CP versions of Cloud Haskell primitives
cpNewChan :: Typeable a => Static (SerializableDict a) -> Closure (Process (SendPort a, ReceivePort a)) Source
Support for some CH operations
cpEnableTraceRemote :: ProcessId -> Closure (Process ()) Source