module Text.HTML.Moe.Element where

import Text.HTML.Moe.Type
import Text.HTML.Moe.Utils
import Data.Default
import Control.Monad.Writer
import Prelude hiding (id, span, div, head, (>), (.), (-))
import MPS.Light ((-))
import Data.DList (singleton, toList)


element' :: String -> MoeCombinator
element' x xs u = tell - singleton - 
  def
    {
      name       = pack - escape x
    , attributes = xs
    , elements   = toList - execWriter - u
    }

e :: String -> MoeCombinator
e = element'
  
element :: (String -> MoeCombinator) -> (String -> MoeCombinator')
element x = flip x []

no_indent_element :: String -> MoeCombinator
no_indent_element x xs u = tell - singleton -
  def
    {
      name       = pack - x
    , attributes = xs
    , elements   = toList - execWriter u
    , indent     = False
    }

ne :: String -> MoeCombinator
ne = no_indent_element

a         :: MoeCombinator
body      :: MoeCombinator
br        :: MoeCombinator
blockquote  :: MoeCombinator
code      :: MoeCombinator
colgroup  :: MoeCombinator
col       :: MoeCombinator
div       :: MoeCombinator
form      :: MoeCombinator
embed     :: MoeCombinator
em        :: MoeCombinator
h1        :: MoeCombinator
h2        :: MoeCombinator
h3        :: MoeCombinator
h4        :: MoeCombinator
h5        :: MoeCombinator
h6        :: MoeCombinator
head      :: MoeCombinator
html      :: MoeCombinator
hr        :: MoeCombinator
img       :: MoeCombinator
input     :: MoeCombinator
label     :: MoeCombinator
li        :: MoeCombinator
link      :: MoeCombinator
meta      :: MoeCombinator
object    :: MoeCombinator
ol        :: MoeCombinator
param     :: MoeCombinator
ul        :: MoeCombinator
dl        :: MoeCombinator
dt        :: MoeCombinator
dd        :: MoeCombinator
option    :: MoeCombinator
p         :: MoeCombinator
pre       :: MoeCombinator
select    :: MoeCombinator
script    :: MoeCombinator
span      :: MoeCombinator
style     :: MoeCombinator
strong    :: MoeCombinator
table     :: MoeCombinator
textarea  :: MoeCombinator
td        :: MoeCombinator
th        :: MoeCombinator
title     :: MoeCombinator
tr        :: MoeCombinator

a'          ::  MoeCombinator'
body'       ::  MoeCombinator'
br'         ::  MoeCombinator'
blockquote' ::  MoeCombinator'
code'       ::  MoeCombinator'
colgroup'   ::  MoeCombinator'
col'        ::  MoeCombinator'
div'        ::  MoeCombinator'
embed'      ::  MoeCombinator'
em'         ::  MoeCombinator'
form'       ::  MoeCombinator'
h1'         ::  MoeCombinator'
h2'         ::  MoeCombinator'
h3'         ::  MoeCombinator'
h4'         ::  MoeCombinator'
h5'         ::  MoeCombinator'
h6'         ::  MoeCombinator'
head'       ::  MoeCombinator'
html'       ::  MoeCombinator'
hr'         ::  MoeCombinator'
img'        ::  MoeCombinator'
input'      ::  MoeCombinator'
label'      ::  MoeCombinator'
li'         ::  MoeCombinator'
link'       ::  MoeCombinator'
meta'       ::  MoeCombinator'
object'     ::  MoeCombinator'
ol'         ::  MoeCombinator'
param'      ::  MoeCombinator'
ul'         ::  MoeCombinator'
dl'         ::  MoeCombinator'
dt'         ::  MoeCombinator'
dd'         ::  MoeCombinator'
option'     ::  MoeCombinator'
p'          ::  MoeCombinator'
pre'        ::  MoeCombinator'
select'     ::  MoeCombinator'
script'     ::  MoeCombinator'
span'       ::  MoeCombinator'
style'      ::  MoeCombinator'
strong'     ::  MoeCombinator'
table'      ::  MoeCombinator'
textarea'   ::  MoeCombinator'
td'         ::  MoeCombinator'
th'         ::  MoeCombinator'
title'      ::  MoeCombinator'
tr'         ::  MoeCombinator'


a          = e "a"
body       = e "body"
br         = e "br"
blockquote  = e "blockquote"
code       = e "code"
colgroup   = e "colgroup"
col        = e "col"
div        = e "div"
embed      = e "embed"
em         = e "em"
form       = e "form"
h1         = e "h1"
h2         = e "h2"
h3         = e "h3"
h4         = e "h4"
h5         = e "h5"
h6         = e "h6"
head       = e "head"
html       = e "html"
hr         = e "hr"
img        = e "img"
input      = e "input"
label      = e "label"
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"
option     = e "option"
p          = e "p"
pre        = e "pre"
select     = e "select"
script     = e "script"
span       = e "span"
style      = e "style"
strong     = e "strong"
table      = e "table"
textarea   = ne "textarea"
td         = e "td"
th         = e "th"
title      = e "title"
tr         = e "tr"





a'         = a          []
body'      = body       []
br'        = br         []
blockquote' = blockquote  []
code'      = code       []
colgroup'  = colgroup   []
col'       = col        []
div'       = div        []
embed'     = embed      []
em'        = em         []
form'      = form       []
h1'        = h1         []
h2'        = h2         []
h3'        = h3         []
h4'        = h4         []
h5'        = h5         []
h6'        = h6         []
head'      = head       []
hr'        = hr         []
html'      = html       []
img'       = img        []
input'     = input      []
label'     = label      []
li'        = li         []
link'      = link       []
meta'      = meta       []
object'    = object     []
ol'        = ol         []
param'     = param      []
ul'        = ul         []
dl'        = dl         []
dt'        = dt         []
dd'        = dd         []
option'    = option     []
p'         = p          []
pre'       = pre        []
select'    = select     []
script'    = script     []
span'      = span       []
style'     = style      []
strong'    = strong     []
table'     = table      []
textarea'  = textarea   []
td'        = td         []
th'        = th         []
title'     = title      []
tr'        = tr         []

str, raw, _pre, prim :: String -> MoeUnit

str x   = tell - singleton - Data (pack - escape x)
raw x   = tell - singleton - Raw  (pack x)
_pre x  = tell - singleton - Pre  (pack - escape x)
prim x  = tell - singleton - Prim (pack x)