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

Methods

parseSchemaType :: String -> XMLParser a Source #

schemaTypeToXML :: String -> a -> [Content ()] Source #

Instances

Instances details
SchemaType Double Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Double Source #

schemaTypeToXML :: String -> Double -> [Content ()] Source #

SchemaType Float Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Float Source #

schemaTypeToXML :: String -> Float -> [Content ()] Source #

SchemaType Int Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Int Source #

schemaTypeToXML :: String -> Int -> [Content ()] Source #

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

Methods

parseSchemaType :: String -> XMLParser Byte Source #

schemaTypeToXML :: String -> Byte -> [Content ()] Source #

SchemaType Short Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Short Source #

schemaTypeToXML :: String -> Short -> [Content ()] Source #

SchemaType Long Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Long Source #

schemaTypeToXML :: String -> Long -> [Content ()] Source #

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

Methods

parseSchemaType :: String -> XMLParser ENTITY Source #

schemaTypeToXML :: String -> ENTITY -> [Content ()] Source #

SchemaType IDREFS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser IDREFS Source #

schemaTypeToXML :: String -> IDREFS -> [Content ()] Source #

SchemaType IDREF Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser IDREF Source #

schemaTypeToXML :: String -> IDREF -> [Content ()] Source #

SchemaType ID Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser ID Source #

schemaTypeToXML :: String -> ID -> [Content ()] Source #

SchemaType NCName Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser NCName Source #

schemaTypeToXML :: String -> NCName -> [Content ()] Source #

SchemaType Name Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Name Source #

schemaTypeToXML :: String -> Name -> [Content ()] Source #

SchemaType Language Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Token Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Token Source #

schemaTypeToXML :: String -> Token -> [Content ()] Source #

SchemaType NormalizedString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser GMonth Source #

schemaTypeToXML :: String -> GMonth -> [Content ()] Source #

SchemaType GDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser GDay Source #

schemaTypeToXML :: String -> GDay -> [Content ()] Source #

SchemaType GMonthDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType GYear Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser GYear Source #

schemaTypeToXML :: String -> GYear -> [Content ()] Source #

SchemaType GYearMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

SchemaType Date Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Date Source #

schemaTypeToXML :: String -> Date -> [Content ()] Source #

SchemaType Time Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

parseSchemaType :: String -> XMLParser Time Source #

schemaTypeToXML :: String -> Time -> [Content ()] Source #

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

Methods

parseSchemaType :: String -> XMLParser AnyURI Source #

schemaTypeToXML :: String -> AnyURI -> [Content ()] Source #

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.

Methods

acceptingParser :: TextParser a Source #

simpleTypeText :: a -> String Source #

Instances

Instances details
SimpleType Bool Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Bool Source #

simpleTypeText :: Bool -> String Source #

SimpleType Double Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Double Source #

simpleTypeText :: Double -> String Source #

SimpleType Float Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Float Source #

simpleTypeText :: Float -> String Source #

SimpleType Int Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Int Source #

simpleTypeText :: Int -> String Source #

SimpleType Integer Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Integer Source #

simpleTypeText :: Integer -> String Source #

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

Methods

acceptingParser :: TextParser Byte Source #

simpleTypeText :: Byte -> String Source #

SimpleType Short Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Short Source #

simpleTypeText :: Short -> String Source #

SimpleType Long Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Long Source #

simpleTypeText :: Long -> String Source #

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

Methods

acceptingParser :: TextParser NMTOKENS Source #

simpleTypeText :: NMTOKENS -> String Source #

SimpleType NMTOKEN Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser NMTOKEN Source #

simpleTypeText :: NMTOKEN -> String Source #

SimpleType ENTITIES Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser ENTITIES Source #

simpleTypeText :: ENTITIES -> String Source #

SimpleType ENTITY Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser ENTITY Source #

simpleTypeText :: ENTITY -> String Source #

SimpleType IDREFS Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser IDREFS Source #

simpleTypeText :: IDREFS -> String Source #

SimpleType IDREF Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser IDREF Source #

simpleTypeText :: IDREF -> String Source #

SimpleType ID Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser ID Source #

simpleTypeText :: ID -> String Source #

SimpleType NCName Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser NCName Source #

simpleTypeText :: NCName -> String Source #

SimpleType Name Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Name Source #

simpleTypeText :: Name -> String Source #

SimpleType Language Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Language Source #

simpleTypeText :: Language -> String Source #

SimpleType Token Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Token Source #

simpleTypeText :: Token -> String Source #

SimpleType NormalizedString Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser GMonth Source #

simpleTypeText :: GMonth -> String Source #

SimpleType GDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser GDay Source #

simpleTypeText :: GDay -> String Source #

SimpleType GMonthDay Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType GYear Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser GYear Source #

simpleTypeText :: GYear -> String Source #

SimpleType GYearMonth Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

SimpleType Date Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Date Source #

simpleTypeText :: Date -> String Source #

SimpleType Time Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Time Source #

simpleTypeText :: Time -> String Source #

SimpleType DateTime Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser DateTime Source #

simpleTypeText :: DateTime -> String Source #

SimpleType Duration Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Duration Source #

simpleTypeText :: Duration -> String Source #

SimpleType Decimal Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser Decimal Source #

simpleTypeText :: Decimal -> String Source #

SimpleType NOTATION Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser NOTATION Source #

simpleTypeText :: NOTATION -> String Source #

SimpleType AnyURI Source # 
Instance details

Defined in Text.XML.HaXml.Schema.PrimitiveTypes

Methods

acceptingParser :: TextParser AnyURI Source #

simpleTypeText :: AnyURI -> String Source #

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

Instances details
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

Methods

showsPrec :: Int -> Occurs -> ShowS

show :: Occurs -> String

showList :: [Occurs] -> ShowS

Semigroup Occurs 
Instance details

Defined in Text.XML.HaXml.Schema.TypeConversion

Methods

(<>) :: Occurs -> Occurs -> Occurs

sconcat :: NonEmpty Occurs -> Occurs

stimes :: Integral b => b -> Occurs -> Occurs

Monoid Occurs 
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 AnyElement Source #

The xsd:any type. Parsing will always produce an UnconvertedANY.

Constructors

forall a.(SchemaType a, Show a) => ANYSchemaType a 
UnconvertedANY (Content Posn) 

Instances

Instances details
Eq AnyElement Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

(==) :: AnyElement -> AnyElement -> Bool

(/=) :: AnyElement -> AnyElement -> Bool

Show AnyElement Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

Methods

showsPrec :: Int -> AnyElement -> ShowS

show :: AnyElement -> String

showList :: [AnyElement] -> ShowS

SchemaType AnyElement Source # 
Instance details

Defined in Text.XML.HaXml.Schema.Schema

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

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

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

toXMLText :: String -> [Content ()] Source #

toXMLAttribute :: SimpleType a => String -> a -> [Attribute] 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.