HaXml-1.25.6: Utilities for manipulating XML documents
Safe HaskellSafe-Inferred
LanguageHaskell98

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

Re-export the relevant set of generic XML document type definitions

data Document i Source #

The symbol table stored in a document holds all its general entity reference definitions.

Constructors

Document Prolog (SymTab EntityDef) (Element i) [Misc] 

Instances

Instances details
Functor Document Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Document a -> Document b

(<$) :: a -> Document b -> Document a

Eq (Document i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Document i -> Document i -> Bool

(/=) :: Document i -> Document i -> Bool

Show i => Show (Document i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Document i -> ShowS

show :: Document i -> String

showList :: [Document i] -> ShowS

data Element i Source #

Constructors

Elem QName [Attribute] [Content i] 

Instances

Instances details
Functor Element Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Element a -> Element b

(<$) :: a -> Element b -> Element a

Eq (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Element i -> Element i -> Bool

(/=) :: Element i -> Element i -> Bool

Show i => Show (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Element i -> ShowS

show :: Element i -> String

showList :: [Element i] -> ShowS

Verbatim (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Element i -> String Source #

data ElemTag Source #

Constructors

ElemTag QName [Attribute] 

Instances

Instances details
Eq ElemTag Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ElemTag -> ElemTag -> Bool

(/=) :: ElemTag -> ElemTag -> Bool

data Content i Source #

Constructors

CElem (Element i) i 
CString Bool CharData i

bool is whether whitespace is significant

CRef Reference i 
CMisc Misc i 

Instances

Instances details
Functor Content Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Content a -> Content b

(<$) :: a -> Content b -> Content a

Eq (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Content i -> Content i -> Bool

(/=) :: Content i -> Content i -> Bool

Show i => Show (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Content i -> ShowS

show :: Content i -> String

showList :: [Content i] -> ShowS

Verbatim (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Content i -> String Source #

data AttValue Source #

Constructors

AttValue [Either String Reference] 

Instances

Instances details
Eq AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: AttValue -> AttValue -> Bool

(/=) :: AttValue -> AttValue -> Bool

Show AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> AttValue -> ShowS

show :: AttValue -> String

showList :: [AttValue] -> ShowS

Verbatim AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: AttValue -> String Source #

data Prolog Source #

Constructors

Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] 

Instances

Instances details
Eq Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Prolog -> Prolog -> Bool

(/=) :: Prolog -> Prolog -> Bool

Show Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Prolog -> ShowS

show :: Prolog -> String

showList :: [Prolog] -> ShowS

data Reference Source #

Instances

Instances details
Eq Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Reference -> Reference -> Bool

(/=) :: Reference -> Reference -> Bool

Show Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Reference -> ShowS

show :: Reference -> String

showList :: [Reference] -> ShowS

Verbatim Reference Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Reference -> String Source #

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

parseContents, toContents

Methods

parseContents :: XMLParser a Source #

Convert from XML to Haskell

toContents :: a -> [Content ()] Source #

Convert from Haskell to XML

xToChar :: a -> Char Source #

Dummy functions (for most types): used only in the Char instance for coercing lists of Char into String.

xFromChar :: Char -> a Source #

Instances

Instances details
XmlContent Bool Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser Bool Source #

toContents :: Bool -> [Content ()] Source #

xToChar :: Bool -> Char Source #

xFromChar :: Char -> Bool Source #

XmlContent Char Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser Char Source #

toContents :: Char -> [Content ()] Source #

xToChar :: Char -> Char Source #

xFromChar :: Char -> Char Source #

XmlContent Char Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent

Methods

parseContents :: XMLParser Char Source #

toContents :: Char -> [Content ()] Source #

xToChar :: Char -> Char Source #

xFromChar :: Char -> Char Source #

XmlContent Double Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

XmlContent Float Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

XmlContent Int Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

XmlContent Integer Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

XmlContent () Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser () Source #

toContents :: () -> [Content ()] Source #

xToChar :: () -> Char Source #

xFromChar :: Char -> () Source #

XmlContent ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

XmlContent a => XmlContent [a] Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser [a] Source #

toContents :: [a] -> [Content ()] Source #

xToChar :: [a] -> Char Source #

xFromChar :: Char -> [a] Source #

XmlContent a => XmlContent [a] Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent

Methods

parseContents :: XMLParser [a] Source #

toContents :: [a] -> [Content ()] Source #

xToChar :: [a] -> Char Source #

xFromChar :: Char -> [a] Source #

XmlContent a => XmlContent (Maybe a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser (Maybe a) Source #

toContents :: Maybe a -> [Content ()] Source #

xToChar :: Maybe a -> Char Source #

xFromChar :: Char -> Maybe a Source #

XmlContent a => XmlContent (Maybe a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent

Methods

parseContents :: XMLParser (Maybe a) Source #

toContents :: Maybe a -> [Content ()] Source #

xToChar :: Maybe a -> Char Source #

xFromChar :: Char -> Maybe a Source #

XmlContent a => XmlContent (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

XmlContent a => XmlContent (OneOf1 a) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

(XmlContent a, XmlContent b) => XmlContent (Either a b) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Haskell

Methods

parseContents :: XMLParser (Either a b) Source #

toContents :: Either a b -> [Content ()] Source #

xToChar :: Either a b -> Char Source #

xFromChar :: Char -> Either a b Source #

(XmlContent a, XmlContent b) => XmlContent (a, b) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b) Source #

toContents :: (a, b) -> [Content ()] Source #

xToChar :: (a, b) -> Char Source #

xFromChar :: Char -> (a, b) Source #

(XmlContent a, XmlContent b) => XmlContent (OneOf2 a b) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf2 a b) Source #

toContents :: OneOf2 a b -> [Content ()] Source #

xToChar :: OneOf2 a b -> Char Source #

xFromChar :: Char -> OneOf2 a b Source #

(XmlContent a, XmlContent b, XmlContent c) => XmlContent (a, b, c) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c) Source #

toContents :: (a, b, c) -> [Content ()] Source #

xToChar :: (a, b, c) -> Char Source #

xFromChar :: Char -> (a, b, c) Source #

(XmlContent a, XmlContent b, XmlContent c) => XmlContent (OneOf3 a b c) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf3 a b c) Source #

toContents :: OneOf3 a b c -> [Content ()] Source #

xToChar :: OneOf3 a b c -> Char Source #

xFromChar :: Char -> OneOf3 a b c Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d) => XmlContent (a, b, c, d) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d) Source #

toContents :: (a, b, c, d) -> [Content ()] Source #

xToChar :: (a, b, c, d) -> Char Source #

xFromChar :: Char -> (a, b, c, d) Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d) => XmlContent (OneOf4 a b c d) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf4 a b c d) Source #

toContents :: OneOf4 a b c d -> [Content ()] Source #

xToChar :: OneOf4 a b c d -> Char Source #

xFromChar :: Char -> OneOf4 a b c d Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e) => XmlContent (a, b, c, d, e) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e) Source #

