HaXml-1.25.5: 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.

Instances
SchemaType Double Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Float Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Int Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Integer Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType PositiveInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType UnsignedByte Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType UnsignedShort Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType UnsignedInt Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType UnsignedLong Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NonNegativeInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Byte Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Short Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Long Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NegativeInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NonPositiveInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NMTOKENS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NMTOKEN Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType ENTITIES Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType ENTITY Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType IDREFS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType IDREF Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType ID Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NCName Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Name Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Language Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Token Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NormalizedString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GMonthDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GYear Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GYearMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Date Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Time Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType DateTime Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Duration Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Decimal Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType NOTATION Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType AnyURI Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType HexBinary Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Base64Binary Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType XsdString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Boolean Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType AnyElement Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

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.

Instances
SimpleType Bool Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Double Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Float Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Int Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Integer Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType PositiveInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType UnsignedByte Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType UnsignedShort Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType UnsignedInt Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType UnsignedLong Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NonNegativeInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Byte Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Short Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Long Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NegativeInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NonPositiveInteger Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NMTOKENS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NMTOKEN Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType ENTITIES Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType ENTITY Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType IDREFS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType IDREF Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType ID Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NCName Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Name Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Language Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Token Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NormalizedString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GMonthDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GYear Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GYearMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Date Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Time Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType DateTime Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Duration Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Decimal Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType NOTATION Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType AnyURI Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType HexBinary Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Base64Binary Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType XsdString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

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.

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.

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
Eq Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Occurs -> Occurs -> Bool #

(/=) :: Occurs -> Occurs -> Bool #

Show Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Semigroup Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.TypeConversion

Monoid Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.TypeConversion

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 # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Eq (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show i => Show (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

show :: Content i -> String #

showList :: [Content i] -> ShowS #

Verbatim (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

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.