hsx-0.4: 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, nibro@cs.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

unXMLGenT :: XMLGenT m a -> m aSource

un-lift.

class Monad m => XMLGenerator m whereSource

Generate XML values in some XMLGenerator monad.

Associated Types

type XML m Source

type Child m Source

type 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

class EmbedAsChild a 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 :: a -> cSource

class EmbedAsAttr a at whereSource

Similarly embed values as attributes of an XML element.

Methods

asAttr :: a -> atSource

data Attr n a Source

Constructors

n := a 

Instances

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

class XMLGenerator m => SetAttr m t whereSource

Set attributes on XML elements

Methods

setAttr :: t -> XMLGenT m (Attribute m) -> XMLGenT m (XML m)Source

setAll :: t -> XMLGenT m [Attribute m] -> XMLGenT m (XML m)Source

set :: (SetAttr m t, EmbedAsAttr a (XMLGenT m (Attribute m))) => t -> a -> XMLGenT m (XML m)Source

(<@) :: (SetAttr m t, EmbedAsAttr a (XMLGenT m (Attribute m))) => t -> a -> XMLGenT m (XML m)Source

(<<@) :: (SetAttr m t, EmbedAsAttr a (XMLGenT m (Attribute m))) => t -> [a] -> XMLGenT m (XML m)Source

class XMLGenerator m => AppendChild m t whereSource

Methods

appChild :: t -> XMLGenT m (Child m) -> XMLGenT m (XML m)Source

appAll :: t -> XMLGenT m [Child m] -> XMLGenT m (XML m)Source

app :: (AppendChild m t, EmbedAsChild c (XMLGenT m [Child m])) => t -> c -> XMLGenT m (XML m)Source

(<:) :: (AppendChild m t, EmbedAsChild c (XMLGenT m [Child m])) => t -> c -> XMLGenT m (XML m)Source

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