Portability | GeneralizedNewtypeDeriving, StandaloneDeriving, ScopedTypeVariables, FlexibleInstances, UndecidableInstances, MultiParamTypeClasses, FunctionalDependencies, IncoherentInstances, TypeFamilies |
---|---|
Stability | experimental |
Maintainer | Matthew Mirman <mmirman@andrew.cmu.edu> |
Safe Haskell | None |
The functions for using a function as a service and calling a remote process
- data WIO w m a
- onHost :: forall w m. (Servable m, Host w) => w -> WIO w m ()
- world :: forall w m. (Servable m, Host w) => WIO w m w
- realRemoteCall :: forall a a' w m. RPC a a' m w => a -> String -> a'
- makeService :: Service a m w => a -> String -> WIO w m ()
- class Host a where
- class (Host w, Servable m, Servable m') => Sendable w m a m' a' | m a' w -> a, m' a -> a', a -> m w, a' -> m'
- class (Servable m, Servable m') => Receivable m a m' a' | m a' -> a, m' a -> a', a -> m, a' -> m'
- class (Functor m, Monad m, MonadIO m, Forkable m) => Servable m
- data Ref a a'
- liftIO :: MonadIO m => forall a. IO a -> m a
- runServer :: forall w m. (Servable m, Host w) => WIO w m () -> m ()
- runServerBG :: Host w => WIO w IO () -> IO ThreadId
Documentation
is a newtype over a server transformer that adds the phantom
host argument WIO
w m aw
(Receivable m' a' m a, Sendable w m b m' b') => Sendable w m (a -> b) m' (a' -> WIO w' m' b') | |
Sendable w m b m' b' => Sendable w m (WIO w m b) m' (WIO w' m' b') | |
(Sendable w' m' a' m a, Receivable m b m' b') => Receivable m (a -> b) m' (a' -> WIO w' m' b') | |
Receivable m b m' b' => Receivable m (WIO w m b) m' (WIO w' m' b') | |
MonadTrans (WIO w) | |
Monad m => Monad (WIO w m) | |
Functor m => Functor (WIO w m) | |
MonadIO m => MonadIO (WIO w m) | |
Forkable m => Forkable (WIO w m) | |
Servable m => Servable (WIO w m) | |
(Host w, Servable m, Sendable w m a m a') => Service (WIO w m a) m w | |
(Receivable m a m' a', Host w, Host w', Servable m, Servable m') => RPC (WIO w m a) (WIO w' m' a') m' w' |
onHost :: forall w m. (Servable m, Host w) => w -> WIO w m ()Source
onHost
declares that the code is running on the given host.
it is usefull when a type inference is wanted, but the action
also needs to be made into a service and used as a remote procedure
realRemoteCall :: forall a a' w m. RPC a a' m w => a -> String -> a'Source
makeService :: Service a m w => a -> String -> WIO w m ()Source
declares that the world is a host. It should
only have one constructor, and the location and port should be invariant
of the given constructor.
Specifically, Host
WorldgetLocation
and getPort
should work even if bottom is supplied.
class (Host w, Servable m, Servable m') => Sendable w m a m' a' | m a' w -> a, m' a -> a', a -> m w, a' -> m'Source
class (Servable m, Servable m') => Receivable m a m' a' | m a' -> a, m' a -> a', a -> m, a' -> m'Source
(Show a, Read a', ~ * a a', Servable m', Servable m) => Receivable m a m' a' | |
(Sendable w' m' a' m a, Receivable m b m' b') => Receivable m (a -> b) m' (a' -> WIO w' m' b') | |
Receivable m b m' b' => Receivable m (WIO w m b) m' (WIO w' m' b') |
class (Functor m, Monad m, MonadIO m, Forkable m) => Servable m Source
Servable
is a declaration that the given monad can be made into a
servlet.
runServer :: forall w m. (Servable m, Host w) => WIO w m () -> m ()Source
runServer
runs a name server and doesn't return
runServerBG :: Host w => WIO w IO () -> IO ThreadIdSource
runServerBG
runs a name server on a background thread and does return