HaXml-1.22.3: Utilities for manipulating XML documents

Text.XML.HaXml.Schema.Parse

Synopsis

Documentation

(|||) :: (a -> Bool) -> (a -> Bool) -> a -> BoolSource

Lift boolean or over predicates.

xsd :: Name -> QNameSource

Qualify an ordinary name with the XSD namespace.

xsdTag :: String -> Content Posn -> BoolSource

Predicate for comparing against an XSD-qualified name. (Also accepts unqualified names, but this is probably a bit too lax. Doing it right would require checking to see whether the current schema module's default namespace is XSD or not.)

type XsdParser a = Parser (Content Posn) aSource

We need a Parser monad for reading from a sequence of generic XML Contents into specific datatypes that model the structure of XSD descriptions. This is a specialisation of the polyparse combinators, fixing the input token type.

posnElementWith :: (Content Posn -> Bool) -> [String] -> XsdParser (Posn, Element Posn)Source

Get the next content element, checking that it matches some criterion given by the predicate. (Skips over comments and whitespace, rejects text and refs. Also returns position of element.) The list of strings argument is for error reporting - it usually represents a list of expected tags.

xsdElement :: Name -> XsdParser (Element Posn)Source

Get the next content element, checking that it has the required tag belonging to the XSD namespace.

anyElement :: XsdParser (Element Posn)Source

Get the next content element, whatever it is.

allChildren :: XsdParser a -> XsdParser aSource

Grab and parse any and all children of the next element.

interiorWith :: (Content Posn -> Bool) -> XsdParser a -> Element Posn -> XsdParser aSource

Run an XsdParser on the child contents of the given element (i.e. not in the current monadic content sequence), filtering the children before parsing, and checking that the contents are exhausted, before returning the calculated value within the current parser context.

attribute :: QName -> TextParser a -> Element Posn -> XsdParser aSource

Check for the presence (and value) of an attribute in the given element. Absence results in failure.

namespaceAttrs :: Element Posn -> XsdParser [Namespace]Source

Grab any attributes that declare a locally-used prefix for a specific namespace.

matchNamespace :: String -> Attribute -> BoolSource

Predicate for whether an attribute belongs to a given namespace.

tidy :: t -> Result x a -> Result t aSource

Tidy up the parsing context.

targetPrefix :: Maybe TargetNamespace -> [Namespace] -> Maybe StringSource

Given a URI for a targetNamespace, and a list of Namespaces, tell me the prefix corresponding to the targetNamespace.

lookupBy :: (a -> Bool) -> [a] -> Maybe aSource

An auxiliary you might expect to find in Data.List

qual :: Maybe TargetNamespace -> [Namespace] -> String -> String -> QNameSource

Turn a qualified attribute value (two strings) into a qualified name (QName), but excluding the case where the namespace prefix corresponds to the targetNamespace of the current schema document.

annotation :: XsdParser AnnotationSource

Parse a Schema declaration

Parse a (possibly missing) xsd:annotation element.

definiteAnnotation :: XsdParser AnnotationSource

Parse a definitely-occurring xsd:annotation element.

qform :: TextParser QFormSource

Parse a FormDefault attribute.

final :: TextParser FinalSource

Parse a Final or Block attribute.

schemaItem :: (String -> String -> QName) -> XsdParser SchemaItemSource

Parse a schema item (just under the toplevel xsd:schema)

complexItem :: (String -> String -> QName) -> XsdParser ComplexItemSource

Parse the alternative contents of a xsd:complexType decl.

particle :: (String -> String -> QName) -> XsdParser ParticleSource

Parse a particle decl.

particleAttrs :: (String -> String -> QName) -> XsdParser ParticleAttrsSource

Parse a particle decl with optional attributes.

nameAndType :: (String -> String -> QName) -> Element Posn -> XsdParser NameAndTypeSource

Parse name and type attributes.

occurs :: Element Posn -> XsdParser OccursSource

Parse an occurrence range from attributes of given element.

uri :: TextParser StringSource

Text parser for a URI (very simple, non-validating, probably incorrect).

string :: TextParser StringSource

Text parser for an arbitrary string consisting of possibly multiple tokens.

bool :: TextParser BoolSource

Parse a textual boolean, i.e. true, false, 0, or 1

use :: TextParser UseSource

Parse a use attribute value, i.e. required, optional, or prohibited

qname :: (String -> String -> QName) -> TextParser QNameSource

Parse an attribute value that should be a QName.

name :: TextParser NameSource

Parse an attribute value that should be a simple Name.