| Portability | Many GHC only extensions |
|---|---|
| Stability | experimental |
| Maintainer | Matthew Mirman <mmirman@andrew.cmu.edu> |
| Safe Haskell | None |
Network.Remote.RPC
Contents
Description
Declaration of the frontend for RPC.
- class Host a where
- data WIO w m a
- world :: forall w m. (Servable m, Host w) => WIO w m w
- class (Functor m, Monad m, MonadIO m, Forkable m) => Servable m
- 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
- onHost :: forall w m. (Servable m, Host w) => w -> WIO w m ()
- autoService :: Name -> Q Exp
- makeHost :: String -> String -> Integer -> Q [Dec]
- makeServices :: [Name] -> Q Exp
- rpcCall :: Name -> Q Exp
- class Monad m => Forkable m where
- class MonadTrans t where
Documentation
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.
is a newtype over a server transformer that adds the phantom
host argument WIO w m aw
Instances
| (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' |
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
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
autoService :: Name -> Q ExpSource
$( finds all services declared in the
module that definitely run on the given world,
and makes them listen for incoming requests.
autoService 'World)
makeHost :: String -> String -> Integer -> Q [Dec]Source
$(
makes a makeHost "HostName" "hostLocation" hostPortNumber)newtype HostName and declares an instance .
Host HostName
makeServices :: [Name] -> Q ExpSource
$( makes all given
services listen for incoming requests.
makeServices ['service1 ,..., 'serviceN])
rpcCall :: Name -> Q ExpSource
$( simply splices in
rpcCall 'serviceNm) which is typed in a manner
similar to typeofcall.
realRemoteCall (undefined :: typeofcall) "serviceNm"
Example: Making remote Calls
This example shows how to make remote procedure from a Client to a Host. It also shows how to send functions, which can now be collected.
-- LANGUAGE TemplateHaskell, KindSignatures, FlexibleContexts module Main where import Network.Remote.RPC
First, hosts must be declared. In the future, hosts might be declared in a configuration file such that they can be configured at runtime rather than only at compile time.
$(makeHost"Client" "localhost" 9000) $(makeHost"Server" "localhost" 9001)
The following services will run on the server.
doubleServer :: Integer ->WIOServer IO Integer doubleServer t = return $ t + t addServer :: Integer ->WIOServer IO (Integer -> Integer) addServer t = return (t +)
When used, addServer will return a function of type Integer ->
because the resulting function will actually be a remote call. Every time WIO w IO IntegeraddServer
is called, it turns the function into a service which is collected when the function is no
longer needed.
client = do
onHost Client
double <- $(rpcCall 'doubleServer) 3
liftIO $ putStrLn $ "r(h3+h3) ? " ++ show double
add <- $(rpcCall 'addServer) 4
r <- add 6 -- add :: Integer -> WIO Client IO Integer
liftIO $ putStrLn $ "r(h4 +) h6 ? " ++ show r
Despite rpcCall being a template splice, the resulting splice is type safe:
$(rpcCall'doubleServer) :: (Hostw,Servablem) => Integer ->WIOw m Integer
Now we declare the runtime. Usually this would be in two different mains, but for educational and testing purposes, both the client and server can be run from the same main.
main = dorunServerBG$(autoService 'Server)runServerclient
-
$(looks for services declared in the file which definitely run on server, and runs them as services on the intended host (autoService'Server)Serverin this case). -
runServerBGruns a service server on a background OS thread, and returns -
runServerruns a service server and does not return. - When run:
>>>:mainr(h3+h3) ? 6 r(h4 +) h6 ? 10
Where rVal means Val is on the server and hVal means Val is on the client.
class MonadTrans t where
The class of monad transformers. Instances should satisfy the
following laws, which state that lift is a transformer of monads:
Methods
lift :: Monad m => m a -> t m a
Lift a computation from the argument monad to the constructed monad.
Instances
| MonadTrans ListT | |
| MonadTrans MaybeT | |
| MonadTrans IdentityT | |
| MonadTrans AIO | |
| MonadTrans (ContT r) | |
| Error e => MonadTrans (ErrorT e) | |
| MonadTrans (ReaderT r) | |
| MonadTrans (StateT s) | |
| MonadTrans (StateT s) | |
| Monoid w => MonadTrans (WriterT w) | |
| Monoid w => MonadTrans (WriterT w) | |
| MonadTrans (WIO w) | |
| Monoid w => MonadTrans (RWST r w s) | |
| Monoid w => MonadTrans (RWST r w s) |