> {-# LANGUAGE OverloadedStrings, FlexibleInstances #-}
> -- |
> -- Module      : Text.XHtmlCombinators.Combinators
> -- Copyright   : (c) Alasdair Armstrong 2010
> -- License     : BSD-style
> -- Maintainer  : alasdair.armstrong@googlemail.com
> -- Stability   : experimental
> -- Portability : GHC
>
> module Text.XHtmlCombinators.Combinators where
>
> import Control.Applicative hiding (empty)
> import Data.Sequence (Seq)
> import qualified Data.Sequence as Seq
>
> import Data.Text (Text)
> import qualified Data.Text as T
>
> import Text.XHtmlCombinators.Internal
> -- ================ Character mnemonic entities =========================-->
%HTMLlat1; %HTMLsymbol; %HTMLspecial;
> -- ================== Imported Names ====================================-->
> -- =================== Generic Attributes ===============================-->
> -- =================== Text Elements ====================================-->
> class CData c where
>     cdata :: Text -> c
>
> text :: (Functor t, Monad t, CData c) => Text -> XHtmlT t c
> text = tellS . cdata
>
> newtype InlineContent = Inline { inlineToNode :: Node }
>
> instance Content InlineContent where 
>     toContent = inlineToNode
>
> instance CData InlineContent where
>     cdata = Inline . TextNode
> 
> class Inline c where
>     inline :: Node -> c
>
> instance Inline InlineContent where inline = Inline
> instance Inline FlowContent where inline = Flow
> -- ================== Block level elements ==============================-->
> newtype BlockContent = Block { blockToNode :: Node }
>
> instance Content BlockContent where 
>     toContent = blockToNode
>
> class Block c where
>     block :: Node -> c
>
> instance Block BlockContent where block = Block
> instance Block FlowContent where block = Flow
> newtype FlowContent = Flow { flowToNode :: Node }
>
> instance Content FlowContent where 
>     toContent = flowToNode
>
> instance CData FlowContent where
>     cdata = Flow . TextNode
>
> class Flow c where
>     flow :: Node -> c
>
> instance Flow BlockContent where flow = Block
> instance Flow InlineContent where flow = Inline
> instance Flow FlowContent where flow = Flow
> -- ================== Content models for exclusions =====================-->
> -- ================ Document Structure ==================================-->
> newtype Page = Page { pageToNode :: Node }
>
> newtype TopLevelContent = TopLevel { topLevelToNode :: Node }
>
> instance Content Page where toContent = pageToNode
>
> instance Content TopLevelContent where 
>     toContent = topLevelToNode
> xhtml10strict :: Text
> xhtml10strict = "<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\"\
>                 \ \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">"
>
> doctype :: (Functor t, Monad t) => XHtmlT t Page
> doctype = tellS . Page . TextNode $ xhtml10strict
>
> xmlDec :: (Functor t, Monad t) => XHtmlT t Page
> xmlDec = tellS . Page . TextNode $ "<?xml version=\"1.0\" encoding=\"UTF-8\"?>"
>
> html' :: (Functor t, Monad t)
>       => Bool -- ^ True for XML declaration, false to omit.
>       -> Attrs -> XHtmlT t TopLevelContent -> XHtmlT t Page
> html' useXmlDec attrs x = do
>     if useXmlDec then xmlDec else empty
>     doctype 
>     tellNode Page "html" [Attr "xmlns" "http://www.w3.org/1999/xhtml"] attrs x
>
> html :: (Functor t, Monad t) => Bool -> XHtmlT t TopLevelContent -> XHtmlT t Page
> html useXmlDec = html' useXmlDec []
> -- ================ Document Head =======================================-->
> newtype HeadContent = Head { headToNode :: Node }
>
> instance Content HeadContent where 
>     toContent = headToNode
> head' :: (Functor t, Monad t) => Attrs -> XHtmlT t HeadContent -> XHtmlT t TopLevelContent
> head' = tellNode TopLevel "head" []
>
> head_ :: (Functor t, Monad t) => XHtmlT t HeadContent -> XHtmlT t TopLevelContent
> head_ = head' []
> title' :: (Functor t, Monad t) => Attrs -> Text -> XHtmlT t HeadContent
> title' = tellTextNode Head "title" []
>
> title :: (Functor t, Monad t) => Text -> XHtmlT t HeadContent
> title = title' []
> base' :: (Functor t, Monad t) => Text -> Attrs -> XHtmlT t HeadContent
> base' href = tellEmptyNode Head "base" [Attr "href" href]
>
> base :: (Functor t, Monad t) => Text -> XHtmlT t HeadContent
> base = flip base' []
> meta' :: (Functor t, Monad t) => Text -- ^ Required content attribute.
>       -> Attrs -> XHtmlT t HeadContent
> meta' content = tellEmptyNode Head "meta" [Attr "content" content]
>
> meta :: (Functor t, Monad t) => Text -> XHtmlT t HeadContent
> meta = flip meta' []
> link' :: (Functor t, Monad t) => Attrs -> XHtmlT t HeadContent
> link' = tellEmptyNode Head "link" []
>
> link :: (Functor t, Monad t) => XHtmlT t HeadContent
> link = link' []
> -- ^ 'link' is a bit useless without any attributes, but it's 
> -- included anyway for consistency reasons. As are several
> -- other similar elements.
> style' :: (Functor t, Monad t) => Text -- ^ Required type attribute.
>        -> Attrs -> Text -> XHtmlT t HeadContent
> style' type_ = tellTextNode Head "style" [Attr "type" type_]
>
> style :: (Functor t, Monad t) => Text -> Text -> XHtmlT t HeadContent
> style = flip style' []
> script' :: (Functor t, Monad t) 
>         => Text -- ^ Required type attribute.
>         -> Attrs -> Text -> XHtmlT t HeadContent
> script' type_ = tellTextNode Head "script" [Attr "type" type_]
>
> script :: (Functor t, Monad t) => Text -> Text -> XHtmlT t HeadContent
> script = flip script' []
> noscript' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t BlockContent -> XHtmlT t c
> noscript' = tellNode block "noscript" []
>
> noscript :: (Functor t, Monad t, Block c) => XHtmlT t BlockContent -> XHtmlT t c
> noscript = noscript' []
> -- =================== Document Body ====================================-->
> body' :: (Functor t, Monad t) => Attrs -> XHtmlT t BlockContent -> XHtmlT t TopLevelContent
> body' = tellNode TopLevel "body" []
>
> body :: (Functor t, Monad t) => XHtmlT t BlockContent -> XHtmlT t TopLevelContent
> body = body' [] 
> div' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t FlowContent -> XHtmlT t c
> div' = tellNode block "div" []
> 
> div_ :: (Functor t, Monad t, Block c) => XHtmlT t FlowContent -> XHtmlT t c
> div_ = div' []
> -- =================== Paragraphs =======================================-->
> p' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> p' = tellNode block "p" []
>
> p :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> p = p' []
> -- =================== Headings =========================================-->
> h1' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h1' = tellNode block "h1" []
>
> h1 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h1 = h1' []
> h2' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h2' = tellNode block "h2" []
>
> h2 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h2 = h2' []
> h3' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h3' = tellNode block "h3" []
>
> h3 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h3 = h3' []
> h4' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h4' = tellNode block "h4" []
>
> h4 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h4 = h4' []
> h5' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h5' = tellNode block "h5" []
>
> h5 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h5 = h5' []
> h6' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> h6' = tellNode block "h6" []
>
> h6 :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> h6 = h6' []
> -- =================== Lists ============================================-->
> newtype ListContent = List { listToNode :: Node }
>
> instance Content ListContent where
>     toContent = listToNode
> ul' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t ListContent -> XHtmlT t c
> ul' = tellNode block "ul" []
>
> ul :: (Functor t, Monad t, Block c) => XHtmlT t ListContent -> XHtmlT t c
> ul = ul' []
> ol' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t ListContent -> XHtmlT t c
> ol' = tellNode block "ol" []
>
> ol :: (Functor t, Monad t, Block c) => XHtmlT t ListContent -> XHtmlT t c
> ol = ol' []
> li' :: (Functor t, Monad t) => Attrs -> XHtmlT t FlowContent -> XHtmlT t ListContent
> li' = tellNode List "li" []
>
> li :: (Functor t, Monad t) => XHtmlT t FlowContent -> XHtmlT t ListContent
> li = li' []
> newtype DefinitionListContent = 
>     DefinitionList { definitionListToNode :: Node }
>
> instance Content DefinitionListContent where
>     toContent = definitionListToNode
> dl' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t DefinitionListContent -> XHtmlT t c
> dl' = tellNode block "dl" []
>
> dl :: (Functor t, Monad t, Block c) => XHtmlT t DefinitionListContent -> XHtmlT t c
> dl = dl' []
> dt' :: (Functor t, Monad t) => Attrs -> XHtmlT t InlineContent -> XHtmlT t DefinitionListContent
> dt' = tellNode DefinitionList "dt" []
>
> dt :: (Functor t, Monad t) => XHtmlT t InlineContent -> XHtmlT t DefinitionListContent
> dt = dt' []
> dd' :: (Functor t, Monad t) => Attrs -> XHtmlT t InlineContent -> XHtmlT t DefinitionListContent
> dd' = tellNode DefinitionList "dd" []
>
> dd :: (Functor t, Monad t) => XHtmlT t InlineContent -> XHtmlT t DefinitionListContent
> dd = dd' []
> -- =================== Address ==========================================-->
> address' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> address' = tellNode block "address" []
>
> address :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> address = address' []
> -- =================== Horizontal Rule ==================================-->
> hr' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t c
> hr' = tellEmptyNode block "hr" []
>
> hr :: (Functor t, Monad t, Block c) => XHtmlT t c
> hr = hr' []
> -- =================== Preformatted Text ================================-->
> pre' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> pre' = tellNode block "pre" []
>
> pre :: (Functor t, Monad t, Block c) => XHtmlT t InlineContent -> XHtmlT t c
> pre = pre' []
> -- =================== Block-like Quotes ================================-->
> blockquote' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t BlockContent -> XHtmlT t c
> blockquote' = tellNode block "blockquote" []
>
> blockquote :: (Functor t, Monad t, Block c) => XHtmlT t BlockContent -> XHtmlT t c
> blockquote = blockquote' []
> -- =================== Inserted/Deleted Text ============================-->
> ins' :: (Functor t, Monad t) => (Flow c, Content c) => Attrs -> XHtmlT t c -> XHtmlT t c
> ins' = tellNode flow "ins" []
>
> ins :: (Functor t, Monad t) => (Flow c, Content c) => XHtmlT t c -> XHtmlT t c
> ins = ins' []
> del' :: (Functor t, Monad t) => (Flow c, Content c) => Attrs -> XHtmlT t c -> XHtmlT t c
> del' = tellNode flow "del" []
>
> del :: (Functor t, Monad t) => (Flow c, Content c) => XHtmlT t c -> XHtmlT t c
> del = del' []
> -- ================== The Anchor Element ================================-->
> a' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> a' = tellNode inline "a" []
>
> a :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> a = a' []
> -- ===================== Inline Elements ================================-->
> span' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> span' = tellNode inline "span" []
>
> span_ :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> span_ = span' []
> bdo' :: (Functor t, Monad t, Inline c) 
>      => Text -- ^ Required language direction code.
>      -> Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> bdo' dir = tellNode inline "bdo" [Attr "dir" dir]
>
> bdo :: (Functor t, Monad t, Inline c) => Text -> XHtmlT t InlineContent -> XHtmlT t c
> bdo = flip bdo' []
> br' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t c
> br' = tellEmptyNode inline "br" []
>
> br :: (Functor t, Monad t, Inline c) => XHtmlT t c
> br = br' []
> em' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> em' = tellNode inline "em" []
>
> em :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> em = em' []
> strong' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> strong' = tellNode inline "strong" []
>
> strong :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> strong = strong' []
> dfn' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> dfn' = tellNode inline "dfn" []
>
> dfn :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> dfn = dfn' []
> code' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> code' = tellNode inline "code" []
>
> code :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> code = code' []
> samp' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> samp' = tellNode inline "samp" []
>
> samp :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> samp = samp' []
> kbd' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> kbd' = tellNode inline "kbd" []
>
> kbd :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> kbd = kbd' []
> var' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> var' = tellNode inline "var" []
>
> var :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> var = var' []
> cite' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> cite' = tellNode inline "cite" []
>
> cite :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> cite = cite' []
> abbr' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> abbr' = tellNode inline "abbr" []
>
> abbr :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> abbr = abbr' []
> acronym' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> acronym' = tellNode inline "acronym" []
>
> acronym :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> acronym = acronym' []
> q' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> q' = tellNode inline "q" []
>
> q :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> q = q' []
> sub' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> sub' = tellNode inline "sub" []
>
> sub :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> sub = sub' []
> sup' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> sup' = tellNode inline "sup" []
>
> sup :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> sup = sup' []
> tt' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> tt' = tellNode inline "tt" []
>
> tt :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> tt = tt' []
> i' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> i' = tellNode inline "i" []
>
> i :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> i = i' []
> b' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> b' = tellNode inline "b" []
>
> b :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> b = b' []
> big' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> big' = tellNode inline "big" []
>
> big :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> big = big' []
> small' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> small' = tellNode inline "small" []
>
> small :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> small = small' []
> -- ==================== Object ======================================-->
> newtype ObjectContent = Object { objectToNode :: Node }
>
> instance Content ObjectContent where 
>     toContent = objectToNode
>
> instance Flow ObjectContent where flow = Object
> instance Inline ObjectContent where inline = Object
> instance Block ObjectContent where block = Object
> object' :: (Functor t, Monad t, Flow c) => Attrs -> XHtmlT t ObjectContent -> XHtmlT t c
> object' = tellNode flow "object" []
>
> object :: (Functor t, Monad t, Flow c) => XHtmlT t ObjectContent -> XHtmlT t c
> object = object' []
> param' :: (Functor t, Monad t) => Attrs -> XHtmlT t ObjectContent
> param' = tellEmptyNode Object "param" []
>
> param :: (Functor t, Monad t) => XHtmlT t ObjectContent
> param = param' []
> -- =================== Images ===========================================-->
> img' :: (Functor t, Monad t, Flow c) 
>      => Text -- ^ Required src attribute. 
>      -> Text -- ^ Required alt attribute.
>      -> Attrs -> XHtmlT t c
> img' src alt = tellEmptyNode flow "img" []
>
> img :: (Functor t, Monad t, Flow c) => Text -> Text -> XHtmlT t c
> img src alt = img' src alt [Attr "src" src, Attr "alt" alt]
> -- ================== Client-side image maps ============================-->
> newtype MapContent = Map { mapToNode :: Node }
>
> instance Content MapContent where 
>     toContent = mapToNode
>
> instance Flow MapContent where flow = Map
> instance Inline MapContent where inline = Map
> instance Block MapContent where block = Map
> map' :: (Functor t, Monad t, Flow c) 
>      => Text -- ^ Required id attribute. 
>      -> Attrs -> XHtmlT t MapContent -> XHtmlT t c
> map' id = tellNode flow "map" [Attr "id" id]
>
> map_ :: (Functor t, Monad t, Flow c) => Text -> XHtmlT t MapContent -> XHtmlT t c
> map_ = flip map' []
> area' :: (Functor t, Monad t) => Text -- ^ Required alt attribute.
>       -> Attrs -> XHtmlT t MapContent
> area' alt = tellEmptyNode Map "area" [Attr "alt" alt]
>
> area :: (Functor t, Monad t) => Text -> XHtmlT t MapContent
> area = flip area' []
> -- ================ Forms ===============================================-->
> form' :: (Functor t, Monad t, Block c)
>       => Text -- ^ Required action attribute. 
>       -> Attrs -> XHtmlT t FlowContent -> XHtmlT t c
> form' action = tellNode block "form" [Attr "action" action]
>
> form :: (Functor t, Monad t, Block c) => Text -> XHtmlT t FlowContent -> XHtmlT t c
> form = flip form' []
> label' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t InlineContent -> XHtmlT t c
> label' = tellNode inline "label" []
>
> label :: (Functor t, Monad t, Inline c) => XHtmlT t InlineContent -> XHtmlT t c
> label = label' []
> input' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t c
> input' = tellEmptyNode inline "input" []
>
> input :: (Functor t, Monad t, Inline c) => XHtmlT t c
> input = input' []
> newtype OptionContent = Option { optionToNode :: Node }
>
> instance Content OptionContent where 
>     toContent = optionToNode
>
> select' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t OptionContent -> XHtmlT t c 
> select' = tellNode inline "select" []
>
> select :: (Functor t, Monad t, Inline c) => XHtmlT t OptionContent -> XHtmlT t c
> select = select' []
> optgroup' :: (Functor t, Monad t) => Text -- ^ Required label attribute. 
>           -> Attrs -> XHtmlT t OptionContent -> XHtmlT t OptionContent
> optgroup' label = tellNode Option "optgroup" [Attr "label" label]
>
> optgroup :: (Functor t, Monad t) => Text -> XHtmlT t OptionContent -> XHtmlT t OptionContent
> optgroup = flip optgroup' []
> option' :: (Functor t, Monad t) => Attrs -> Text -> XHtmlT t OptionContent
> option' = tellTextNode Option "option" []
>
> option :: (Functor t, Monad t) => Text -> XHtmlT t OptionContent
> option = option' []
> textarea' :: (Functor t, Monad t, Inline c)
>           => Int -- ^ Required rows attribute.
>           -> Int -- ^ Required cols attribute.
>           -> Attrs -> Text -> XHtmlT t c
> textarea' rows cols = tellTextNode inline "textarea" 
>                           [ Attr "rows" (T.pack (show rows))
>                           , Attr "cols" (T.pack (show cols))
>                           ]
> 
> textarea :: (Functor t, Monad t, Inline c) => Int -> Int -> Text -> XHtmlT t c
> textarea  rows cols = textarea' rows cols []
> newtype FieldSetContent = FieldSet { fieldSetToNode :: Node }
>
> instance Content FieldSetContent where 
>     toContent = fieldSetToNode
>
> instance Flow FieldSetContent where flow = FieldSet
> instance Inline FieldSetContent where inline = FieldSet
> instance Block FieldSetContent where block = FieldSet
> fieldset' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t FieldSetContent -> XHtmlT t c
> fieldset' = tellNode block "fieldset" []
>
> fieldset :: (Functor t, Monad t, Block c) => XHtmlT t FieldSetContent -> XHtmlT t c
> fieldset = fieldset' []
> legend' :: (Functor t, Monad t) => Attrs -> XHtmlT t InlineContent -> XHtmlT t FieldSetContent 
> legend' = tellNode FieldSet "legend" []
>
> legend :: (Functor t, Monad t) => XHtmlT t InlineContent -> XHtmlT t FieldSetContent
> legend = legend' []
> button' :: (Functor t, Monad t, Inline c) => Attrs -> XHtmlT t FlowContent -> XHtmlT t c
> button' = tellNode inline "button" []
>
> button :: (Functor t, Monad t, Inline c) => XHtmlT t FlowContent -> XHtmlT t c
> button = button' []
> -- ======================= Tables =======================================-->
> newtype Table1Content = Table1 { table1ToNode :: Node }
>
> instance Content Table1Content where 
>     toContent = table1ToNode
> newtype Table2Content = Table2 { table2ToNode :: Node }
>
> instance Content Table2Content where 
>     toContent = table2ToNode
>
> newtype Table3Content = Table3 { table3ToNode :: Node }
>
> instance Content Table3Content where 
>     toContent = table3ToNode
>
> newtype TableColContent = TableCol { tableColToNode :: Node }
>
> instance Content TableColContent where 
>     toContent = tableColToNode
> table' :: (Functor t, Monad t, Block c) => Attrs -> XHtmlT t Table1Content -> XHtmlT t c
> table' = tellNode block "table" []
> 
> table :: (Functor t, Monad t, Block c) => XHtmlT t Table1Content -> XHtmlT t c
> table = table' []
> caption' :: (Functor t, Monad t) => Attrs -> XHtmlT t InlineContent -> XHtmlT t Table1Content
> caption' = tellNode Table1 "caption" []
>
> caption :: (Functor t, Monad t) => XHtmlT t InlineContent -> XHtmlT t Table1Content
> caption = caption' []
> thead' :: (Functor t, Monad t) => Attrs -> XHtmlT t Table2Content -> XHtmlT t Table1Content
> thead' = tellNode Table1 "thead" []
>
> thead :: (Functor t, Monad t) => XHtmlT t Table2Content -> XHtmlT t Table1Content
> thead = thead' []
> tfoot' :: (Functor t, Monad t) => Attrs -> XHtmlT t Table2Content -> XHtmlT t Table1Content
> tfoot' = tellNode Table1 "tfoot" []
>
> tfoot :: (Functor t, Monad t) => XHtmlT t Table2Content -> XHtmlT t Table1Content
> tfoot = tfoot' []
> tbody' :: (Functor t, Monad t) => Attrs -> XHtmlT t Table2Content -> XHtmlT t Table1Content
> tbody' = tellNode Table1 "tbody" []
>
> tbody :: (Functor t, Monad t) => XHtmlT t Table2Content -> XHtmlT t Table1Content
> tbody = tbody' []
> colgroup' :: (Functor t, Monad t) => Attrs -> XHtmlT t TableColContent -> XHtmlT t Table1Content
> colgroup' = tellNode Table1 "colgroup" []
>
> colgroup :: (Functor t, Monad t) => XHtmlT t TableColContent -> XHtmlT t Table1Content
> colgroup = colgroup' []
> col' :: (Functor t, Monad t) => Attrs -> XHtmlT t TableColContent
> col' = tellEmptyNode TableCol "col" []
>
> col :: (Functor t, Monad t) => XHtmlT t TableColContent
> col = col' []
> tr' :: (Functor t, Monad t) => Attrs -> XHtmlT t Table3Content -> XHtmlT t Table2Content
> tr' = tellNode Table2 "tr" []
> 
> tr :: (Functor t, Monad t) => XHtmlT t Table3Content -> XHtmlT t Table2Content
> tr = tr' []
> th' :: (Functor t, Monad t) => Attrs -> XHtmlT t FlowContent -> XHtmlT t Table3Content
> th' = tellNode Table3 "th" []
>
> th :: (Functor t, Monad t) => XHtmlT t FlowContent -> XHtmlT t Table3Content
> th = th' []
> td' :: (Functor t, Monad t) => Attrs -> XHtmlT t FlowContent -> XHtmlT t Table3Content
> td' = tellNode Table3 "td" []
>
> td :: (Functor t, Monad t) => XHtmlT t FlowContent -> XHtmlT t Table3Content
> td = td' []