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.Generics

Contents

Description

 

Synopsis

Classes

class GToElem e n a t z Source #

Class for generically converting a type to an element.

Minimal complete definition

gToElem

Instances

GToElem e n a t U1 Source #

U1 - no-argument constructor.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> U1 r -> c -> c

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

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

Methods

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

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

S1 (named or unnamed) + Maybe z - record selector for a ToElem child.

Methods

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

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

S1 (named or unnamed) - record selector for a ToElem child.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> S1 q (Rec0 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 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

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

(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, 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

(GToElem e n a t z1, GToElem e n a t z2) => GToElem e n a t ((:+:) z1 z2) Source #

Sum type (ie. multiple constructors).

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> (z1 :+: z2) r -> c -> c

(GToElem e n a t z1, GToElem e n a t z2) => GToElem e n a t ((:*:) z1 z2) Source #

Product type (ie. multiple fields).

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> (z1 :*: z2) r -> c -> c

(KnownSymbol name, GToElem e n a t z) => GToElem e n a t (C1 (MetaCons name q w) z) Source #

C1 - constructor.

The name of the element is obtained from the constructor name.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> C1 (MetaCons name q w) z r -> c -> c

(KnownSymbol name, ToElem e z) => GToElem e n a t (D1 (MetaData g h i True) (C1 (MetaCons name q w) (S1 s (Rec0 z)))) Source #

Newtype.

A newtype should be processed in the same way as the type it wraps, but the name of the element must be changed at the end.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> D1 (MetaData g h i True) (C1 (MetaCons name q w) (S1 s (Rec0 z))) r -> c -> c

GToElem e n a t z => GToElem e n a t (D1 (MetaData g h i False) z) Source #

D1 - Datatype (non-newtype).

When we encounter a Datatype, just proceed directly to processing its contents, without any additional handling.

Methods

gToElem :: OptionsElement n a -> Compose e n a t c -> D1 (MetaData g h i False) z r -> c -> c

class GFromElem e n a t z Source #

Class for generically converting an element to a type.

Minimal complete definition

gFromElem

Instances

GFromElem e n a t U1 Source #

U1 - no-argument constructor.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (U1 r, d)

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

S1 (named or unnamed) + List - record selector for a list of FromElem children.

Methods

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

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

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

Methods

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

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

S1 (named or unnamed) - record selector for a FromElem child.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (S1 q (Rec0 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 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)

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)

(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)

(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)

(GFromElem e n a t z1, GFromElem e n a t z2) => GFromElem e n a t ((:+:) z1 z2) Source #

Sum type (ie. multiple constructors).

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t ((z1 :+: z2) r, d)

(GFromElem e n a t z1, GFromElem e n a t z2) => GFromElem e n a t ((:*:) z1 z2) Source #

Product type (ie. multiple fields).

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t ((z1 :*: z2) r, d)

(KnownSymbol name, Eq n, GFromElem e n a t z) => GFromElem e n a t (C1 (MetaCons name q w) z) Source #

C1 - constructor.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (C1 (MetaCons name q w) z r, d)

(Generic z, GSingleConstructorName (Rep z), KnownSymbol name, FromElem e n a t z) => GFromElem e n a t (D1 (MetaData g h i True) (C1 (MetaCons name q w) (S1 s (Rec0 z)))) Source #

Newtype.

A newtype should appear the same as the type it wraps, but the name of the element is expected to be different.

To read a newtype, there are some shenanigans involved: 1. Check that the actual element name matches the newtype's constructor. 2. Rename the element to the original, wrapped type. The original type must have ONLY ONE constructor, otherwise we wouldn't know what the element should be renamed to. 3. Read in the original element and wrap it in the newtype constructor.

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (D1 (MetaData g h i True) (C1 (MetaCons name q w) (S1 s (Rec0 z))) r, d)

GFromElem e n a t z => GFromElem e n a t (D1 (MetaData g h i False) z) Source #

D1 - Datatype (non-newtype).

Methods

gFromElem :: Eq n => OptionsElement n a -> Decompose e n a t d -> d -> Result e n a t (D1 (MetaData g h i False) z r, d)

Types

data OptionsElement n a Source #

Options for generating ToElem and FromElem instances using GHC Generics.

Type parameters:

  • n - Type for an element name.
  • a - Type for an attribute name.

Constructors

OptionsElement 

Fields

data ReadNodeOrdering Source #

Specifies how child nodes should be treated when reading a type from an element.

Constructors

Sequence

Child nodes should be read in strict sequence (ie. <xsd:sequence>).

All

Child nodes can appear in any order (ie. <xsd:all>).

data ReadLeftovers Source #

Specifies how any left-over parts of an element should be treated when reading a type from an element.

Constructors

LeftoversOK

Left-over parts of an element are OK, and not an error.

LeftoversError

Left-over parts of an element should produce an error.

Generic instance creation

genericToElem :: (Generic z, GToElem e n a t (Rep z)) => OptionsElement n a -> Compose e n a t c -> z -> e Source #

Generic producer for a ToElem instance.

genericFromElem :: (Generic z, GFromElem e n a t (Rep z), Eq n) => OptionsElement n a -> Decompose e n a t d -> e -> Result e n a t z Source #

Generic producer for a FromElem instance.

genericConv :: (Generic a, Generic b, GConv (Rep a) (Rep b)) => a -> b Source #

Generic producer for a Conv instance.