Safe Haskell | None |
---|---|
Language | Haskell98 |
Text.TDoc.Tags
Contents
- data Leaf
- class LeafTag t where
- newtype Url = Url {}
- class LeafTags t where
- char :: LeafTags t => Char -> TDoc t Leaf
- string :: LeafTags t => String -> TDoc t Leaf
- strictByteString :: LeafTags t => ByteString -> TDoc t Leaf
- lazyByteString :: LeafTags t => ByteString -> TDoc t Leaf
- data Paragraph
- class ParagraphTag t where
- paragraph :: ParagraphTag t => Star t Paragraph
- para :: ParagraphTag t => Star t Paragraph
- data Title
- class TitleTag t where
- title :: TitleTag t => Star t Title
- data Br
- class BrTag t where
- br :: BrTag t => Nullary t Br
- data Hr
- class HrTag t where
- hr :: HrTag t => Nullary t Hr
- data Col
- class ColTag t where
- col :: ColTag t => Star t Col
- data HCol
- class HColTag t where
- hcol :: HColTag t => Star t HCol
- data Row
- class RowTag t where
- row :: RowTag t => Star t Row
- data Table
- class TableTag t where
- table :: TableTag t => Star t Table
- data Item
- class ItemTag t where
- item :: ItemTag t => Star t Item
- data UList
- class UListTag t where
- ulist :: UListTag t => Star t UList
- ulistQ :: (UListTag t, ItemTag t, a `IsChildOf` Item) => [TDoc t a] -> TDoc t UList
- data Span
- class ClassAttrTag t => SpanTag t where
- spanDoc :: SpanTag t => Star t Span
- spanDocCA :: SpanTag t => String -> Star t Span
- strong :: SpanTag t => Star t Span
- small :: SpanTag t => Star t Span
- big :: SpanTag t => Star t Span
- italics :: SpanTag t => Star t Span
- sub :: SpanTag t => Star t Span
- sup :: SpanTag t => Star t Span
- tt :: SpanTag t => Star t Span
- bold :: SpanTag t => Star t Span
- data Div a
- class DivTag t where
- div :: DivTag t => Star t (Div a)
- data Subsection
- class SubsectionTag t where
- subsection :: forall a b t. (SubsectionTag t, a `IsChildOf` Span, ToTDoc b t a) => b -> Star t Subsection
- data Section
- class SectionTag t where
- section :: forall a b t. (SectionTag t, a `IsChildOf` Span, ToTDoc b t a) => b -> Star t Section
- data HLink
- class HLinkTag t where
- hlink :: HLinkTag t => String -> Star t HLink
- data Anchor
- class AnchorTag t where
- anchor :: AnchorTag t => Unary t Anchor
- data Image
- class ImageTag t where
- image :: ImageTag t => Nullary t Image
- data Preambule
- class PreambuleTag t where
- preambule :: PreambuleTag t => Star t Preambule
- data Document
- class DocumentTag t where
- document :: DocumentTag t => Star t Document
- data Root
- class RootTag t where
- root :: forall t doc preambule. (RootTag t, ToTDoc preambule t Preambule, ToTDoc doc t Document) => preambule -> doc -> TDoc t Root
- class (AttributeTags t, LeafTags t, ParagraphTag t, TitleTag t, BrTag t, HrTag t, ColTag t, HColTag t, RowTag t, TableTag t, ItemTag t, UListTag t, SpanTag t, DivTag t, SubsectionTag t, SectionTag t, HLinkTag t, AnchorTag t, ImageTag t, PreambuleTag t, DocumentTag t, RootTag t) => Tags t
Documentation
class LeafTags t where Source #
Minimal complete definition
Methods
charTag :: Char -> t Leaf Source #
stringTag :: String -> t Leaf Source #
strictByteStringTag :: ByteString -> t Leaf Source #
lazyByteStringTag :: ByteString -> t Leaf Source #
strictByteString :: LeafTags t => ByteString -> TDoc t Leaf Source #
lazyByteString :: LeafTags t => ByteString -> TDoc t Leaf Source #
class ParagraphTag t where Source #
Minimal complete definition
Methods
paragraphTag :: t Paragraph Source #
Instances
Minimal complete definition
Minimal complete definition
Minimal complete definition
Minimal complete definition
class ClassAttrTag t => SpanTag t where Source #
Minimal complete definition
Instances
IsChildOf b a => IsChildOf b (Div a) Source # | |
IsBlock a => IsBlock (Div a) Source # | |
IsBlockOrInline a => IsBlockOrInline (Div a) Source # | |
IsNode a => IsNode (Div a) Source # | |
(~) * a Section => IsChildOf (Div a) Section Source # | |
(~) * a Document => IsChildOf (Div a) Document Source # | |
(~) * Form a => IsChildOf (Div a) Form Source # | |
Minimal complete definition
data Subsection Source #
Instances
class SubsectionTag t where Source #
Minimal complete definition
Methods
subsectionTag :: a `IsChildOf` Span => TDoc t a -> t Subsection Source #
Instances
subsection :: forall a b t. (SubsectionTag t, a `IsChildOf` Span, ToTDoc b t a) => b -> Star t Subsection Source #
class SectionTag t where Source #
Minimal complete definition
Methods
sectionTag :: a `IsChildOf` Span => TDoc t a -> t Section Source #
Instances
section :: forall a b t. (SectionTag t, a `IsChildOf` Span, ToTDoc b t a) => b -> Star t Section Source #
class PreambuleTag t where Source #
Minimal complete definition
Methods
preambuleTag :: t Preambule Source #
Instances
Instances
class DocumentTag t where Source #
Minimal complete definition
Methods
documentTag :: t Document Source #
Instances
root :: forall t doc preambule. (RootTag t, ToTDoc preambule t Preambule, ToTDoc doc t Document) => preambule -> doc -> TDoc t Root Source #
class (AttributeTags t, LeafTags t, ParagraphTag t, TitleTag t, BrTag t, HrTag t, ColTag t, HColTag t, RowTag t, TableTag t, ItemTag t, UListTag t, SpanTag t, DivTag t, SubsectionTag t, SectionTag t, HLinkTag t, AnchorTag t, ImageTag t, PreambuleTag t, DocumentTag t, RootTag t) => Tags t Source #
Orphan instances
(LeafTags t, (~) * a Leaf) => ToTDoc Char t a Source # | |
(LeafTags t, (~) * a Leaf) => ToTDoc ByteString t a Source # | |
(LeafTags t, (~) * a Leaf) => ToTDoc ByteString t a Source # | |
(LeafTags t, IsChildOf Leaf a) => ToChildren Char t a Source # | |
(LeafTags t, IsChildOf Leaf a) => ToChildren ByteString t a Source # | |
(LeafTags t, IsChildOf Leaf a) => ToChildren ByteString t a Source # | |
(LeafTags t, (~) * b Char, (~) * a Leaf) => ToTDoc [b] t a Source # | |