Portability | portable |
---|---|
Stability | experimental |
Maintainer | pxqr.sta@gmail.com |
Safe Haskell | None |
This module provides straightforward implementation of KRPC
protocol. In many situations KRPC
should be prefered
since it gives more safe, convenient and high level api.
See http://www.bittorrent.org/beps/bep_0005.html#krpc-protocol
- data KError
- = GenericError { }
- | ServerError { }
- | ProtocolError { }
- | MethodUnknown { }
- type ErrorCode = Int
- errorCode :: KError -> ErrorCode
- mkKError :: ErrorCode -> ByteString -> KError
- data KQuery
- type MethodName = ByteString
- type ParamName = ByteString
- kquery :: MethodName -> [(ParamName, BEncode)] -> KQuery
- data KResponse
- type ValName = ByteString
- kresponse :: [(ValName, BEncode)] -> KResponse
- sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO ()
- recvResponse :: KRemote -> IO (Either KError KResponse)
- type KRemote = Socket
- type KRemoteAddr = (HostAddress, PortNumber)
- withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m a
- remoteServer :: (MonadBaseControl IO remote, MonadIO remote) => PortNumber -> (KRemoteAddr -> KQuery -> remote (Either KError KResponse)) -> remote ()
- encode :: BEncode -> ByteString
- encoded :: BEncodable a => a -> ByteString
- decode :: ByteString -> Result BEncode
- decoded :: BEncodable a => ByteString -> Result a
- toBEncode :: BEncodable a => a -> BEncode
- fromBEncode :: BEncodable a => BEncode -> Result a
Error
Errors used to signal that some error occurred while processing a procedure call. Error may be send only from server to client but not in the opposite direction.
Errors are encoded as bencoded dictionary:
{ "y" : "e", "e" : [<error_code>, <human_readable_error_reason>] }
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. |
mkKError :: ErrorCode -> ByteString -> KErrorSource
Query
Query used to signal that caller want to make procedure call to callee and pass arguments in. Therefore query may be only sent from client to server but not in the opposite direction.
Queries are encoded as bencoded dictionary:
{ "y" : "q", "q" : "<method_name>", "a" : [<arg1>, <arg2>, ...] }
type MethodName = ByteStringSource
type ParamName = ByteStringSource
Response
KResponse used to signal that callee successufully process a procedure call and to return values from procedure. KResponse should not be sent if error occurred during RPC. Thus KResponse may be only sent from server to client.
Responses are encoded as bencoded dictionary:
{ "y" : "r", "r" : [<val1>, <val2>, ...] }
type ValName = ByteStringSource
sendMessage :: BEncodable msg => msg -> KRemoteAddr -> KRemote -> IO ()Source
Remote
type KRemoteAddr = (HostAddress, PortNumber)Source
withRemote :: (MonadBaseControl IO m, MonadIO m) => (KRemote -> m a) -> m aSource
:: (MonadBaseControl IO remote, MonadIO remote) | |
=> PortNumber | Port number to listen. |
-> (KRemoteAddr -> KQuery -> remote (Either KError KResponse)) | Handler. |
-> remote () |
Run server using a given port. Method invocation should be done manually.
Re-exports
encode :: BEncode -> ByteString
Convert bencoded value to raw bytestring according to the specification.
encoded :: BEncodable a => a -> ByteString
The same as encode
but takes any bencodable value.
decode :: ByteString -> Result BEncode
Try to convert raw bytestring to bencoded value according to specification.
decoded :: BEncodable a => ByteString -> Result a
The same as decode
but returns any bencodable value.
toBEncode :: BEncodable a => a -> BEncode
See an example of implementation here Assoc
fromBEncode :: BEncodable a => BEncode -> Result a
See an example of implementation here reqKey
.