HaXml-1.22.3: Utilities for manipulating XML documents

Text.XML.HaXml.Schema.Schema

Synopsis

Documentation

class Extension t s whereSource

A type t can extend another type s by the addition of extra elements and/or attributes. s is therefore the supertype of t.

Methods

supertype :: t -> sSource

class Restricts t s | t -> s whereSource

A type t can restrict another type s, that is, t admits fewer values than s, but all the values t does admit also belong to the type s.

Methods

restricts :: t -> sSource

class FwdDecl fd a | fd -> aSource

A trick to enable forward-declaration of a type that will be defined properly in another module, higher in the dependency graph. fd is a dummy type e.g. the empty data FwdA, where a is the proper data A, not yet available.

getAttribute :: (SimpleType a, Show a) => String -> Element Posn -> Posn -> XMLParser aSource

Generated parsers will use getAttribute as a convenient wrapper to lift a SchemaAttribute parser into an XMLParser.

between :: PolyParse p => Occurs -> p a -> p [a]Source

Between is a list parser that tries to ensure that any range specification (min and max elements) is obeyed when parsing.

data Occurs Source

Constructors

Occurs (Maybe Int) (Maybe Int) 

Instances

parseSimpleType :: SimpleType t => XMLParser tSource

Given a TextParser for a SimpleType, make it into an XMLParser, i.e. consuming textual XML content as input rather than a String.

parseText :: XMLParser StringSource

Parse the textual part of mixed content

data AnyElement Source

The xsd:any type. Parsing will always produce an UnconvertedANY.

Constructors

forall a . (SchemaType a, Show a) => ANYSchemaType a 
UnconvertedANY (Content Posn) 

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

type XMLParser a = Parser (Content Posn) aSource

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.

posnElement :: [String] -> XMLParser (Posn, Element Posn)Source

A specialisation of posnElementWith (==).

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

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 aSource

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.

text :: XMLParser StringSource

text is a counterpart to element, parsing text content if it exists. Adjacent text and references are coalesced.

module Text.Parse