hsx-0.6.2: HSX (Haskell Source with XML) allows literal XML syntax to be used in Haskell source code.

Portabilityrequires newtype deriving and MPTCs with fundeps
Stabilityexperimental
MaintainerNiklas Broberg, niklas.broberg@chalmers.se

HSX.XMLGenerator

Description

The class and monad transformer that forms the basis of the literal XML syntax translation. Literal tags will be translated into functions of the GenerateXML class, and any instantiating monads with associated XML types can benefit from that syntax.

Synopsis

Documentation

newtype XMLGenT m a Source

The monad transformer that allows a monad to generate XML values.

Constructors

XMLGenT (m a) 

Instances

MonadTrans XMLGenT 
(AppendChild m x, TypeCastM m1 m) => AppendChild m (XMLGenT m1 x) 
(TypeCastM m1 m, SetAttr m x) => SetAttr m (XMLGenT m1 x) 
(XMLGen m, EmbedAsAttr m a) => EmbedAsAttr m (XMLGenT m a) 
(EmbedAsChild m c, TypeCastM m1 m) => EmbedAsChild m (XMLGenT m1 c) 
Monad m => Monad (XMLGenT m) 
Functor m => Functor (XMLGenT m) 
MonadPlus m => MonadPlus (XMLGenT m) 
MonadIO m => MonadIO (XMLGenT m) 

unXMLGenT :: XMLGenT m a -> m aSource

un-lift.

class Monad m => XMLGen m whereSource

Generate XML values in some XMLGenerator monad.

Associated Types

type XML m Source

data Child m Source

data Attribute m Source

Methods

genElement :: Name -> [XMLGenT m [Attribute m]] -> [XMLGenT m [Child m]] -> XMLGenT m (XML m)Source

genEElement :: Name -> [XMLGenT m [Attribute m]] -> XMLGenT m (XML m)Source

xmlToChild :: XML m -> Child mSource

type GenXML m = XMLGenT m (XML m)Source

Type synonyms to avoid writing out the XMLnGenT all the time

class XMLGen m => EmbedAsChild m c whereSource

Embed values as child nodes of an XML element. The parent type will be clear from the context so it is not mentioned.

Methods

asChild :: c -> GenChildList mSource

Instances

(XML m ~ x, XMLGen m) => EmbedAsChild m x 
XMLGen m => EmbedAsChild m (Child m) 
EmbedAsChild m c => EmbedAsChild m [c] 
(EmbedAsChild m c, TypeCastM m1 m) => EmbedAsChild m (XMLGenT m1 c) 

class XMLGen m => EmbedAsAttr m a whereSource

Similarly embed values as attributes of an XML element.

Instances

EmbedAsAttr m a => EmbedAsAttr m [a] 
XMLGen m => EmbedAsAttr m (Attribute m) 
(XMLGen m, EmbedAsAttr m a) => EmbedAsAttr m (XMLGenT m a) 

data Attr n a Source

Constructors

n := a 

Instances

(Show n, Show a) => Show (Attr n a) 

class XMLGen m => SetAttr m elem whereSource

Set attributes on XML elements

Methods

setAttr :: elem -> GenAttribute m -> GenXML mSource

setAll :: elem -> GenAttributeList m -> GenXML mSource

Instances

(TypeCastM m1 m, SetAttr m x) => SetAttr m (XMLGenT m1 x) 

set :: (SetAttr m elem, EmbedAsAttr m attr) => elem -> attr -> GenXML mSource

(<@) :: (SetAttr m elem, EmbedAsAttr m attr) => elem -> attr -> GenXML mSource

(<<@) :: (SetAttr m elem, EmbedAsAttr m a) => elem -> [a] -> GenXML mSource

class XMLGen m => AppendChild m elem whereSource

Methods

appChild :: elem -> GenChild m -> GenXML mSource

appAll :: elem -> GenChildList m -> GenXML mSource

Instances

(AppendChild m x, TypeCastM m1 m) => AppendChild m (XMLGenT m1 x) 

app :: (AppendChild m elem, EmbedAsChild m c) => elem -> c -> GenXML mSource

(<:) :: (AppendChild m elem, EmbedAsChild m c) => elem -> c -> GenXML mSource

(<<:) :: (AppendChild m elem, EmbedAsChild m c) => elem -> [c] -> GenXML mSource

class Show n => IsName n whereSource

Names can be simple or qualified with a domain. We want to conveniently use both simple strings or pairs wherever a Name is expected.

Methods

toName :: n -> NameSource

Instances

IsName String

Strings can represent names, meaning a simple name with no domain.

IsName Name

Names can represent names, of course.

IsName (String, String)

Pairs of strings can represent names, meaning a name qualified with a domain.

class TypeCast a b | a -> b, b -> a whereSource

Methods

typeCast :: a -> bSource

Instances

TypeCast' () a b => TypeCast a b 

class TypeCast' t a b | t a -> b, t b -> a whereSource

Methods

typeCast' :: t -> a -> bSource

Instances

TypeCast'' t a b => TypeCast' t a b 

class TypeCast'' t a b | t a -> b, t b -> a whereSource

Methods

typeCast'' :: t -> a -> bSource

Instances

TypeCast'' () a a 

class TypeCastM ma mb | ma -> mb, mb -> ma whereSource

Methods

typeCastM :: ma x -> mb xSource

Instances

TypeCastM' () ma mb => TypeCastM ma mb 

class TypeCastM' t ma mb | t ma -> mb, t mb -> ma whereSource

Methods

typeCastM' :: t -> ma x -> mb xSource

Instances

TypeCastM'' t ma mb => TypeCastM' t ma mb 

class TypeCastM'' t ma mb | t ma -> mb, t mb -> ma whereSource

Methods

typeCastM'' :: t -> ma x -> mb xSource

Instances

TypeCastM'' () ma ma