toContents :: (a, b, c, d, e) -> [Content ()] Source #

xToChar :: (a, b, c, d, e) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e) Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e) => XmlContent (OneOf5 a b c d e) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf5 a b c d e) Source #

toContents :: OneOf5 a b c d e -> [Content ()] Source #

xToChar :: OneOf5 a b c d e -> Char Source #

xFromChar :: Char -> OneOf5 a b c d e Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f) => XmlContent (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f) Source #

toContents :: (a, b, c, d, e, f) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f) Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f) => XmlContent (OneOf6 a b c d e f) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf6 a b c d e f) Source #

toContents :: OneOf6 a b c d e f -> [Content ()] Source #

xToChar :: OneOf6 a b c d e f -> Char Source #

xFromChar :: Char -> OneOf6 a b c d e f Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g) => XmlContent (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g) Source #

toContents :: (a, b, c, d, e, f, g) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g) Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g) => XmlContent (OneOf7 a b c d e f g) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf7 a b c d e f g) Source #

toContents :: OneOf7 a b c d e f g -> [Content ()] Source #

xToChar :: OneOf7 a b c d e f g -> Char Source #

xFromChar :: Char -> OneOf7 a b c d e f g Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h) => XmlContent (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h) Source #

toContents :: (a, b, c, d, e, f, g, h) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf8 a b c d e f g h) Source #

toContents :: OneOf8 a b c d e f g h -> [Content ()] Source #

xToChar :: OneOf8 a b c d e f g h -> Char Source #

xFromChar :: Char -> OneOf8 a b c d e f g h Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i) => XmlContent (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i) Source #

toContents :: (a, b, c, d, e, f, g, h, i) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf9 a b c d e f g h i) Source #

toContents :: OneOf9 a b c d e f g h i -> [Content ()] Source #

xToChar :: OneOf9 a b c d e f g h i -> Char Source #

xFromChar :: Char -> OneOf9 a b c d e f g h i Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j) => XmlContent (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf10 a b c d e f g h i j) Source #

toContents :: OneOf10 a b c d e f g h i j -> [Content ()] Source #

xToChar :: OneOf10 a b c d e f g h i j -> Char Source #

xFromChar :: Char -> OneOf10 a b c d e f g h i j Source #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k) => XmlContent (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j, k) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j, k) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j, k) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j, k) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf11 a b c d e f g h i j k) Source #

toContents :: OneOf11 a b c d e f g h i j k -> [Content ()] Source #

xToChar :: OneOf11 a b c d e f g h i j k -> Char Source #

xFromChar :: Char -> OneOf11 a b c d e f g h i j k Source #

(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 (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j, k, l) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j, k, l) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf12 a b c d e f g h i j k l) Source #

toContents :: OneOf12 a b c d e f g h i j k l -> [Content ()] Source #

xToChar :: OneOf12 a b c d e f g h i j k l -> Char Source #

xFromChar :: Char -> OneOf12 a b c d e f g h i j k l Source #

