xml-tydom-core-0.1.0.0: Typed XML encoding (core library).

Copyright(c) Jonathan Merritt 2017
LicenseBSD3
Maintainerj.s.merritt@gmail.com
StabilityExperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.XML.TyDom.Core.Types

Contents

Description

This module contains classes and types which are parameterized to allow a very generic typed DOM interface.

Type parameters have been abbreviated to single letters, which are used uniformly throughout:

  • e - element type
  • n - type for the name of an element
  • a - type for the name of an attribute
  • t - type for text content in the XML document

Synopsis

Classes

class ToElem e z where Source #

Typeclass for a type z that can be represented as element type e.

Minimal complete definition

toElem

Methods

toElem :: z -> e Source #

Converts a value of type z to element type e.

class FromElem e n a t z where Source #

Typeclass for a type z which can be read from an element of type e.

Minimal complete definition

fromElem

Methods

fromElem :: e -> Result e n a t z Source #

Converts a value of element type e to a Result of type z, thus allowing for the possibility of failure.

class ToXText t z where Source #

Typeclass for a type z which can be represented as text type t.

Minimal complete definition

toXText

Methods

toXText :: z -> t Source #

Converts a value of type z to text type t.

class FromXText t z where Source #

Typeclass for a type z which can be read from a text type t.

Minimal complete definition

fromXText

Methods

fromXText :: t -> Either XTextError z Source #

Reads a value of type t into an Either.

As a failure case (Left), the Either may contain an XTextError, describing the reason for the failure. On success (Right), the Either contains a value of type z.

class Conv p q where Source #

Typeclass for conversion between types p and q.

This typeclass is particularly used for conversion between raw types and their XML-decorated versions, corresponding to Attr, Child, Content and CData.

Minimal complete definition

conv

Methods

conv :: p -> q Source #

Converts a value of type p to a value of type q.

Instances

Conv z z Source # 

Methods

conv :: z -> z Source #

Conv z (CData z) Source # 

Methods

conv :: z -> CData z Source #

Conv z (Content z) Source # 

Methods

conv :: z -> Content z Source #

Conv z (Child z) Source # 

Methods

conv :: z -> Child z Source #

Conv z (Attr z) Source # 

Methods

conv :: z -> Attr z Source #

Conv (CData z) z Source # 

Methods

conv :: CData z -> z Source #

Conv (Content z) z Source # 

Methods

conv :: Content z -> z Source #

Conv (Child z) z Source # 

Methods

conv :: Child z -> z Source #

Conv (Attr z) z Source # 

Methods

conv :: Attr z -> z Source #

XML DOM Types

newtype Attr z Source #

Attribute.

Specifies that a record field of type Attr z should become an XML attribute. The name of the attribute is specified by the name of the record selector, while the value is the textual representation of the value of type z.

Constructors

Attr 

Fields

Instances

(KnownSymbol name, ToXText t z) => GToElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr (Maybe z)))) Source #

S1 (named) + Attr Maybe - record selector for optional XML attribute.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr (Maybe z))) r -> c -> c

(KnownSymbol name, ToXText t z) => GToElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr z))) Source #

S1 (named) + Attr - record selector for an XML attribute.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr z)) r -> c -> c

(KnownSymbol name, FromXText t z) => GFromElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr (Maybe z)))) Source #

S1 (named) + Attr Maybe - record selector for an optional XML attribute.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr (Maybe z))) r, d)

(KnownSymbol name, FromXText t z) => GFromElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr z))) Source #

S1 (named) + Attr - record selector for an XML attribute.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Attr z)) r, d)

Conv z (Attr z) Source # 

Methods

conv :: z -> Attr z Source #

Eq z => Eq (Attr z) Source # 

Methods

(==) :: Attr z -> Attr z -> Bool #

(/=) :: Attr z -> Attr z -> Bool #

Show z => Show (Attr z) Source # 

Methods

showsPrec :: Int -> Attr z -> ShowS #

show :: Attr z -> String #

showList :: [Attr z] -> ShowS #

Arbitrary z => Arbitrary (Attr z) Source # 

Methods

arbitrary :: Gen (Attr z) #

shrink :: Attr z -> [Attr z] #

Conv (Attr z) z Source # 

Methods

