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

Safe HaskellNone
LanguageHaskell98

Text.XML.Writer

Contents

Description

Overcome XML insanity, node by node.

{-# LANGUAGE OverloadedStrings #-}

let doc = document "root" $ do
    element "hello" $ content "world"
    element "hierarchy" $ do
        element "simple" True
        element "as" ("it should be" :: Text)
        toXML $ Just . T.pack $ "like this"
    comment "that's it!"

Synopsis

Documents

document Source #

Arguments

:: Name

Root node name

-> XML

Contents

-> Document 

Create a simple Document starting with a root element.

soap :: (ToXML h, ToXML b) => h -> b -> Document Source #

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 -> XML Source #

Insert one node.

instruction :: Text -> Text -> XML Source #

Insert an Instruction node.

comment :: Text -> XML Source #

Insert a text comment node.

element :: ToXML a => Name -> a -> XML Source #

Insert an Element node constructed with name and children.

elementMaybe :: ToXML a => Name -> Maybe a -> XML Source #

Insert an Element node converted from Maybe value or do nothing.

elementA :: ToXML a => Name -> [(Name, Text)] -> a -> XML Source #

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

content :: Text -> XML Source #

Insert text content node.

empty :: XML Source #

Do nothing.

many Source #

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 -> Name Source #

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 where Source #

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

Minimal complete definition

toXML

Methods

toXML :: a -> XML Source #

Instances

ToXML Bool Source #

XML schema uses lower case.

Methods

toXML :: Bool -> XML Source #

ToXML Char Source # 

Methods

toXML :: Char -> XML Source #

ToXML Double Source # 

Methods

toXML :: Double -> XML Source #

ToXML Float Source # 

Methods

toXML :: Float -> XML Source #

ToXML Int Source # 

Methods

toXML :: Int -> XML Source #

ToXML Integer Source # 

Methods

toXML :: Integer -> XML Source #

ToXML () Source #

Do nothing.

Methods

toXML :: () -> XML Source #

ToXML Text Source #

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

Methods

toXML :: Text -> XML Source #

ToXML XML Source #

Insert already prepared nodes.

Methods

toXML :: XML -> XML Source #

ToXML a => ToXML (Maybe a) Source #

Insert node if available. Otherwise do nothing.

Methods

toXML :: Maybe a -> XML Source #

Orphan instances