dom-parser-3.2.0: Simple monadic DOM parser
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.XML.DOM.Parser.Types

Synopsis

Element matching

data ElemMatcher Source #

Arbitrary element matcher

Since: 2.0.0

Constructors

ElemMatcher 

Fields

Instances

Instances details
IsString ElemMatcher Source #

Instance using instance of NameMatcher

Instance details

Defined in Text.XML.DOM.Parser.Types

Show ElemMatcher Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

matchElemName :: NameMatcher -> ElemMatcher Source #

Match element by name

Since: 2.0.0

elMatch :: ElemMatcher -> Traversal' Element Element Source #

Match over elements

Since: 2.0.0

Name matching

data NameMatcher Source #

Arbitrary name matcher. Match name any way you want, but considered to be used as comparator with some name with some rules

Since: 2.0.0

Constructors

NameMatcher 

Fields

  • _nmMatch :: Name -> Bool

    Name matching function, usually should be simple comparsion function takin in account only local name or other components of Name

  • _nmShow :: Text

    Field for Show instance and bulding usefull errors

Instances

Instances details
IsString NameMatcher Source #

Instance use matchCILocalName as most general and liberal matching strategy (while XML is often malformed).

Since: 2.0.0

Instance details

Defined in Text.XML.DOM.Parser.Types

Show NameMatcher Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

matchName :: Name -> NameMatcher Source #

Makes matcher which match name by Eq with given

Since: 2.0.0

matchLocalName :: Text -> NameMatcher Source #

Makes matcher which matches only local part of name igoring namespace and prefix. Local name matching is case sensitive.

Since: 2.0.0

matchCILocalName :: Text -> NameMatcher Source #

Makes matcher which matches only local part of name igoring namespace and prefix. Local name matching is case insensitive. This is the most common case.

Since: 2.0.0

Parser internals

newtype DomPath Source #

Path some element should be found at. Path starts from the root element of the document. Errors are much more usefull with path.

Constructors

DomPath 

Fields

Instances

Instances details
Monoid DomPath Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Semigroup DomPath Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Show DomPath Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Eq DomPath Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Methods

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

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

Ord DomPath Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

data ParserError Source #

DOM parser error description.

Constructors

PENotFound

Tag not found which should be.

Fields

PEAttributeNotFound

Expected attribute but not found

Since: 1.0.0

Fields

PEAttributeWrongFormat

Could not parse attribute

Since: 1.0.0

Fields

PEContentNotFound

Node should have text content, but it does not.

Fields

PEContentWrongFormat

Tag contents has wrong format, (could not read text to value)

Fields

PEOther

Some other error

Fields

Instances

Instances details
Exception ParserError Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Generic ParserError Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Associated Types

type Rep ParserError :: Type -> Type #

Show ParserError Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

type Rep ParserError Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

type Rep ParserError = D1 ('MetaData "ParserError" "Text.XML.DOM.Parser.Types" "dom-parser-3.2.0-IGvKALn5GGL30CFrMXvJrq" 'False) ((C1 ('MetaCons "PENotFound" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath)) :+: (C1 ('MetaCons "PEAttributeNotFound" 'PrefixI 'True) (S1 ('MetaSel ('Just "_peAttributeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameMatcher) :*: S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath)) :+: C1 ('MetaCons "PEAttributeWrongFormat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_peAttributeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameMatcher) :*: (S1 ('MetaSel ('Just "_peDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath))))) :+: (C1 ('MetaCons "PEContentNotFound" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath)) :+: (C1 ('MetaCons "PEContentWrongFormat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_peDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath)) :+: C1 ('MetaCons "PEOther" 'PrefixI 'True) (S1 ('MetaSel ('Just "_peDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_pePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomPath)))))

newtype ParserErrors Source #

Constructors

ParserErrors 

Instances

Instances details
Monoid ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Semigroup ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Exception ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Generic ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

Associated Types

type Rep ParserErrors :: Type -> Type #

Show ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

type Rep ParserErrors Source # 
Instance details

Defined in Text.XML.DOM.Parser.Types

type Rep ParserErrors = D1 ('MetaData "ParserErrors" "Text.XML.DOM.Parser.Types" "dom-parser-3.2.0-IGvKALn5GGL30CFrMXvJrq" 'True) (C1 ('MetaCons "ParserErrors" 'PrefixI 'True) (S1 ('MetaSel ('Just "unParserErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ParserError])))

data ParserData f Source #

Parser scope.

Functor argument is usually Identity or [].

If functor is Identity then parser expects exactly ONE current element. This is common behavior for content parsers, or parsers expecting strict XML structure.

If functor is [] then parser expects arbitrary current elements count. This is the case when you use combinators divePath or diveElem (posible other variants of similar combinators). This kind of combinators performs search for elements somewhere in descendants and result have arbitrary length in common case.

Constructors

ParserData 

Fields

pdElements :: forall f f. Lens (ParserData f) (ParserData f) (f Element) (f Element) Source #

runDomParserT :: Monad m => Document -> DomParserT Identity m a -> m (Either ParserErrors a) Source #

Run parser on root element of Document.

Auxiliary