tdoc-0.4.1: TDoc is a typed document builder with support for (X)HTML

Safe HaskellSafe-Infered

Text.TDoc.Core

Synopsis

Documentation

data AttributeOf t node Source

Constructors

forall attr . attr `IsAttributeOf` node => TAttr (t attr) attr 

type AttributesOf t node = [AttributeOf t node]Source

data TDoc t tag Source

Constructors

TNode 

Fields

tTag :: t tag
 
tAttrs :: AttributesOf t tag
 
tChildren :: [ChildOf t tag]
 

Instances

(~ (* -> *) t HtmlTag, IsNode a) => HTML (TDoc t a) 
(~ (* -> *) t1 t2, ~ * a b) => FromTDoc (TDoc t1 a) t2 b 
(~ (* -> *) t1 t2, ~ * a b) => AddAttrs (TDoc t1 a) t2 b 
(~ (* -> *) t1 t2, ~ * a b) => ToTDoc (TDoc t1 a) t2 b 
(~ (* -> *) t1 t2, IsChildOf a b) => ToChildren (TDoc t1 a) t2 b 

data ChildOf t father Source

Constructors

forall child . child `IsChildOf` father => Child (TDoc t child) 

Instances

~ (* -> *) t HtmlTag => HTML (ChildOf t fatherTag) 
(~ (* -> *) t1 t2, IsChildOf b a) => FromTDoc (ChildOf t1 a) t2 b 
(~ (* -> *) t1 t2, ~ * a b) => ToChildren (ChildOf t1 a) t2 b 

class ToChildren a t father whereSource

Methods

toChildren :: a -> [ChildOf t father]Source

Instances

(LeafTags t, IsChildOf Leaf a) => ToChildren Char t a 
ToChildren () t b 
(LeafTags t, IsChildOf Leaf a) => ToChildren ByteString t a 
(LeafTags t, IsChildOf Leaf a) => ToChildren ByteString t a 
ToChildren a t b => ToChildren [a] t b 
ToChildren a t b => ToChildren (Identity a) t b 
(ToChildren a t n, ToChildren b t n) => ToChildren (a, b) t n 
(~ (* -> *) t1 t2, ~ * a b) => ToChildren (ChildOf t1 a) t2 b 
(~ (* -> *) t1 t2, IsChildOf a b) => ToChildren (TDoc t1 a) t2 b 
(ToChildren a t n, ToChildren b t n, ToChildren c t n) => ToChildren (a, b, c) t n 
(Monad m, ToChildren (m w) t b, ~ * a ()) => ToChildren (WriterT w m a) t b 

class ToTDoc a t b whereSource

Methods

toTDoc :: a -> TDoc t bSource

Instances

(LeafTags t, ~ * a Leaf) => ToTDoc Char t a 
(LeafTags t, ~ * a Leaf) => ToTDoc ByteString t a 
(LeafTags t, ~ * a Leaf) => ToTDoc ByteString t a 
(LeafTags t, ~ * b Char, ~ * a Leaf) => ToTDoc [b] t a 
ToTDoc a t b => ToTDoc (Identity a) t b 
(~ (* -> *) t1 t2, ~ * a b) => ToTDoc (TDoc t1 a) t2 b 
(Monad m, ToTDoc (m w) t b, ~ * a ()) => ToTDoc (WriterT w m a) t b 

class AddAttrs a t b whereSource

Methods

(!) :: a -> AttributesOf t b -> aSource

Instances

AddAttrs b t c => AddAttrs (a -> b) t c 
(~ (* -> *) t1 t2, ~ * a b) => AddAttrs (TDoc t1 a) t2 b 

class FromTDoc a t tag whereSource

Methods

fromTDoc :: TDoc t tag -> aSource

Instances

FromTDoc a t tag => FromTDoc [a] t tag 
FromTDoc a t tag => FromTDoc (Identity a) t tag 
(~ (* -> *) t1 t2, IsChildOf b a) => FromTDoc (ChildOf t1 a) t2 b 
(~ (* -> *) t1 t2, ~ * a b) => FromTDoc (TDoc t1 a) t2 b 
(Monad m, FromTDoc w t tag, Monoid w, ~ * a ()) => FromTDoc (WriterT w m a) t tag 

type PutM a = Writer [a] ()Source

type Star t node = forall children. ToChildren children t node => children -> TDoc t nodeSource

type Nullary t node = TDoc t nodeSource

type Unary t node = forall child. child `IsChildOf` node => TDoc t child -> TDoc t nodeSource

type Plus t node = forall children child. (child `IsChildOf` node, ToChildren children t node) => TDoc t child -> children -> TDoc t nodeSource

(+++) :: (ToChildren a t tag, ToChildren b t tag) => a -> b -> [ChildOf t tag]Source

(<<) :: a `IsChildOf` b => (c -> TDoc t a) -> c -> PutM (ChildOf t b)Source

This operator is an infix sugar for put paragraph << do ... is equal to put $ paragraph $ do ....

put :: ToChildren children t father => children -> PutM (ChildOf t father)Source

tStar :: t a -> Star t aSource

tNullary :: t a -> Nullary t aSource

tUnary :: t a -> Unary t aSource

tPlus :: t a -> Plus t aSource