Safe Haskell | None |
---|---|
Language | Haskell98 |
- class SchemaType a where
- parseSchemaType :: String -> XMLParser a
- schemaTypeToXML :: String -> a -> [Content ()]
- class SimpleType a where
- acceptingParser :: TextParser a
- simpleTypeText :: a -> String
- class Extension t s where
- supertype :: t -> s
- class Restricts t s | t -> s where
- restricts :: t -> s
- class FwdDecl fd a | fd -> a
- getAttribute :: (SimpleType a, Show a) => String -> Element Posn -> Posn -> XMLParser a
- between :: PolyParse p => Occurs -> p a -> p [a]
- data Occurs = Occurs (Maybe Int) (Maybe Int)
- parseSimpleType :: SimpleType t => XMLParser t
- parseText :: XMLParser String
- data AnyElement
- = forall a . (SchemaType a, Show a) => ANYSchemaType a
- | UnconvertedANY (Content Posn)
- parseAnyElement :: XMLParser AnyElement
- data Content i
- type XMLParser a = Parser (Content Posn) a
- posnElement :: [String] -> XMLParser (Posn, Element Posn)
- posnElementWith :: (String -> String -> Bool) -> [String] -> XMLParser (Posn, Element Posn)
- element :: [String] -> XMLParser (Element Posn)
- interior :: Element Posn -> XMLParser a -> XMLParser a
- text :: XMLParser String
- module Text.ParserCombinators.Poly
- module Text.Parse
- module Text.XML.HaXml.OneOfN
- toXMLElement :: String -> [[Attribute]] -> [[Content ()]] -> [Content ()]
- toXMLText :: String -> [Content ()]
- toXMLAnyElement :: AnyElement -> [Content ()]
- toXMLAttribute :: SimpleType a => String -> a -> [Attribute]
- addXMLAttributes :: [[Attribute]] -> [Content ()] -> [Content ()]
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.
parseSchemaType :: String -> XMLParser a Source
schemaTypeToXML :: String -> a -> [Content ()] 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.
acceptingParser :: TextParser a Source
simpleTypeText :: a -> String 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.
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.
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.
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.
data AnyElement Source
The xsd:any type. Parsing will always produce an UnconvertedANY.
forall a . (SchemaType a, Show a) => ANYSchemaType a | |
UnconvertedANY (Content Posn) |
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.
module Text.ParserCombinators.Poly
module Text.Parse
module Text.XML.HaXml.OneOfN
toXMLAnyElement :: AnyElement -> [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.