haxr-3000.11.4: XML-RPC client and server library.

Copyright(c) Bjorn Bringert 2003
LicenseBSD-style
Maintainerbjorn@bringert.net
Stabilityexperimental
Portabilitynon-portable (requires extensions and non-portable libraries)
Safe HaskellNone
LanguageHaskell2010

Network.XmlRpc.Internals

Contents

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 Network.XmlRpc.Client and server applications should use Network.XmlRpc.Server.

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

Synopsis

Method calls and repsonses

data MethodCall Source #

An XML-RPC method call. Consists of a method name and a list of parameters.

Constructors

MethodCall String [Value] 
Instances
Eq MethodCall Source # 
Instance details

Defined in Network.XmlRpc.Internals

Show MethodCall Source # 
Instance details

Defined in Network.XmlRpc.Internals

data MethodResponse Source #

An XML-RPC response.

Constructors

Return Value

A method response returning a value

Fault Int String

A fault response

XML-RPC types

data Value Source #

An XML-RPC value.

Constructors

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

ValueNil

nil

Instances
Eq Value Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Show Value Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

XmlRpcType Value Source #

Exists to allow explicit type conversions.

Instance details

Defined in Network.XmlRpc.Internals

data Type Source #

An XML-RPC value. Use for error messages and introspection.

Instances
Eq Type Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Read Type Source # 
Instance details

Defined in Network.XmlRpc.Internals

Show Type Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

class XmlRpcType a where Source #

A class for mapping Haskell types to XML-RPC types.

Methods

toValue :: a -> Value Source #

Convert from this type to a Value

fromValue :: MonadFail m => Value -> Err m a Source #

Convert from a Value to this type. May fail if if there is a type error.

getType :: a -> Type Source #

Instances
XmlRpcType Bool Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType Double Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType Int Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType () Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: () -> Value Source #

fromValue :: MonadFail m => Value -> Err m () Source #

getType :: () -> Type Source #

XmlRpcType ByteString Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType Text Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType String Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType CalendarTime Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType LocalTime Source # 
Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType Value Source #

Exists to allow explicit type conversions.

Instance details

Defined in Network.XmlRpc.Internals

XmlRpcType a => XmlRpcType [(String, a)] Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: [(String, a)] -> Value Source #

fromValue :: MonadFail m => Value -> Err m [(String, a)] Source #

getType :: [(String, a)] -> Type Source #

XmlRpcType a => XmlRpcType [a] Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: [a] -> Value Source #

fromValue :: MonadFail m => Value -> Err m [a] Source #

getType :: [a] -> Type Source #

(XmlRpcType a, XmlRpcType b) => XmlRpcType (a, b) Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: (a, b) -> Value Source #

fromValue :: MonadFail m => Value -> Err m (a, b) Source #

getType :: (a, b) -> Type Source #

(XmlRpcType a, XmlRpcType b, XmlRpcType c) => XmlRpcType (a, b, c) Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: (a, b, c) -> Value Source #

fromValue :: MonadFail m => Value -> Err m (a, b, c) Source #

getType :: (a, b, c) -> Type Source #

(XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d) => XmlRpcType (a, b, c, d) Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: (a, b, c, d) -> Value Source #

fromValue :: MonadFail m => Value -> Err m (a, b, c, d) Source #

getType :: (a, b, c, d) -> Type Source #

(XmlRpcType a, XmlRpcType b, XmlRpcType c, XmlRpcType d, XmlRpcType e) => XmlRpcType (a, b, c, d, e) Source # 
Instance details

Defined in Network.XmlRpc.Internals

Methods

toValue :: (a, b, c, d, e) -> Value Source #

fromValue :: MonadFail m => Value -> Err m (a, b, c, d, e) Source #

getType :: (a, b, c, d, e) -> Type Source #

Converting from XML

parseResponse :: (Show e, MonadError e m, MonadFail m) => String -> Err m MethodResponse Source #

Parses a method response from XML.

parseCall :: (Show e, MonadError e m, MonadFail m) => String -> Err m MethodCall Source #

Parses a method call from XML.

getField Source #

Arguments

:: (MonadFail m, XmlRpcType a) 
=> String

Field name

-> [(String, Value)]

Struct

-> Err m a 

Get a field value from a (possibly heterogeneous) struct.

getFieldMaybe Source #

Arguments

:: (MonadFail m, XmlRpcType a) 
=> String

Field name

-> [(String, Value)]

Struct

-> Err m (Maybe a) 

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

Error monad

type Err m a = ExceptT String m a Source #

maybeToM Source #

Arguments

:: MonadFail m 
=> String

Error message to fail with for Nothing

-> Maybe a

The HType value.

-> m a

The resulting value in the monad.

Convert a HType value to a value in any monad

handleError :: MonadFail m => (String -> m a) -> Err m a -> m a Source #

Handle errors from the error monad.

ioErrorToErr :: IO a -> Err IO a Source #

Catch IO errors in the error monad.