module Text.HTML.Moe.Element where import Text.HTML.Moe.Type import Data.Default import Control.Monad.Writer import Prelude hiding (id, span, div) element' :: String -> MoeCombinator' element' x xs u = tell [ def { name = x , attributes = xs , elements = execWriter u } ] element :: (String -> MoeCombinator') -> (String -> MoeCombinator) element x = flip x [] e :: String -> MoeCombinator' e = element' a' :: MoeCombinator' body' :: MoeCombinator' br' :: MoeCombinator' colgroup' :: MoeCombinator' col' :: MoeCombinator' div' :: MoeCombinator' embed' :: MoeCombinator' h1' :: MoeCombinator' h2' :: MoeCombinator' h3' :: MoeCombinator' head' :: MoeCombinator' html' :: MoeCombinator' img' :: MoeCombinator' li' :: MoeCombinator' link' :: MoeCombinator' meta' :: MoeCombinator' object' :: MoeCombinator' ol' :: MoeCombinator' param' :: MoeCombinator' ul' :: MoeCombinator' dl' :: MoeCombinator' dt' :: MoeCombinator' dd' :: MoeCombinator' p' :: MoeCombinator' pre' :: MoeCombinator' script' :: MoeCombinator' span' :: MoeCombinator' style' :: MoeCombinator' table' :: MoeCombinator' td' :: MoeCombinator' th' :: MoeCombinator' title' :: MoeCombinator' tr' :: MoeCombinator' a' = e "a" body' = e "body" br' = e "br" colgroup' = e "colgroup" col' = e "col" div' = e "div" embed' = e "embed" h1' = e "h1" h2' = e "h2" h3' = e "h3" head' = e "head" html' = e "html" img' = e "img" li' = e "li" link' = e "link" meta' = e "meta" object' = e "object" ol' = e "ol" param' = e "param" ul' = e "ul" dl' = e "dl" dt' = e "dt" dd' = e "dd" p' = e "p" pre' = e "pre" script' = e "script" span' = e "span" style' = e "style" table' = e "table" td' = e "td" th' = e "th" title' = e "title" tr' = e "tr" a :: MoeCombinator body :: MoeCombinator br :: MoeCombinator colgroup :: MoeCombinator col :: MoeCombinator div :: MoeCombinator embed :: MoeCombinator h1 :: MoeCombinator h2 :: MoeCombinator h3 :: MoeCombinator head :: MoeCombinator html :: MoeCombinator img :: MoeCombinator li :: MoeCombinator link :: MoeCombinator meta :: MoeCombinator object :: MoeCombinator ol :: MoeCombinator param :: MoeCombinator ul :: MoeCombinator dl :: MoeCombinator dt :: MoeCombinator dd :: MoeCombinator p :: MoeCombinator pre :: MoeCombinator script :: MoeCombinator span :: MoeCombinator style :: MoeCombinator table :: MoeCombinator td :: MoeCombinator th :: MoeCombinator title :: MoeCombinator tr :: MoeCombinator a = a' [] body = body' [] br = br' [] colgroup = colgroup' [] col = col' [] div = div' [] embed = embed' [] h1 = h1' [] h2 = h2' [] h3 = h3' [] head = head' [] html = html' [] img = img' [] li = li' [] link = link' [] meta = meta' [] object = object' [] ol = ol' [] param = param' [] ul = ul' [] dl = dl' [] dt = dt' [] dd = dd' [] p = p' [] pre = pre' [] script = script' [] span = span' [] style = style' [] table = table' [] td = td' [] th = th' [] title = title' [] tr = tr' [] str :: String -> MoeUnit raw :: String -> MoeUnit str x = tell [Data x] raw x = tell [Raw x]