haxr-3000.0.0: XML-RPC client and server library.ContentsIndex
Network.XmlRpc.Internals
Portabilitynon-portable (requires extensions and non-portable libraries)
Stabilityexperimental
Maintainerbjorn@bringert.net
Contents
Method calls and repsonses
XML-RPC types
Converting from XML
Converting to XML
Error monad
Description

This module contains the core functionality of the XML-RPC library. Most applications should not need to use this module. Client applications should use XmlRpcClient and server applications should use XmlRpcServer.

The XML-RPC specifcation is available at http://www.xmlrpc.com/spec.

Synopsis
data MethodCall = MethodCall String [Value]
data MethodResponse
= Return Value
| Fault Int String
data Value
= ValueInt Int
| ValueBool Bool
| ValueString String
| ValueDouble Double
| ValueDateTime CalendarTime
| ValueBase64 String
| ValueStruct [(String, Value)]
| ValueArray [Value]
data Type
= TInt
| TBool
| TString
| TDouble
| TDateTime
| TBase64
| TStruct
| TArray
| TUnknown
class XmlRpcType a where
toValue :: a -> Value
fromValue :: Monad m => Value -> Err m a
getType :: a -> Type
parseResponse :: Monad m => String -> Err m MethodResponse
parseCall :: Monad m => String -> Err m MethodCall
getField :: (Monad m, XmlRpcType a) => String -> [(String, Value)] -> Err m a
getFieldMaybe :: (Monad m, XmlRpcType a) => String -> [(String, Value)] -> Err m (Maybe a)
renderCall :: MethodCall -> String
renderResponse :: MethodResponse -> String
type Err m a = ErrorT String m a
maybeToM :: Monad m => String -> Maybe a -> m a
handleError :: Monad m => (String -> m a) -> Err m a -> m a
ioErrorToErr :: IO a -> Err IO a
Method calls and repsonses
data MethodCall
An XML-RPC method call. Consists of a method name and a list of parameters.
Constructors
MethodCall String [Value]
show/hide Instances
data MethodResponse
An XML-RPC response.
Constructors
Return ValueA method response returning a value
Fault Int StringA fault response
show/hide Instances
XML-RPC types
data Value
An XML-RPC value.
Constructors
ValueInt Intint or i4
ValueBool Boolbool
ValueString Stringstring
ValueDouble Doubledouble
ValueDateTime CalendarTimedateTime.iso8601
ValueBase64 Stringbase 64
ValueStruct [(String, Value)]struct
ValueArray [Value]array
show/hide Instances
data Type
An XML-RPC value. Use for error messages and introspection.
Constructors
TInt
TBool
TString
TDouble
TDateTime
TBase64
TStruct
TArray
TUnknown
show/hide Instances
class XmlRpcType a where
A class for mapping Haskell types to XML-RPC types.
Methods
toValue :: a -> Value
Convert from this type to a Value
fromValue :: Monad m => Value -> Err m a
Convert from a Value to this type. May fail if if there is a type error.
getType :: a -> Type
show/hide Instances
Converting from XML
parseResponse :: Monad m => String -> Err m MethodResponse
Parses a method response from XML.
parseCall :: Monad m => String -> Err m MethodCall
Parses a method call from XML.
getField
:: (Monad m, XmlRpcType a)
=> StringField name
-> [(String, Value)]Struct
-> Err m a
Get a field value from a (possibly heterogeneous) struct.
getFieldMaybe
:: (Monad m, XmlRpcType a)
=> StringField name
-> [(String, Value)]Struct
-> Err m (Maybe a)
Get a field value from a (possibly heterogeneous) struct.
Converting to XML
renderCall :: MethodCall -> String
Makes an XML-representation of a method call. FIXME: pretty prints ugly XML
renderResponse :: MethodResponse -> String
Makes an XML-representation of a method response. FIXME: pretty prints ugly XML
Error monad
type Err m a = ErrorT String m a
maybeToM
:: Monad m
=> StringError message to fail with for Nothing
-> Maybe aThe Maybe value.
-> m aThe resulting value in the monad.
Convert a Maybe value to a value in any monad
handleError :: Monad m => (String -> m a) -> Err m a -> m a
Handle errors from the error monad.
ioErrorToErr :: IO a -> Err IO a
Catch IO errors in the error monad.
Produced by Haddock version 0.8