HaXml-1.19.1: Utilities for manipulating XML documentsContentsIndex
Text.XML.HaXml.XmlContent
Contents
Re-export the relevant set of generic XML document type definitions
The enabling classes, that define parsing/unparsing between Haskell
Auxiliaries for writing parsers in the XmlContent class
Auxiliaries for generating in the XmlContent class
Auxiliaries for the attribute-related classes
Whole-document conversion functions
Explicit representation of Haskell datatype information
Types useful for some content models
Description

The class XmlContent is a kind of replacement for Read and Show: it provides conversions between a generic XML tree representation and your own more specialised typeful Haskell data trees.

If you are starting with a set of Haskell datatypes, use DrIFT to derive instances of this class for you: http://repetae.net/john/computer/haskell/DrIFT If you are starting with an XML DTD, use HaXml's tool DtdToHaskell to generate both the Haskell types and the corresponding instances.

This unified class interface replaces two previous (somewhat similar) classes: Haskell2Xml and Xml2Haskell. There was no real reason to have separate classes depending on how you originally defined your datatypes.

Synopsis
data Document i = Document Prolog (SymTab EntityDef) (Element i) [Misc]
data Element i = Elem Name [Attribute] [Content i]
data ElemTag = ElemTag Name [Attribute]
data Content i
= CElem (Element i) i
| CString Bool CharData i
| CRef Reference i
| CMisc Misc i
type Attribute = (Name, AttValue)
data AttValue = AttValue [Either String Reference]
data Prolog = Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
data Reference
= RefEntity EntityRef
| RefChar CharRef
class HTypeable a => XmlContent a where
parseContents :: XMLParser a
toContents :: a -> [Content ()]
xToChar :: a -> Char
xFromChar :: Char -> a
class XmlAttributes a where
fromAttrs :: [Attribute] -> a
toAttrs :: a -> [Attribute]
class XmlAttrType a where
fromAttrToTyp :: String -> Attribute -> Maybe a
toAttrFrTyp :: String -> a -> Maybe Attribute
module Text.ParserCombinators.Poly
type XMLParser a = Parser (Content Posn) a
content :: String -> XMLParser (Content Posn)
posnElement :: [String] -> XMLParser (Posn, Element Posn)
element :: [String] -> XMLParser (Element Posn)
interior :: Element Posn -> XMLParser a -> XMLParser a
inElement :: String -> XMLParser a -> XMLParser a
text :: XMLParser String
attributes :: XmlAttributes a => Element Posn -> XMLParser a
posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn)
elementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Element Posn)
inElementWith :: (String -> String -> Bool) -> String -> XMLParser a -> XMLParser a
choice :: XmlContent a => (a -> b) -> XMLParser b -> XMLParser b
definite :: XmlContent a => XMLParser a -> String -> String -> XMLParser a
mkElem :: XmlContent a => a -> [Content ()] -> Content ()
mkElemC :: String -> [Content ()] -> Content ()
mkAttr :: String -> String -> Attribute
toText :: String -> [Content ()]
toCData :: String -> [Content ()]
maybeToAttr :: (String -> a -> Maybe Attribute) -> String -> Maybe a -> Maybe Attribute
defaultToAttr :: (String -> a -> Maybe Attribute) -> String -> Defaultable a -> Maybe Attribute
definiteA :: (String -> Attribute -> Maybe a) -> String -> String -> [Attribute] -> a
defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a
possibleA :: (String -> Attribute -> Maybe a) -> String -> [Attribute] -> Maybe a
fromAttrToStr :: String -> Attribute -> Maybe String
toAttrFrStr :: String -> String -> Maybe Attribute
data Defaultable a
= Default a
| NonDefault a
str2attr :: String -> AttValue
attr2str :: AttValue -> String
attval :: Read a => Element i -> a
catMaybes
toXml :: XmlContent a => Bool -> a -> Document ()
fromXml :: XmlContent a => Document Posn -> Either String a
readXml :: XmlContent a => String -> Either String a
showXml :: XmlContent a => Bool -> a -> String
fpsShowXml :: XmlContent a => Bool -> a -> ByteString
fReadXml :: XmlContent a => FilePath -> IO a
fWriteXml :: XmlContent a => FilePath -> a -> IO ()
fpsWriteXml :: XmlContent a => FilePath -> a -> IO ()
hGetXml :: XmlContent a => Handle -> IO a
hPutXml :: XmlContent a => Handle -> Bool -> a -> IO ()
fpsHPutXml :: XmlContent a => Handle -> Bool -> a -> IO ()
module Text.XML.HaXml.TypeMapping
data List1 a = NonEmpty [a]
data ANYContent
= forall a . (XmlContent a, Show a) => ANYContent a
| UnConverted [Content Posn]
Re-export the relevant set of generic XML document type definitions
data Document i
The symbol table stored in a document holds all its general entity reference definitions.
Constructors
Document Prolog (SymTab EntityDef) (Element i) [Misc]
show/hide Instances
data Element i
Constructors
Elem Name [Attribute] [Content i]
show/hide Instances
data ElemTag
Constructors
ElemTag Name [Attribute]
show/hide Instances
data Content i
Constructors
CElem (Element i) i
CString Bool CharData ibool is whether whitespace is significant
CRef Reference i
CMisc Misc i
show/hide Instances
type Attribute = (Name, AttValue)
data AttValue
Constructors
AttValue [Either String Reference]
show/hide Instances
data Prolog
Constructors
Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
show/hide Instances
data Reference
Constructors
RefEntity EntityRef
RefChar CharRef
show/hide Instances
The enabling classes, that define parsing/unparsing between Haskell
class HTypeable a => XmlContent a where
The XmlContent class promises that an XML Content element can be converted to and from a Haskell value.
Methods
parseContents :: XMLParser a
Convert from XML to Haskell
toContents :: a -> [Content ()]
Convert from Haskell to XML
xToChar :: a -> Char
Dummy functions (for most types): used only in the Char instance for coercing lists of Char into String.
xFromChar :: Char -> a
show/hide Instances
XmlContent ANYContent
XmlContent Bool
XmlContent Char
XmlContent Double
XmlContent Float
XmlContent Int
XmlContent Integer
XmlContent ()
(XmlContent a, XmlContent b) => XmlContent (a, b)
(XmlContent a, XmlContent b, XmlContent c) => XmlContent (a, b, c)
XmlContent a => XmlContent (List1 a)
XmlContent a => XmlContent (Maybe a)
XmlContent a => XmlContent [a]
(XmlContent a, XmlContent b) => XmlContent (Either a b)
(XmlContent a, XmlContent b) => XmlContent (OneOf2 a b)
(XmlContent a, XmlContent b, XmlContent c) => XmlContent (OneOf3 a b c)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d) => XmlContent (OneOf4 a b c d)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e) => XmlContent (OneOf5 a b c d e)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f) => XmlContent (OneOf6 a b c d e f)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g) => XmlContent (OneOf7 a b c d e f g)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h) => XmlContent (OneOf8 a b c d e f g h)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i) => XmlContent (OneOf9 a b c d e f g h i)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j) => XmlContent (OneOf10 a b c d e f g h i j)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k) => XmlContent (OneOf11 a b c d e f g h i j k)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l) => XmlContent (OneOf12 a b c d e f g h i j k l)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m) => XmlContent (OneOf13 a b c d e f g h i j k l m)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n) => XmlContent (OneOf14 a b c d e f g h i j k l m n)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o) => XmlContent (OneOf15 a b c d e f g h i j k l m n o)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p) => XmlContent (OneOf16 a b c d e f g h i j k l m n o p)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q) => XmlContent (OneOf17 a b c d e f g h i j k l m n o p q)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r) => XmlContent (OneOf18 a b c d e f g h i j k l m n o p q r)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r, XmlContent s) => XmlContent (OneOf19 a b c d e f g h i j k l m n o p q r s)
(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r, XmlContent s, XmlContent t) => XmlContent (OneOf20 a b c d e f g h i j k l m n o p q r s t)
class XmlAttributes a where
The XmlAttributes class promises that a list of XML tag attributes can be converted to and from a Haskell value.
Methods
fromAttrs :: [Attribute] -> a
toAttrs :: a -> [Attribute]
class XmlAttrType a where
The XmlAttrType class promises that an attribute taking an XML enumerated type can be converted to and from a Haskell value.
Methods
fromAttrToTyp :: String -> Attribute -> Maybe a
toAttrFrTyp :: String -> a -> Maybe Attribute
Auxiliaries for writing parsers in the XmlContent class
module Text.ParserCombinators.Poly
type XMLParser a = Parser (Content Posn) a
We need a parsing monad for reading generic XML Content into specific datatypes. This is a specialisation of the Text.ParserCombinators.Poly ones, where the input token type is fixed as XML Content.
content :: String -> XMLParser (Content Posn)
The most primitive combinator for XMLParser - get one content item.
posnElement :: [String] -> XMLParser (Posn, Element Posn)
A specialisation of posnElementWith (==).
element :: [String] -> XMLParser (Element Posn)
Get the next content element, checking that it has one of the required tags. (Skips over comments and whitespace, rejects text and refs.)
interior :: Element Posn -> XMLParser a -> XMLParser a
Run an XMLParser on the contents of the given element (i.e. not on the current monadic content sequence), checking that the contents are exhausted, before returning the calculated value within the current parser context.
inElement :: String -> XMLParser a -> XMLParser a
A combination of element + interior.
text :: XMLParser String
text is a counterpart to element, parsing text content if it exists. Adjacent text and references are coalesced.
attributes :: XmlAttributes a => Element Posn -> XMLParser a
Do some parsing of the attributes of the given element
posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn)
Get the next content element, checking that it has one of the required tags, using the given matching function. (Skips over comments and whitespace, rejects text and refs. Also returns position of element.)
elementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Element Posn)
Like element, only permits a more flexible match against the tagname.
inElementWith :: (String -> String -> Bool) -> String -> XMLParser a -> XMLParser a
A combination of elementWith + interior.
choice :: XmlContent a => (a -> b) -> XMLParser b -> XMLParser b
'choice f p' means if parseContents succeeds, apply f to the result, otherwise use the continuation parser.
definite :: XmlContent a => XMLParser a -> String -> String -> XMLParser a
not sure this is needed now. 'definite p' previously ensured that an element was definitely present. Now I think the monad might take care of that for us.
Auxiliaries for generating in the XmlContent class
mkElem :: XmlContent a => a -> [Content ()] -> Content ()
Generate an element with no attributes, named for its HType.
mkElemC :: String -> [Content ()] -> Content ()
Generate an element with no attributes, named directly.
mkAttr :: String -> String -> Attribute
Generate a single attribute.
toText :: String -> [Content ()]
Turn a simple string into XML text.
toCData :: String -> [Content ()]
Turn a string into an XML CDATA section. (i.e. special characters like & are preserved without interpretation.)
Auxiliaries for the attribute-related classes
maybeToAttr :: (String -> a -> Maybe Attribute) -> String -> Maybe a -> Maybe Attribute
defaultToAttr :: (String -> a -> Maybe Attribute) -> String -> Defaultable a -> Maybe Attribute
definiteA :: (String -> Attribute -> Maybe a) -> String -> String -> [Attribute] -> a
defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a
possibleA :: (String -> Attribute -> Maybe a) -> String -> [Attribute] -> Maybe a
fromAttrToStr :: String -> Attribute -> Maybe String
toAttrFrStr :: String -> String -> Maybe Attribute
data Defaultable a
If an attribute is defaultable, then it either takes the default value (which is omitted from the output), or a non-default value (which obviously must be printed).
Constructors
Default a
NonDefault a
show/hide Instances
str2attr :: String -> AttValue
attr2str :: AttValue -> String
attval :: Read a => Element i -> a
Read a single attribute called value.
catMaybes
Whole-document conversion functions
toXml :: XmlContent a => Bool -> a -> Document ()
Convert a fully-typed XML document to a string (with or without DTD).
fromXml :: XmlContent a => Document Posn -> Either String a
Read a Haskell value from an XML document, ignoring the DTD and using the Haskell result type to determine how to parse it.
readXml :: XmlContent a => String -> Either String a
Read a fully-typed XML document from a string.
showXml :: XmlContent a => Bool -> a -> String
Convert a fully-typed XML document to a string (without DTD).
fpsShowXml :: XmlContent a => Bool -> a -> ByteString
Convert a fully-typed XML document to a ByteString (without DTD).
fReadXml :: XmlContent a => FilePath -> IO a
Read an XML document from a file and convert it to a fully-typed Haskell value.
fWriteXml :: XmlContent a => FilePath -> a -> IO ()
Write a fully-typed Haskell value to the given file as an XML document.
fpsWriteXml :: XmlContent a => FilePath -> a -> IO ()
Write any Haskell value to the given file as an XML document, using the FastPackedString interface (output will not be prettified).
hGetXml :: XmlContent a => Handle -> IO a
Read a fully-typed XML document from a file handle.
hPutXml :: XmlContent a => Handle -> Bool -> a -> IO ()
Write a fully-typed XML document to a file handle.
fpsHPutXml :: XmlContent a => Handle -> Bool -> a -> IO ()
Write a fully-typed XML document to a file handle, using the FastPackedString interface (output will not be prettified).
Explicit representation of Haskell datatype information
module Text.XML.HaXml.TypeMapping
Types useful for some content models
data List1 a
The List1 type represents lists with at least one element. It is required for DTD content models that use + as a modifier.
Constructors
NonEmpty [a]
show/hide Instances
??? a => Eq (List1 a)
HTypeable a => HTypeable (List1 a)
??? a => Show (List1 a)
XmlContent a => XmlContent (List1 a)
data ANYContent

A type corresponding to XML's ANY contentspec. It is either a list of unconverted xml Content or some XmlContent-able value.

Parsing functions (e.g. parseContents) will always produce UnConverted. Note: The Show instance for UnConverted uses verbatim.

Constructors
forall a . (XmlContent a, Show a) => ANYContent a
UnConverted [Content Posn]
show/hide Instances
Produced by Haddock version 0.8