Copyright | (c) Bjorn Bringert 2003 |
---|---|
License | BSD-style |
Maintainer | bjorn@bringert.net |
Stability | experimental |
Portability | non-portable (requires extensions and non-portable libraries) |
Safe Haskell | None |
Language | Haskell2010 |
This module contains the core functionality of the XML-RPC library. Most applications should not need to use this module. Client applications should use Network.XmlRpc.Client and server applications should use Network.XmlRpc.Server.
The XML-RPC specifcation is available at http://www.xmlrpc.com/spec.
- data MethodCall = MethodCall String [Value]
- data MethodResponse
- data Value
- data Type
- class XmlRpcType a where
- parseResponse :: (Show e, MonadError e m) => String -> Err m MethodResponse
- parseCall :: (Show e, MonadError e 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 -> ByteString
- renderResponse :: MethodResponse -> ByteString
- toXRValue :: Value -> Value
- fromXRValue :: Monad m => Value -> Err m Value
- toXRMethodCall :: MethodCall -> MethodCall
- fromXRMethodCall :: Monad m => MethodCall -> Err m MethodCall
- toXRMethodResponse :: MethodResponse -> MethodResponse
- fromXRMethodResponse :: Monad m => MethodResponse -> Err m MethodResponse
- toXRParams :: [Value] -> Params
- fromXRParams :: Monad m => Params -> Err m [Value]
- toXRMember :: (String, Value) -> Member
- fromXRMember :: Monad m => Member -> Err m (String, Value)
- type Err m a = ExceptT 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 Source #
An XML-RPC method call. Consists of a method name and a list of parameters.
data MethodResponse Source #
An XML-RPC response.
XML-RPC types
An XML-RPC value.
ValueInt Int | int, i4, or i8 |
ValueBool Bool | bool |
ValueString String | string |
ValueUnwrapped String | no inner element |
ValueDouble Double | double |
ValueDateTime LocalTime | dateTime.iso8601 |
ValueBase64 ByteString | base 64. NOTE that you should provide the raw data; the haxr library takes care of doing the base-64 encoding. |
ValueStruct [(String, Value)] | struct |
ValueArray [Value] | array |
An XML-RPC value. Use for error messages and introspection.
class XmlRpcType a where Source #
A class for mapping Haskell types to XML-RPC types.
toValue :: a -> Value Source #
Convert from this type to a Value
fromValue :: Monad m => Value -> Err m a Source #
Convert from a Value
to this type. May fail if
if there is a type error.
XmlRpcType Bool Source # | |
XmlRpcType Double Source # | |
XmlRpcType Int Source # | |
XmlRpcType ByteString Source # | |
XmlRpcType String Source # | |
XmlRpcType Text Source # | |
XmlRpcType CalendarTime Source # | |
XmlRpcType LocalTime Source # | |
XmlRpcType Value Source # | Exists to allow explicit type conversions. |
XmlRpcType a => XmlRpcType [(String, a)] Source # | |
XmlRpcType a => XmlRpcType [a] Source # | |
(XmlRpcType a, XmlRpcType b) => XmlRpcType (a, b) Source # | |
(XmlRpcType a, XmlRpcType b, XmlRpcType c) => XmlRpcType (a, b, c) Source # | |
(XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d) => XmlRpcType (a, b, c, d) Source # | |
(XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d, XmlRpcType e) => XmlRpcType (a, b, c, d, e) Source # | |
Converting from XML
parseResponse :: (Show e, MonadError e m) => String -> Err m MethodResponse Source #
Parses a method response from XML.
parseCall :: (Show e, MonadError e m) => String -> Err m MethodCall Source #
Parses a method call from XML.
Get a field value from a (possibly heterogeneous) struct.
Get a field value from a (possibly heterogeneous) struct.
Converting to XML
renderCall :: MethodCall -> ByteString Source #
Makes an XML-representation of a method call. FIXME: pretty prints ugly XML
renderResponse :: MethodResponse -> ByteString Source #
Makes an XML-representation of a method response. FIXME: pretty prints ugly XML
Converting to and from DTD types
fromXRMethodCall :: Monad m => MethodCall -> Err m MethodCall Source #
fromXRMethodResponse :: Monad m => MethodResponse -> Err m MethodResponse Source #
toXRParams :: [Value] -> Params Source #
Error monad
:: Monad m | |
=> String | Error message to fail with for |
-> Maybe a | The |
-> m a | The resulting value in the monad. |
Convert a Maybe
value to a value in any monad