| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Text.XML.HaXml.XmlContent.Parser
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. However, some instances for basic types like lists will depend on which direction you are using. See Text.XML.HaXml.XmlContent and Text.XML.HaXml.XmlContent.Haskell.
Synopsis
- data Document i = Document Prolog (SymTab EntityDef) (Element i) [Misc]
- data Element i = Elem QName [Attribute] [Content i]
- data ElemTag = ElemTag QName [Attribute]
- data Content i
- type Attribute = (QName, AttValue)
- data AttValue = AttValue [Either String Reference]
- data Prolog = Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
- data Reference
- class HTypeable a => XmlContent a where- parseContents :: XMLParser a
- toContents :: a -> [Content ()]
- xToChar :: a -> Char
- xFromChar :: Char -> a
 
- class XmlAttributes a where
- class XmlAttrType a where- fromAttrToTyp :: String -> Attribute -> Maybe a
- toAttrFrTyp :: String -> a -> Maybe Attribute
 
- 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 :: [Maybe a] -> [a]
- 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
The symbol table stored in a document holds all its general entity reference definitions.
Constructors
| CElem (Element i) i | |
| CString Bool CharData i | bool is whether whitespace is significant | 
| CRef Reference i | |
| CMisc Misc i | 
Constructors
| Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] | 
The enabling classes, that define parsing/unparsing between Haskell
class HTypeable a => XmlContent a where Source #
The XmlContent class promises that an XML Content element can be
   converted to and from a Haskell value.
Minimal complete definition
Methods
parseContents :: XMLParser a Source #
Convert from XML to Haskell
toContents :: a -> [Content ()] Source #
Convert from Haskell to XML
Dummy functions (for most types): used only in the Char instance for coercing lists of Char into String.
Instances
class XmlAttributes a where Source #
The XmlAttributes class promises that a list of XML tag attributes
   can be converted to and from a Haskell value.
class XmlAttrType a where Source #
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 Source #
toAttrFrTyp :: String -> a -> Maybe Attribute Source #
Auxiliaries for writing parsers in the XmlContent class
type XMLParser a = Parser (Content Posn) a Source #
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) Source #
The most primitive combinator for XMLParser - get one content item.
posnElement :: [String] -> XMLParser (Posn, Element Posn) Source #
A specialisation of posnElementWith (==).
element :: [String] -> XMLParser (Element Posn) Source #
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 Source #
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.
attributes :: XmlAttributes a => Element Posn -> XMLParser a Source #
Do some parsing of the attributes of the given element
posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn) Source #
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) Source #
Like element, only permits a more flexible match against the tagname.
inElementWith :: (String -> String -> Bool) -> String -> XMLParser a -> XMLParser a Source #
A combination of elementWith + interior.
choice :: XmlContent a => (a -> b) -> XMLParser b -> XMLParser b Source #
'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 Source #
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 () Source #
Generate an element with no attributes, named for its HType.
mkElemC :: String -> [Content ()] -> Content () Source #
Generate an element with no attributes, named directly.
toCData :: String -> [Content ()] Source #
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 Source #
defaultToAttr :: (String -> a -> Maybe Attribute) -> String -> Defaultable a -> Maybe Attribute Source #
defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a Source #
fromAttrToStr :: String -> Attribute -> Maybe String Source #
toAttrFrStr :: String -> String -> Maybe Attribute Source #
data Defaultable a Source #
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 | 
Instances
| Eq a => Eq (Defaultable a) Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser | |
| Show a => Show (Defaultable a) Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser Methods showsPrec :: Int -> Defaultable a -> ShowS show :: Defaultable a -> String showList :: [Defaultable a] -> ShowS | |
Explicit representation of Haskell datatype information
module Text.XML.HaXml.TypeMapping
Types useful for some content models
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] | 
data ANYContent Source #
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] | 
Instances
| Eq ANYContent Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser | |
| Show ANYContent Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser Methods showsPrec :: Int -> ANYContent -> ShowS show :: ANYContent -> String showList :: [ANYContent] -> ShowS | |
| HTypeable ANYContent Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser Methods toHType :: ANYContent -> HType Source # | |
| XmlContent ANYContent Source # | |
| Defined in Text.XML.HaXml.XmlContent.Parser Methods parseContents :: XMLParser ANYContent Source # toContents :: ANYContent -> [Content ()] Source # xToChar :: ANYContent -> Char Source # xFromChar :: Char -> ANYContent Source # | |