xml-conduit-writer-0.1.0.0: Warm and fuzzy creation of XML documents.

Safe HaskellNone

Text.XML.Writer

Contents

Description

Overcome XML insanity, node by node.

 {-# LANGUAGE OverloadedStrings #-}

 let doc = document "root" $ do
     element "hello" "world"
     element "hierarchy" $ do
         element "simple" $ toXML True
         element "as" "it should be"
         toXML $ Just "like this"
     comment "that's it!"

Synopsis

Documents

documentSource

Arguments

:: Name

Root node name

-> XML

Contents

-> Document 

Create a simple Document starting with a root element.

soap :: (ToXML h, ToXML b) => h -> b -> DocumentSource

Generate a SOAPv1.1 document.

Empty header will be ignored. Envelope uses a soapenv prefix. Works great with ToXML class.

 data BigData = BigData { webScale :: Bool }
 instance ToXML BigData where
     toXML (BigData ws) = element ("v" !: "{vendor:uri}bigData") $ toXML ws
 let doc = soap () (BigData True)

pprint :: Document -> IO ()Source

Render document using xml-conduit's pretty-printer.

Elements

type XML = Writer (DList Node) ()Source

Node container to be rendered as children nodes.

Node creation

node :: Node -> XMLSource

Insert one node

instruction :: Text -> Text -> XMLSource

Insert an Instruction node.

comment :: Text -> XMLSource

Insert a text comment node.

element :: Name -> XML -> XMLSource

Insert an Element node constructed with name and children.

elementA :: Name -> [(Name, Text)] -> XML -> XMLSource

Insert an Element node constructed with name, attributes and children.

content :: Text -> XMLSource

Insert text content node.

empty :: XMLSource

Do nothing.

manySource

Arguments

:: ToXML a 
=> Name

Container element name.

-> [a]

Items to convert.

-> XML 

Mass-convert to nodes.

 let array = element "container" $ many "wrapper" [1..3]

Which gives:

 <container>
     <wrapper>1</wrapper>
     <wrapper>2</wrapper>
     <wrapper>3</wrapper>
 </container>

Use `mapM_ toXML xs` to convert a list without wrapping each item in separate element.

 let mess = element "container" $ mapM_ toXML ["chunky", "chunk"]

Content nodes tend to glue together:

 <container>chunkychunk</container>

Element helpers

render :: XML -> [Node]Source

Convert collected nodes to a list of child nodes.

(!:) :: Text -> Name -> NameSource

Attach a prefix to a Name.

Because simply placing a colon in an element name yields Nothing as a prefix and children will revert to en empty namespace.

Converting data

class ToXML a whereSource

Provide instances for this class to use your data as XML nodes.

Methods

toXML :: a -> XMLSource

Instances

ToXML Bool

XML schema uses lower case.

ToXML Char 
ToXML Double 
ToXML Float 
ToXML Int 
ToXML Integer 
ToXML ()

Do nothing.

ToXML Text

Don't use [Char] please, it will scare OverloadedStrings.

ToXML XML

Insert already prepared nodes.

ToXML a => ToXML (Maybe a)

Insert node if available. Otherwise do nothing.