symantic-xml-2.0.0.20200523: Library for reading, validating and writing XML.

Safe HaskellNone
LanguageHaskell2010

Symantic.XML.Tree.Read

Contents

Synopsis

Documentation

Type ErrorRead

Type ReadTree

type ReadTree e s a = ReadTreeConstraints e s a => ReaderT ReadTreeInh (Parsec e s) a Source #

Convenient alias.

Type ReadTreeConstraints

Type ReadTreeInh

p_SourcedBegin :: ReadTree e s a -> ReadTree e s a Source #

Like p_Sourced but uncoupled (through the use of p_SourcedEnd) for more flexibility.

p_SourcedEnd :: ReadTree e s (a -> Sourced (FileSource Offset) a) Source #

WARNING: only to be used within a p_SourcedBegin.

Type Error

data Error Source #

Constructors

Error_CharRef_invalid Integer

Well-formedness constraint: Legal Character.

Characters referred to using character references MUST match the production for Char.

Error_EntityRef_unknown NCName

Well-formedness constraint: Entity Declared

In a document without any DTD, a document with only an internal DTD subset which contains no parameter entity references, or a document with " standalone=yes ", for an entity reference that does not occur within the external subset or a parameter entity, the Name given in the entity reference MUST match that in an entity declaration that does not occur within the external subset or a parameter entity, except that well-formed documents need not declare any of the following entities: amp, lt, gt, apos, quot. The declaration of a general entity MUST precede any reference to it which appears in a default value in an attribute-list declaration.

Note that non-validating processors are not obligated to read and process entity declarations occurring in parameter entities or in the external subset; for such documents, the define that an entity must be declared is a well-formedness constraint only if standalone=yes.

Error_Closing_tag_unexpected QName QName

Well-formedness constraint: Element Type Match.

The Name in an element's end-tag MUST match the element type in the start-tag.

Error_Attribute_collision QName

Well-formedness constraint: Unique Att Spec.

An attribute name MUST NOT appear more than once in the same start-tag or empty-element tag.

Error_PI_reserved PName

The target names " XML ", " xml ", and so on are reserved for standardization.

Error_Namespace_prefix_unknown NCName

Namespace constraint: Prefix Declared

The namespace prefix, unless it is xml or xmlns, MUST have been declared in a namespace declaration attribute in either the start-tag of the element where the prefix is used or in an ancestor element (i.e., an element in whose content the prefixed markup occurs).

Error_Namespace_empty NCName

Namespace constraint: No Prefix Undeclaring

In a namespace declaration for a prefix (i.e., where the NSAttName is a PrefixedAttName), the attribute value MUST NOT be empty.

Error_Namespace_reserved Namespace 
Error_Namespace_reserved_prefix NCName

Namespace constraint: Reserved Prefixes and Namespace Names

The prefix xml is by definition bound to the namespace name http://www.w3.org/XML/1998/namespace. It MAY, but need not, be declared, and MUST NOT be bound to any other namespace name. Other prefixes MUST NOT be bound to this namespace name, and it MUST NOT be declared as the default namespace.

The prefix xmlns is used only to declare namespace bindings and is by definition bound to the namespace name http://www.w3.org/2000/xmlns/. It MUST NOT be declared . Other prefixes MUST NOT be bound to this namespace name, and it MUST NOT be declared as the default namespace. Element names MUST NOT have the prefix xmlns.

All other prefixes beginning with the three-letter sequence x, m, l, in any case combination, are reserved. This means that:

  • users SHOULD NOT use them except as defined by later specifications
  • processors MUST NOT treat them as fatal errors.
Instances
Eq Error Source # 
Instance details

Defined in Symantic.XML.Tree.Read

Methods

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

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

Ord Error Source # 
Instance details

Defined in Symantic.XML.Tree.Read

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

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

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Show Error Source # 
Instance details

Defined in Symantic.XML.Tree.Read

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

ShowErrorComponent Error Source # 
Instance details

Defined in Symantic.XML.Tree.Read

Helpers

p_error :: e -> ReadTree e s a Source #

p_quoted :: Tokens s ~ Text => (Char -> ReadTree e s a) -> ReadTree e s a Source #

p_until :: Tokens s ~ Text => (Char -> Bool) -> (Char, Text) -> ReadTree e s Text Source #

p_until1 :: Tokens s ~ Text => (Char -> Bool) -> (Char, Text) -> ReadTree e s Text Source #

Document

Prolog

Misc

XMLDecl

SDDecl

CharData

Comment

CDATA

PI

Element

STag

Attribute

p_Attribute :: Tokens s ~ Text => ReadTree Error s (PName, FileSourced EscapedAttr) Source #

Note: despite the type, the returned FileSource encompasses also the attribute PName. It is pushed in the attribute value to fit the insertion of the attribute into a HashMap.

content

ETag

PName

QName

NCName

Reference

EntityRef

CharRef

Char

Space

p_CRLF :: Tokens s ~ Text => ReadTree e s Char Source #

Map '\r' and '\r\n' to '\n'. See: https://www.w3.org/TR/xml/#sec-line-ends

p_Spaces :: Tokens s ~ Text => ReadTree e s () Source #

Eq

p_Eq :: Tokens s ~ Text => ReadTree e s () Source #