HaXml-1.25.4: Utilities for manipulating XML documents

Safe HaskellNone
LanguageHaskell98

Text.XML.HaXml.Schema.Schema

Synopsis

Documentation

class SchemaType a where Source #

A SchemaType promises to interconvert between a generic XML content tree and a Haskell value, according to the rules of XSD.

Minimal complete definition

parseSchemaType, schemaTypeToXML

Instances

SchemaType Double Source # 
SchemaType Float Source # 
SchemaType Int Source # 
SchemaType Integer Source # 
SchemaType PositiveInteger Source # 
SchemaType UnsignedByte Source # 
SchemaType UnsignedShort Source # 
SchemaType UnsignedInt Source # 
SchemaType UnsignedLong Source # 
SchemaType NonNegativeInteger Source # 
SchemaType Byte Source # 
SchemaType Short Source # 
SchemaType Long Source # 
SchemaType NegativeInteger Source # 
SchemaType NonPositiveInteger Source # 
SchemaType NMTOKENS Source # 
SchemaType NMTOKEN Source # 
SchemaType ENTITIES Source # 
SchemaType ENTITY Source # 
SchemaType IDREFS Source # 
SchemaType IDREF Source # 
SchemaType ID Source # 
SchemaType NCName Source # 
SchemaType Name Source # 
SchemaType Language Source # 
SchemaType Token Source # 
SchemaType NormalizedString Source # 
SchemaType GMonth Source # 
SchemaType GDay Source # 
SchemaType GMonthDay Source # 
SchemaType GYear Source # 
SchemaType GYearMonth Source # 
SchemaType Date Source # 
SchemaType Time Source # 
SchemaType DateTime Source # 
SchemaType Duration Source # 
SchemaType Decimal Source # 
SchemaType NOTATION Source # 
SchemaType AnyURI Source # 
SchemaType HexBinary Source # 
SchemaType Base64Binary Source # 
SchemaType XsdString Source # 
SchemaType Boolean Source # 
SchemaType AnyElement Source # 

class SimpleType a where Source #

Ultimately, an XML parser will find some plain text as the content of a simpleType, which will need to be parsed. We use a TextParser, because values of simpleTypes can also be given elsewhere, e.g. as attribute values in an XSD definition, e.g. to restrict the permissible values of the simpleType. Such restrictions are therefore implemented as layered parsers.

Minimal complete definition

acceptingParser, simpleTypeText

Instances

SimpleType Bool Source # 
SimpleType Double Source # 
SimpleType Float Source # 
SimpleType Int Source # 
SimpleType Integer Source # 
SimpleType PositiveInteger Source # 
SimpleType UnsignedByte Source # 
SimpleType UnsignedShort Source # 
SimpleType UnsignedInt Source # 
SimpleType UnsignedLong Source # 
SimpleType NonNegativeInteger Source # 
SimpleType Byte Source # 
SimpleType Short Source # 
SimpleType Long Source # 
SimpleType NegativeInteger Source # 
SimpleType NonPositiveInteger Source # 
SimpleType NMTOKENS Source # 
SimpleType NMTOKEN Source # 
SimpleType ENTITIES Source # 
SimpleType ENTITY Source # 
SimpleType IDREFS Source # 
SimpleType IDREF Source # 
SimpleType ID Source # 
SimpleType NCName Source # 
SimpleType Name Source # 
SimpleType Language Source # 
SimpleType Token Source # 
SimpleType NormalizedString Source # 
SimpleType GMonth Source # 
SimpleType GDay Source # 
SimpleType GMonthDay Source # 
SimpleType GYear Source # 
SimpleType GYearMonth Source # 
SimpleType Date Source # 
SimpleType Time Source # 
SimpleType DateTime Source # 
SimpleType Duration Source # 
SimpleType Decimal Source # 
SimpleType NOTATION Source # 
SimpleType AnyURI Source # 
SimpleType HexBinary Source # 
SimpleType Base64Binary Source # 
SimpleType XsdString Source # 

class Extension t s where Source #

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

Minimal complete definition

supertype

Methods

supertype :: t -> s Source #

class Restricts t s | t -> s where Source #

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.

Minimal complete definition

restricts

Methods

restricts :: t -> s Source #

class FwdDecl fd a | fd -> a Source #

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 a Source #

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 t Source #

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 String Source #

Parse the textual part of mixed content

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

Functor Content Source # 

Methods

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

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

Eq (Content i) Source # 

Methods

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

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

Show i => Show (Content i) Source # 

Methods

showsPrec :: Int -> Content i -> ShowS #

show :: Content i -> String #

showList :: [Content i] -> ShowS #

Verbatim (Content i) Source # 

Methods

verbatim :: Content i -> String Source #

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.

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

text :: XMLParser String Source #

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

module Text.Parse

toXMLElement :: String -> [[Attribute]] -> [[Content ()]] -> [Content ()] Source #

addXMLAttributes :: [[Attribute]] -> [Content ()] -> [Content ()] Source #

For a ComplexType that is an extension of a SimpleType, it is necessary to convert the value to XML first, then add in the extra attributes that constitute the extension.