Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- type XsdParser a = Parser (Content Posn) a
- bool :: TextParser Bool
- (|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- string :: TextParser String
- key :: XsdParser Key
- space :: TextParser String
- attribute :: QName -> TextParser a -> Element Posn -> XsdParser a
- qname :: (String -> String -> QName) -> TextParser QName
- lookupBy :: (a -> Bool) -> [a] -> Maybe a
- xsd :: Name -> QName
- targetPrefix :: Maybe TargetNamespace -> [Namespace] -> Maybe String
- posnElementWith :: (Content Posn -> Bool) -> [String] -> XsdParser (Posn, Element Posn)
- xsdTag :: String -> Content Posn -> Bool
- xsdElement :: Name -> XsdParser (Element Posn)
- anyElement :: XsdParser (Element Posn)
- allChildren :: XsdParser a -> XsdParser a
- interiorWith :: (Content Posn -> Bool) -> XsdParser a -> Element Posn -> XsdParser a
- tidy :: t -> Result x a -> Result t a
- namespaceAttrs :: Element Posn -> XsdParser [Namespace]
- matchNamespace :: String -> Attribute -> Bool
- uri :: TextParser String
- qual :: Maybe TargetNamespace -> [Namespace] -> String -> String -> QName
- schema :: Parser (Content Posn) Schema
- qform :: TextParser QForm
- final :: TextParser Final
- block :: TextParser Block
- schemaItem :: (String -> String -> QName) -> XsdParser SchemaItem
- annotation :: XsdParser Annotation
- definiteAnnotation :: XsdParser Annotation
- include :: XsdParser SchemaItem
- import_ :: XsdParser SchemaItem
- redefine :: (String -> String -> QName) -> XsdParser SchemaItem
- simpleType :: (String -> String -> QName) -> XsdParser SimpleType
- complexType :: (String -> String -> QName) -> XsdParser ComplexType
- elementDecl :: (String -> String -> QName) -> XsdParser ElementDecl
- attributeDecl :: (String -> String -> QName) -> XsdParser AttributeDecl
- attributeGroup :: (String -> String -> QName) -> XsdParser AttrGroup
- group_ :: (String -> String -> QName) -> XsdParser Group
- particle :: (String -> String -> QName) -> XsdParser Particle
- aFacet :: XsdParser Facet
- facet :: String -> FacetType -> XsdParser Facet
- complexItem :: (String -> String -> QName) -> XsdParser ComplexItem
- particleAttrs :: (String -> String -> QName) -> XsdParser ParticleAttrs
- choiceOrSeq :: (String -> String -> QName) -> XsdParser ChoiceOrSeq
- anyAttr :: XsdParser AnyAttr
- occurs :: Element Posn -> XsdParser Occurs
- elementEtc :: (String -> String -> QName) -> XsdParser ElementEtc
- any_ :: XsdParser Any
- processContents :: TextParser ProcessContents
- nameAndType :: (String -> String -> QName) -> Element Posn -> XsdParser NameAndType
- uniqueKeyOrKeyRef :: (String -> String -> QName) -> XsdParser UniqueKeyOrKeyRef
- use :: TextParser Use
- unique :: XsdParser Unique
- keyRef :: (String -> String -> QName) -> XsdParser KeyRef
- selector :: XsdParser Selector
- field_ :: XsdParser Field
Documentation
type XsdParser a = Parser (Content Posn) a Source #
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.
bool :: TextParser Bool Source #
Parse a textual boolean, i.e. "true", "false", "0", or "1"
string :: TextParser String Source #
Text parser for an arbitrary string consisting of possibly multiple tokens.
space :: TextParser String Source #
attribute :: QName -> TextParser a -> Element Posn -> XsdParser a Source #
Check for the presence (and value) of an attribute in the given element. Absence results in failure.
qname :: (String -> String -> QName) -> TextParser QName Source #
Parse an attribute value that should be a QName.
lookupBy :: (a -> Bool) -> [a] -> Maybe a Source #
An auxiliary you might expect to find in Data.List
targetPrefix :: Maybe TargetNamespace -> [Namespace] -> Maybe String Source #
Given a URI for a targetNamespace, and a list of Namespaces, tell me the prefix corresponding to the targetNamespace.
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.
xsdTag :: String -> Content Posn -> Bool Source #
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.)
xsdElement :: Name -> XsdParser (Element Posn) Source #
Get the next content element, checking that it has the required tag belonging to the XSD namespace.
allChildren :: XsdParser a -> XsdParser a Source #
Grab and parse any and all children of the next element.
interiorWith :: (Content Posn -> Bool) -> XsdParser a -> Element Posn -> XsdParser a Source #
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.
namespaceAttrs :: Element Posn -> XsdParser [Namespace] Source #
Grab any attributes that declare a locally-used prefix for a specific namespace.
matchNamespace :: String -> Attribute -> Bool Source #
Predicate for whether an attribute belongs to a given namespace.
uri :: TextParser String Source #
Text parser for a URI (very simple, non-validating, probably incorrect).
qual :: Maybe TargetNamespace -> [Namespace] -> String -> String -> QName Source #
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.
qform :: TextParser QForm Source #
Parse a FormDefault attribute.
final :: TextParser Final Source #
Parse a Final or Block attribute.
block :: TextParser Block Source #
schemaItem :: (String -> String -> QName) -> XsdParser SchemaItem Source #
Parse a schema item (just under the toplevel xsd:schema)
annotation :: XsdParser Annotation Source #
Parse a (possibly missing) xsd:annotation element.
definiteAnnotation :: XsdParser Annotation Source #
Parse a definitely-occurring xsd:annotation element.
include :: XsdParser SchemaItem Source #
Parse an xsd:include.
import_ :: XsdParser SchemaItem Source #
Parse an xsd:import.
redefine :: (String -> String -> QName) -> XsdParser SchemaItem Source #
Parse a xsd:redefine.
simpleType :: (String -> String -> QName) -> XsdParser SimpleType Source #
Parse a xsd:simpleType decl.
complexType :: (String -> String -> QName) -> XsdParser ComplexType Source #
Parse a xsd:complexType decl.
elementDecl :: (String -> String -> QName) -> XsdParser ElementDecl Source #
Parse an xsd:element decl.
attributeDecl :: (String -> String -> QName) -> XsdParser AttributeDecl Source #
Parse an xsd:attribute decl.
attributeGroup :: (String -> String -> QName) -> XsdParser AttrGroup Source #
Parse an xsd:attributegroup.
complexItem :: (String -> String -> QName) -> XsdParser ComplexItem Source #
Parse the alternative contents of a xsd:complexType decl.
particleAttrs :: (String -> String -> QName) -> XsdParser ParticleAttrs Source #
Parse a particle decl with optional attributes.
choiceOrSeq :: (String -> String -> QName) -> XsdParser ChoiceOrSeq Source #
Parse an xsd:all, xsd:choice, or xsd:sequence decl.
occurs :: Element Posn -> XsdParser Occurs Source #
Parse an occurrence range from attributes of given element.
elementEtc :: (String -> String -> QName) -> XsdParser ElementEtc Source #
Parse an xsd:element, xsd:group, xsd:all, xsd:choice, xsd:sequence or xsd:any.
processContents :: TextParser ProcessContents Source #
Parse a "processContents" attribute, i.e. "skip", "lax", or "strict".
nameAndType :: (String -> String -> QName) -> Element Posn -> XsdParser NameAndType Source #
Parse name and type attributes.
uniqueKeyOrKeyRef :: (String -> String -> QName) -> XsdParser UniqueKeyOrKeyRef Source #
Parse a xsd:unique, xsd:key, or xsd:keyref.
use :: TextParser Use Source #
Parse a "use" attribute value, i.e. "required", "optional", or "prohibited"