| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.XML.Writer
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!"- document :: Name -> XML -> Document
- soap :: (ToXML h, ToXML b) => h -> b -> Document
- pprint :: Document -> IO ()
- type XML = Writer (DList Node) ()
- node :: Node -> XML
- instruction :: Text -> Text -> XML
- comment :: Text -> XML
- element :: ToXML a => Name -> a -> XML
- elementMaybe :: ToXML a => Name -> Maybe a -> XML
- elementA :: ToXML a => Name -> [(Name, Text)] -> a -> XML
- content :: Text -> XML
- empty :: XML
- many :: ToXML a => Name -> [a] -> XML
- render :: XML -> [Node]
- (!:) :: Text -> Name -> Name
- class ToXML a where
Documents
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)Elements
Node creation
instruction :: Text -> Text -> XML Source #
Insert an Instruction 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.
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
(!:) :: 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
Provide instances for this class to use your data as XML nodes.
Minimal complete definition
Instances
| ToXML Bool Source # | XML schema uses lower case. | 
| ToXML Char Source # | |
| ToXML Double Source # | |
| ToXML Float Source # | |
| ToXML Int Source # | |
| ToXML Integer Source # | |
| ToXML () Source # | Do nothing. | 
| ToXML Text Source # | Don't use [Char] please, it will scare OverloadedStrings. | 
| ToXML XML Source # | Insert already prepared nodes. | 
| ToXML a => ToXML (Maybe a) Source # | Insert node if available. Otherwise do nothing. |