conv :: Attr z -> z Source #

newtype Child z Source #

Child (containing only text).

Specifies that a record field of type Child z should become a child element of the current element, containing the textual representation of the value of type z.

Constructors

Child 

Fields

Instances

(KnownSymbol name, ToXText t z) => GToElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child [z]))) Source #

S1 (named) + [Child] - record selector for a list of simple child elements with text.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child [z])) r -> c -> c

(KnownSymbol name, ToXText t z) => GToElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child (Maybe z)))) Source #

S1 (named) + Child Maybe - record selector for an optional simple child element with text.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child (Maybe z))) r -> c -> c

(KnownSymbol name, ToXText t z) => GToElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child z))) Source #

S1 (named) + Child - record selector for a simple child element with text.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child z)) r -> c -> c

(KnownSymbol name, FromXText t z) => GFromElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child [z]))) Source #

S1 (named) + [Child] - record selector for a list of child elements with text content.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child [z])) r, d)

(KnownSymbol name, FromXText t z) => GFromElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child (Maybe z)))) Source #

S1 (named) + Child Maybe - record selector for a simple optional child element with text content.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child (Maybe z))) r, d)

(KnownSymbol name, FromXText t z) => GFromElem e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child z))) Source #

S1 (named) + Child - record selector for a simple child element with text content.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 (MetaSel (Just Symbol name) g h i) (Rec0 (Child z)) r, d)

Conv z (Child z) Source # 

Methods

conv :: z -> Child z Source #

Eq z => Eq (Child z) Source # 

Methods

(==) :: Child z -> Child z -> Bool #

(/=) :: Child z -> Child z -> Bool #

Show z => Show (Child z) Source # 

Methods

showsPrec :: Int -> Child z -> ShowS #

show :: Child z -> String #

showList :: [Child z] -> ShowS #

Arbitrary z => Arbitrary (Child z) Source # 

Methods

arbitrary :: Gen (Child z) #

shrink :: Child z -> [Child z] #

Conv (Child z) z Source # 

Methods

conv :: Child z -> z Source #

newtype Content z Source #

Content node.

Specifies that a record field of type Content z should become a content node of the current element, containing the textual representation of the value of type z.

Constructors

Content 

Fields

Instances

ToXText t z => GToElem e n a t (S1 q (Rec0 (Content (Maybe z)))) Source #

S1 (named or unnamed) + Content Maybe - record selector for an optional content node.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 (Content (Maybe z))) r -> c -> c

ToXText t z => GToElem e n a t (S1 q (Rec0 (Content z))) Source #

S1 (named or unnamed) + Content - record selector for a content node.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 (Content z)) r -> c -> c

FromXText t z => GFromElem e n a t (S1 q (Rec0 (Content (Maybe z)))) Source #

S1 (named or unnamed) + Content Maybe - record selector for an optional content child.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 (Content (Maybe z))) r, d)

FromXText t z => GFromElem e n a t (S1 q (Rec0 (Content z))) Source #

S1 (named or unnamed) + Content - record selector for a content child.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 (Content z)) r, d)

Conv z (Content z) Source # 

Methods

conv :: z -> Content z Source #

Eq z => Eq (Content z) Source # 

Methods

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

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

Show z => Show (Content z) Source # 

Methods

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

show :: Content z -> String #

showList :: [Content z] -> ShowS #

Arbitrary z => Arbitrary (Content z) Source # 

Methods

arbitrary :: Gen (Content z) #

shrink :: Content z -> [Content z] #

Conv (Content z) z Source # 

Methods

conv :: Content z -> z Source #

newtype CData z Source #

CData node.

Specifies that a record field of type CData z should become a CDATA node of the current element, containing the textual representation of the value of type z.

Constructors

CData 

Fields

Instances

ToXText t z => GToElem e n a t (S1 q (Rec0 (CData [z]))) Source #

S1 (named or unnamed) + [CData] - record selector for a list of CDATA child nodes.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 (CData [z])) r -> c -> c

ToXText t z => GToElem e n a t (S1 q (Rec0 (CData (Maybe z)))) Source #

S1 (named or unnamed) + CData Maybe - record selector for an optional CDATA child node.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 (CData (Maybe z))) r -> c -> c

