krpc-0.5.0.0: KRPC protocol implementation

Portabilityportable
Stabilityexperimental
Maintainerpxqr.sta@gmail.com
Safe HaskellNone

Network.KRPC

Contents

Description

This module provides safe remote procedure call. One important point is exceptions and errors, so to be able handle them properly we need to investigate a bit about how this all works. Internally, in order to make method invokation KRPC makes the following steps:

  • Caller serialize arguments to bencoded bytestrings;
  • Caller send bytestring data over UDP to the callee;
  • Callee receive and decode arguments to the method and method name. If it can't decode then it send ProtocolError back to the caller;
  • Callee search for the method name in the method table. If it not present in the table then callee send MethodUnknown back to the caller;
  • Callee check if argument names match. If not it send ProtocolError back;
  • Callee make the actuall call to the plain old haskell function. If the function throw exception then callee send ServerError back.
  • Callee serialize result of the function to bencoded bytestring.
  • Callee encode result to bencoded bytestring and send it back to the caller.
  • Caller check if return values names match with the signature it called in the first step.
  • Caller extracts results and finally return results of the procedure call as ordinary haskell values.

If every other error occurred then caller get the GenericError. All errors returned by callee are throwed as ordinary haskell exceptions at caller side. Also note that both caller and callee use plain UDP, so KRPC is unreliable.

For async query use async package.

For protocol details see Network.KRPC.Message module.

Synopsis

Methods

data Method param result Source

Method datatype used to describe method name, parameters and return values of procedure. Client use a method to invoke, server implements the method to make the actual work.

We use the following fantom types to ensure type-safiety:

  • param: Type of method parameters.
  • result: Type of return value of the method.

Instances

Eq (Method param result) 
Ord (Method param result) 
(Typeable a, Typeable b) => Show (Method a b)

Example:

show (Method "concat" :: [Int] Int) == "concat :: [Int] -> Int"
IsString (Method param result) 
BEncode (Method param result) 

class (BEncode req, BEncode resp) => KRPC req resp | req -> resp whereSource

In order to perform or handle KRPC query you need to provide corresponding KRPC class.

Example:

   data Ping = Ping Text deriving BEncode
   data Pong = Pong Text deriving BEncode

instance KRPC Ping Pong where
     method = "ping"

Methods

method :: Method req respSource

Method name. Default implementation uses lowercased req datatype name.

RPC

type Handler h = (MethodName, HandlerBody h)Source

Handler is a function which will be invoked then some remote node querying this node.

handler :: forall h a b. (KRPC a b, Monad h) => (SockAddr -> a -> h b) -> Handler hSource

Make handler from handler function. Any thrown exception will be supressed and send over the wire back to the querying node.

query :: forall h m a b. (MonadKRPC h m, KRPC a b) => SockAddr -> a -> m bSource

Enqueue query to the given node.

This function will throw exception if quered node respond with error message or timeout expires.

Manager

class (MonadBaseControl IO m, MonadIO m) => MonadKRPC h m | m -> h whereSource

A monad which can perform or handle queries.

Methods

getManager :: m (Manager h)Source

Ask for manager.

liftHandler :: h a -> m aSource

Can be used to add logging for instance.

Instances

data Manager h Source

Keep track pending queries made by this node and handle queries made by remote nodes.

Instances

newManagerSource

Arguments

:: SockAddr

address to listen on;

-> [Handler h]

handlers to run on incoming queries.

-> IO (Manager h)

new manager.

Bind socket to the specified address. To enable query handling run listen.

closeManager :: Manager m -> IO ()Source

Unblock all pending calls and close socket.

withManager :: SockAddr -> [Handler h] -> (Manager h -> IO a) -> IO aSource

Normally you should use Control.Monad.Trans.Resource.allocate function.

listen :: MonadKRPC h m => m ()Source

Should be run before any query, otherwise they will never succeed.

Exceptions

data KError Source

Errors are sent when a query cannot be fulfilled. Error message can be send only from server to client but not in the opposite direction.

Constructors

KError 

Fields

errorCode :: !ErrorCode

the type of error;

errorMessage :: !ByteString

human-readable text message;

errorId :: !TransactionId

match to the corresponding queryId.

Instances

Eq KError 
Ord KError 
Read KError 
Show KError 
Typeable KError 
Exception KError 
BEncode KError

Errors, or KRPC message dictionaries with a "y" value of "e", contain one additional key "e". The value of "e" is a list. The first element is an integer representing the error code. The second element is a string containing the error message.

Example Error Packet:

 { "t": "aa", "y":"e", "e":[201, "A Generic Error Ocurred"]}

or bencoded:

 d1:eli201e23:A Generic Error Ocurrede1:t2:aa1:y1:ee

data ErrorCode Source

Types of RPC errors.

Constructors

GenericError

Some error doesn't fit in any other category.

ServerError

Occur when server fail to process procedure call.

ProtocolError

Malformed packet, invalid arguments or bad token.

MethodUnknown

Occur when client trying to call method server don't know.

Re-export