Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- (|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool
- xsd :: Name -> QName
- xsdTag :: String -> Content Posn -> Bool
- type XsdParser a = Parser (Content Posn) a
- posnElementWith :: (Content Posn -> Bool) -> [String] -> XsdParser (Posn, Element Posn)
- xsdElement :: Name -> XsdParser (Element Posn)
- anyElement :: XsdParser (Element Posn)
- allChildren :: XsdParser a -> XsdParser a
- interiorWith :: (Content Posn -> Bool) -> XsdParser a -> Element Posn -> XsdParser a
- attribute :: QName -> TextParser a -> Element Posn -> XsdParser a
- namespaceAttrs :: Element Posn -> XsdParser [Namespace]
- matchNamespace :: String -> Attribute -> Bool
- tidy :: t -> Result x a -> Result t a
- targetPrefix :: Maybe TargetNamespace -> [Namespace] -> Maybe String
- lookupBy :: (a -> Bool) -> [a] -> Maybe a
- qual :: Maybe TargetNamespace -> [Namespace] -> String -> String -> QName
- schema :: Parser (Content Posn) Schema
- annotation :: XsdParser Annotation
- definiteAnnotation :: XsdParser Annotation
- qform :: TextParser QForm
- final :: TextParser Final
- block :: TextParser Block
- schemaItem :: (String -> String -> QName) -> XsdParser SchemaItem
- include :: XsdParser SchemaItem
- import_ :: XsdParser SchemaItem
- redefine :: (String -> String -> QName) -> XsdParser SchemaItem
- simpleType :: (String -> String -> QName) -> XsdParser SimpleType
- aFacet :: XsdParser Facet
- facet :: String -> FacetType -> XsdParser Facet
- complexType :: (String -> String -> QName) -> XsdParser ComplexType
- complexItem :: (String -> String -> QName) -> XsdParser ComplexItem
- particle :: (String -> String -> QName) -> XsdParser Particle
- particleAttrs :: (String -> String -> QName) -> XsdParser ParticleAttrs
- choiceOrSeq :: (String -> String -> QName) -> XsdParser ChoiceOrSeq
- group_ :: (String -> String -> QName) -> XsdParser Group
- elementEtc :: (String -> String -> QName) -> XsdParser ElementEtc
- any_ :: XsdParser Any
- anyAttr :: XsdParser AnyAttr
- attributeGroup :: (String -> String -> QName) -> XsdParser AttrGroup
- elementDecl :: (String -> String -> QName) -> XsdParser ElementDecl
- nameAndType :: (String -> String -> QName) -> Element Posn -> XsdParser NameAndType
- attributeDecl :: (String -> String -> QName) -> XsdParser AttributeDecl
- occurs :: Element Posn -> XsdParser Occurs
- uniqueKeyOrKeyRef :: (String -> String -> QName) -> XsdParser UniqueKeyOrKeyRef
- unique :: XsdParser Unique
- key :: XsdParser Key
- keyRef :: (String -> String -> QName) -> XsdParser KeyRef
- selector :: XsdParser Selector
- field_ :: XsdParser Field
- uri :: TextParser String
- string :: TextParser String
- space :: TextParser String
- bool :: TextParser Bool
- use :: TextParser Use
- processContents :: TextParser ProcessContents
- qname :: (String -> String -> QName) -> TextParser QName
- name :: TextParser Name
Documentation
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.)
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.
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 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.
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.
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.
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.
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.
annotation :: XsdParser Annotation Source
Parse a (possibly missing) xsd:annotation element.
definiteAnnotation :: XsdParser Annotation Source
Parse a definitely-occurring xsd:annotation element.
qform :: TextParser QForm Source
Parse a FormDefault attribute.
final :: TextParser Final Source
Parse a Final or Block attribute.
schemaItem :: (String -> String -> QName) -> XsdParser SchemaItem Source
Parse a schema item (just under the toplevel xsd:schema)
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.
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.
elementEtc :: (String -> String -> QName) -> XsdParser ElementEtc Source
Parse an xsd:element, xsd:group, xsd:all, xsd:choice, xsd:sequence or xsd:any.
anyAttr :: XsdParser AnyAttr Source
Parse an xsd:anyAttribute.
attributeGroup :: (String -> String -> QName) -> XsdParser AttrGroup Source
Parse an xsd:attributegroup.
elementDecl :: (String -> String -> QName) -> XsdParser ElementDecl Source
Parse an xsd:element decl.
nameAndType :: (String -> String -> QName) -> Element Posn -> XsdParser NameAndType Source
Parse name and type attributes.
attributeDecl :: (String -> String -> QName) -> XsdParser AttributeDecl Source
Parse an xsd:attribute decl.
occurs :: Element Posn -> XsdParser Occurs Source
Parse an occurrence range from attributes of given element.
uniqueKeyOrKeyRef :: (String -> String -> QName) -> XsdParser UniqueKeyOrKeyRef Source
Parse a xsd:unique, xsd:key, or xsd:keyref.
unique :: XsdParser Unique Source
Parse a xsd:unique.
selector :: XsdParser Selector Source
Parse a xsd:selector.
uri :: TextParser String Source
Text parser for a URI (very simple, non-validating, probably incorrect).
string :: TextParser String Source
Text parser for an arbitrary string consisting of possibly multiple tokens.
bool :: TextParser Bool Source
Parse a textual boolean, i.e. "true", "false", "0", or "1"
use :: TextParser Use Source
Parse a "use" attribute value, i.e. "required", "optional", or "prohibited"
processContents :: TextParser ProcessContents Source
Parse a "processContents" attribute, i.e. "skip", "lax", or "strict".
qname :: (String -> String -> QName) -> TextParser QName Source
Parse an attribute value that should be a QName.
name :: TextParser Name Source
Parse an attribute value that should be a simple Name.