ToXText t z => GToElem e n a t (S1 q (Rec0 (CData z))) Source #

S1 (named or unnamed) + CData - record selector for a CDATA child node.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 (CData z)) r -> c -> c

FromXText t z => GFromElem e n a t (S1 q (Rec0 (CData [z]))) Source #

S1 (named or unnamed) + [CData] - record selector for a list of CDATA child nodes.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 (CData [z])) r, d)

FromXText t z => GFromElem e n a t (S1 q (Rec0 (CData (Maybe z)))) Source #

S1 (named or unnamed) + CData Maybe - record selector for an optional CDATA child node.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 (CData (Maybe z))) r, d)

FromXText t z => GFromElem e n a t (S1 q (Rec0 (CData z))) Source #

S1 (named or unnamed) + CData - record selector for a CDATA child node.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 (CData z)) r, d)

Conv z (CData z) Source # 

Methods

conv :: z -> CData z Source #

Eq z => Eq (CData z) Source # 

Methods

(==) :: CData z -> CData z -> Bool #

(/=) :: CData z -> CData z -> Bool #

Show z => Show (CData z) Source # 

Methods

showsPrec :: Int -> CData z -> ShowS #

show :: CData z -> String #

showList :: [CData z] -> ShowS #

Arbitrary z => Arbitrary (CData z) Source # 

Methods

arbitrary :: Gen (CData z) #

shrink :: CData z -> [CData z] #

Conv (CData z) z Source # 

Methods

conv :: CData z -> z Source #

Result Types

newtype XTextError Source #

Error which may occur when parsing XML text.

Constructors

XTextError 

Fields

data Result e n a t z Source #

Result of converting an element (type e) to type z.

Constructors

Success z

Successful result of type z.

Failure (Path n) (Cause e n a t)

Failure.

The failure contains the Path to the element which failed, as well as the Cause of the failure.

Instances

Monad (Result elem elemN attrN txt) Source # 

Methods

(>>=) :: Result elem elemN attrN txt a -> (a -> Result elem elemN attrN txt b) -> Result elem elemN attrN txt b #

(>>) :: Result elem elemN attrN txt a -> Result elem elemN attrN txt b -> Result elem elemN attrN txt b #

return :: a -> Result elem elemN attrN txt a #

fail :: String -> Result elem elemN attrN txt a #

Functor (Result e n a t) Source # 

Methods

fmap :: (a -> b) -> Result e n a t a -> Result e n a t b #

(<$) :: a -> Result e n a t b -> Result e n a t a #

Applicative (Result e n a t) Source # 

Methods

pure :: a -> Result e n a t a #

(<*>) :: Result e n a t (a -> b) -> Result e n a t a -> Result e n a t b #

(*>) :: Result e n a t a -> Result e n a t b -> Result e n a t b #

(<*) :: Result e n a t a -> Result e n a t b -> Result e n a t a #

Alternative (Result elem elemN attrN txt) Source # 

Methods

empty :: Result elem elemN attrN txt a #

(<|>) :: Result elem elemN attrN txt a -> Result elem elemN attrN txt a -> Result elem elemN attrN txt a #

some :: Result elem elemN attrN txt a -> Result elem elemN attrN txt [a] #

many :: Result elem elemN attrN txt a -> Result elem elemN attrN txt [a] #

(Show e, Show n, Show a, Show t, Show z) => Show (Result e n a t z) Source # 

Methods

showsPrec :: Int -> Result e n a t z -> ShowS #

show :: Result e n a t z -> String #

showList :: [Result e n a t z] -> ShowS #

data Path n Source #

Path to a failure.

Constructors

PathItem n (Path n)

Item in the path.

PathRoot

Root (source / origin) of the path.

Instances

Show n => Show (Path n) Source # 

Methods

showsPrec :: Int -> Path n -> ShowS #

show :: Path n -> String #

showList :: [Path n] -> ShowS #

Functions

xTextErrType :: Text -> Text -> Either XTextError a Source #

Formats an XTextError string and returns it as a Left instance.

prependPath :: n -> Result e n a t z -> Result e n a t z Source #

Prepends an element name to a Path in a failure result.

replacePathHead :: n -> Result e n a t z -> Result e n a t z Source #

Replaces the current head of a Path in a failure result.