(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 (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf13 a b c d e f g h i j k l m) Source #

toContents :: OneOf13 a b c d e f g h i j k l m -> [Content ()] Source #

xToChar :: OneOf13 a b c d e f g h i j k l m -> Char Source #

xFromChar :: Char -> OneOf13 a b c d e f g h i j k l m Source #

(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 (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf14 a b c d e f g h i j k l m n) Source #

toContents :: OneOf14 a b c d e f g h i j k l m n -> [Content ()] Source #

xToChar :: OneOf14 a b c d e f g h i j k l m n -> Char Source #

xFromChar :: Char -> OneOf14 a b c d e f g h i j k l m n Source #

(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 (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

parseContents :: XMLParser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

toContents :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> [Content ()] Source #

xToChar :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Char Source #

xFromChar :: Char -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf15 a b c d e f g h i j k l m n o) Source #

toContents :: OneOf15 a b c d e f g h i j k l m n o -> [Content ()] Source #

xToChar :: OneOf15 a b c d e f g h i j k l m n o -> Char Source #

xFromChar :: Char -> OneOf15 a b c d e f g h i j k l m n o Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf16 a b c d e f g h i j k l m n o p) Source #

toContents :: OneOf16 a b c d e f g h i j k l m n o p -> [Content ()] Source #

xToChar :: OneOf16 a b c d e f g h i j k l m n o p -> Char Source #

xFromChar :: Char -> OneOf16 a b c d e f g h i j k l m n o p Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf17 a b c d e f g h i j k l m n o p q) Source #

toContents :: OneOf17 a b c d e f g h i j k l m n o p q -> [Content ()] Source #

xToChar :: OneOf17 a b c d e f g h i j k l m n o p q -> Char Source #

xFromChar :: Char -> OneOf17 a b c d e f g h i j k l m n o p q Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf18 a b c d e f g h i j k l m n o p q r) Source #

toContents :: OneOf18 a b c d e f g h i j k l m n o p q r -> [Content ()] Source #

xToChar :: OneOf18 a b c d e f g h i j k l m n o p q r -> Char Source #

xFromChar :: Char -> OneOf18 a b c d e f g h i j k l m n o p q r Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf19 a b c d e f g h i j k l m n o p q r s) Source #

toContents :: OneOf19 a b c d e f g h i j k l m n o p q r s -> [Content ()] Source #

xToChar :: OneOf19 a b c d e f g h i j k l m n o p q r s -> Char Source #

xFromChar :: Char -> OneOf19 a b c d e f g h i j k l m n o p q r s Source #

(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) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf20 a b c d e f g h i j k l m n o p q r s t) Source #

toContents :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> [Content ()] Source #

xToChar :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> Char Source #

xFromChar :: Char -> OneOf20 a b c d e f g h i j k l m n o p q r s t Source #

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.

Methods

fromAttrs :: [Attribute] -> a Source #

toAttrs :: a -> [Attribute] Source #

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.

inElement :: String -> XMLParser a -> XMLParser a Source #

A combination of element + interior.

text :: XMLParser String Source #

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 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.

mkAttr :: String -> String -> Attribute Source #

Generate a single attribute.

toText :: String -> [Content ()] Source #

Turn a simple string into XML text.

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 #

definiteA :: (String -> Attribute -> Maybe a) -> String -> String -> [Attribute] -> a Source #

defaultA :: (String -> Attribute -> Maybe a) -> a -> String -> [Attribute] -> Defaultable a Source #

possibleA :: (String -> Attribute -> Maybe a) -> String -> [Attribute] -> Maybe 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

Instances details
Eq a => Eq (Defaultable a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

(==) :: Defaultable a -> Defaultable a -> Bool

(/=) :: Defaultable a -> Defaultable a -> Bool

Show a => Show (Defaultable a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

showsPrec :: Int -> Defaultable a -> ShowS

show :: Defaultable a -> String

showList :: [Defaultable a] -> ShowS

str2attr :: String -> AttValue Source #

attr2str :: AttValue -> String Source #

attval :: Read a => Element i -> a Source #

Read a single attribute called "value".

catMaybes :: [Maybe a] -> [a] #

Explicit representation of Haskell datatype information

Types useful for some content models

data List1 a Source #

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] 

Instances

Instances details
Eq a => Eq (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

(==) :: List1 a -> List1 a -> Bool

(/=) :: List1 a -> List1 a -> Bool

Show a => Show (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

showsPrec :: Int -> List1 a -> ShowS

show :: List1 a -> String

showList :: [List1 a] -> ShowS

HTypeable a => HTypeable (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

toHType :: List1 a -> HType Source #

XmlContent a => XmlContent (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

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

Instances details
Eq ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

(==) :: ANYContent -> ANYContent -> Bool

(/=) :: ANYContent -> ANYContent -> Bool

Show ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

showsPrec :: Int -> ANYContent -> ShowS

show :: ANYContent -> String

showList :: [ANYContent] -> ShowS

HTypeable ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

XmlContent ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser