{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS -fno-warn-type-defaults #-}
module Lucid.Html5 where
import Lucid.Base
import Data.Monoid
import Data.Text (Text, unwords)
doctype_ :: Applicative m => HtmlT m ()
doctype_ :: HtmlT m ()
doctype_ = Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"!DOCTYPE HTML"
doctypehtml_ :: Applicative m => HtmlT m a -> HtmlT m a
doctypehtml_ :: HtmlT m a -> HtmlT m a
doctypehtml_ HtmlT m a
m = HtmlT m ()
forall (m :: * -> *). Applicative m => HtmlT m ()
doctype_ HtmlT m () -> HtmlT m a -> HtmlT m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> HtmlT m a -> HtmlT m a
forall arg result. Term arg result => arg -> result
html_ HtmlT m a
m
a_ :: Term arg result => arg -> result
a_ :: arg -> result
a_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"a"
abbr_ :: Term arg result => arg -> result
abbr_ :: arg -> result
abbr_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"abbr"
address_ :: Term arg result => arg -> result
address_ :: arg -> result
address_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"address"
area_ :: Applicative m => [Attribute] -> HtmlT m ()
area_ :: [Attribute] -> HtmlT m ()
area_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"area")
article_ :: Term arg result => arg -> result
article_ :: arg -> result
article_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"article"
aside_ :: Term arg result => arg -> result
aside_ :: arg -> result
aside_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"aside"
audio_ :: Term arg result => arg -> result
audio_ :: arg -> result
audio_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"audio"
b_ :: Term arg result => arg -> result
b_ :: arg -> result
b_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"b"
base_ :: Applicative m => [Attribute] -> HtmlT m ()
base_ :: [Attribute] -> HtmlT m ()
base_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"base")
bdo_ :: Term arg result => arg -> result
bdo_ :: arg -> result
bdo_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"bdo"
blockquote_ :: Term arg result => arg -> result
blockquote_ :: arg -> result
blockquote_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"blockquote"
body_ :: Term arg result => arg -> result
body_ :: arg -> result
body_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"body"
br_ :: Applicative m => [Attribute] -> HtmlT m ()
br_ :: [Attribute] -> HtmlT m ()
br_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"br")
button_ :: Term arg result => arg -> result
button_ :: arg -> result
button_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"button"
canvas_ :: Term arg result => arg -> result
canvas_ :: arg -> result
canvas_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"canvas"
caption_ :: Term arg result => arg -> result
caption_ :: arg -> result
caption_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"caption"
cite_ :: Term arg result => arg -> result
cite_ :: arg -> result
cite_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"cite"
code_ :: Term arg result => arg -> result
code_ :: arg -> result
code_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"code"
col_ :: Applicative m => [Attribute] -> HtmlT m ()
col_ :: [Attribute] -> HtmlT m ()
col_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"col")
colgroup_ :: Term arg result => arg -> result
colgroup_ :: arg -> result
colgroup_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"colgroup"
command_ :: Term arg result => arg -> result
command_ :: arg -> result
command_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"command"
datalist_ :: Term arg result => arg -> result
datalist_ :: arg -> result
datalist_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"datalist"
dd_ :: Term arg result => arg -> result
dd_ :: arg -> result
dd_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"dd"
del_ :: Term arg result => arg -> result
del_ :: arg -> result
del_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"del"
details_ :: Term arg result => arg -> result
details_ :: arg -> result
details_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"details"
dfn_ :: Term arg result => arg -> result
dfn_ :: arg -> result
dfn_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"dfn"
div_ :: Term arg result => arg -> result
div_ :: arg -> result
div_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"div"
dl_ :: Term arg result => arg -> result
dl_ :: arg -> result
dl_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"dl"
dt_ :: Term arg result => arg -> result
dt_ :: arg -> result
dt_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"dt"
em_ :: Term arg result => arg -> result
em_ :: arg -> result
em_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"em"
embed_ :: Applicative m => [Attribute] -> HtmlT m ()
embed_ :: [Attribute] -> HtmlT m ()
embed_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"embed")
fieldset_ :: Term arg result => arg -> result
fieldset_ :: arg -> result
fieldset_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"fieldset"
figcaption_ :: Term arg result => arg -> result
figcaption_ :: arg -> result
figcaption_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"figcaption"
figure_ :: Term arg result => arg -> result
figure_ :: arg -> result
figure_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"figure"
footer_ :: Term arg result => arg -> result
= Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"footer"
form_ :: Term arg result => arg -> result
form_ :: arg -> result
form_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"form"
h1_ :: Term arg result => arg -> result
h1_ :: arg -> result
h1_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h1"
h2_ :: Term arg result => arg -> result
h2_ :: arg -> result
h2_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h2"
h3_ :: Term arg result => arg -> result
h3_ :: arg -> result
h3_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h3"
h4_ :: Term arg result => arg -> result
h4_ :: arg -> result
h4_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h4"
h5_ :: Term arg result => arg -> result
h5_ :: arg -> result
h5_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h5"
h6_ :: Term arg result => arg -> result
h6_ :: arg -> result
h6_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"h6"
head_ :: Term arg result => arg -> result
head_ :: arg -> result
head_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"head"
header_ :: Term arg result => arg -> result
= Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"header"
hgroup_ :: Term arg result => arg -> result
hgroup_ :: arg -> result
hgroup_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"hgroup"
hr_ :: Applicative m => [Attribute] -> HtmlT m ()
hr_ :: [Attribute] -> HtmlT m ()
hr_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"hr")
html_ :: Term arg result => arg -> result
html_ :: arg -> result
html_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"html"
i_ :: Term arg result => arg -> result
i_ :: arg -> result
i_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"i"
iframe_ :: Term arg result => arg -> result
iframe_ :: arg -> result
iframe_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"iframe"
img_ :: Applicative m => [Attribute] -> HtmlT m ()
img_ :: [Attribute] -> HtmlT m ()
img_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"img")
input_ :: Applicative m => [Attribute] -> HtmlT m ()
input_ :: [Attribute] -> HtmlT m ()
input_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"input")
ins_ :: Term arg result => arg -> result
ins_ :: arg -> result
ins_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"ins"
kbd_ :: Term arg result => arg -> result
kbd_ :: arg -> result
kbd_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"kbd"
keygen_ :: Applicative m => [Attribute] -> HtmlT m ()
keygen_ :: [Attribute] -> HtmlT m ()
keygen_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"keygen")
label_ :: Term arg result => arg -> result
label_ :: arg -> result
label_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"label"
legend_ :: Term arg result => arg -> result
legend_ :: arg -> result
legend_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"legend"
li_ :: Term arg result => arg -> result
li_ :: arg -> result
li_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"li"
link_ :: Applicative m => [Attribute] -> HtmlT m ()
link_ :: [Attribute] -> HtmlT m ()
link_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"link")
map_ :: Term arg result => arg -> result
map_ :: arg -> result
map_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"map"
main_ :: Term arg result => arg -> result
main_ :: arg -> result
main_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"main"
mark_ :: Term arg result => arg -> result
mark_ :: arg -> result
mark_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"mark"
menu_ :: Term arg result => arg -> result
= Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"menu"
menuitem_ :: Applicative m => [Attribute] -> HtmlT m ()
= HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"menuitem")
meta_ :: Applicative m => [Attribute] -> HtmlT m ()
meta_ :: [Attribute] -> HtmlT m ()
meta_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"meta")
meter_ :: Term arg result => arg -> result
meter_ :: arg -> result
meter_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"meter"
nav_ :: Term arg result => arg -> result
nav_ :: arg -> result
nav_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"nav"
noscript_ :: Term arg result => arg -> result
noscript_ :: arg -> result
noscript_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"noscript"
object_ :: Term arg result => arg -> result
object_ :: arg -> result
object_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"object"
ol_ :: Term arg result => arg -> result
ol_ :: arg -> result
ol_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"ol"
optgroup_ :: Term arg result => arg -> result
optgroup_ :: arg -> result
optgroup_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"optgroup"
option_ :: Term arg result => arg -> result
option_ :: arg -> result
option_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"option"
output_ :: Term arg result => arg -> result
output_ :: arg -> result
output_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"output"
p_ :: Term arg result => arg -> result
p_ :: arg -> result
p_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"p"
param_ :: Applicative m => [Attribute] -> HtmlT m ()
param_ :: [Attribute] -> HtmlT m ()
param_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"param")
svg_ :: Term arg result => arg -> result
svg_ :: arg -> result
svg_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"svg"
pre_ :: Term arg result => arg -> result
pre_ :: arg -> result
pre_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"pre"
progress_ :: Term arg result => arg -> result
progress_ :: arg -> result
progress_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"progress"
q_ :: Term arg result => arg -> result
q_ :: arg -> result
q_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"q"
rp_ :: Term arg result => arg -> result
rp_ :: arg -> result
rp_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"rp"
rt_ :: Term arg result => arg -> result
rt_ :: arg -> result
rt_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"rt"
ruby_ :: Term arg result => arg -> result
ruby_ :: arg -> result
ruby_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"ruby"
samp_ :: Term arg result => arg -> result
samp_ :: arg -> result
samp_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"samp"
script_ :: TermRaw arg result => arg -> result
script_ :: arg -> result
script_ = Text -> arg -> result
forall arg result. TermRaw arg result => Text -> arg -> result
termRaw Text
"script"
section_ :: Term arg result => arg -> result
section_ :: arg -> result
section_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"section"
select_ :: Term arg result => arg -> result
select_ :: arg -> result
select_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"select"
small_ :: Term arg result => arg -> result
small_ :: arg -> result
small_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"small"
source_ :: Applicative m => [Attribute] -> HtmlT m ()
source_ :: [Attribute] -> HtmlT m ()
source_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"source")
span_ :: Term arg result => arg -> result
span_ :: arg -> result
span_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"span"
strong_ :: Term arg result => arg -> result
strong_ :: arg -> result
strong_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"strong"
style_ :: TermRaw arg result => arg -> result
style_ :: arg -> result
style_ = Text -> arg -> result
forall arg result. TermRaw arg result => Text -> arg -> result
termRaw Text
"style"
sub_ :: Term arg result => arg -> result
sub_ :: arg -> result
sub_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"sub"
summary_ :: Term arg result => arg -> result
summary_ :: arg -> result
summary_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"summary"
sup_ :: Term arg result => arg -> result
sup_ :: arg -> result
sup_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"sup"
table_ :: Term arg result => arg -> result
table_ :: arg -> result
table_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"table"
tbody_ :: Term arg result => arg -> result
tbody_ :: arg -> result
tbody_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"tbody"
td_ :: Term arg result => arg -> result
td_ :: arg -> result
td_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"td"
textarea_ :: Term arg result => arg -> result
textarea_ :: arg -> result
textarea_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"textarea"
tfoot_ :: Term arg result => arg -> result
= Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"tfoot"
th_ :: Term arg result => arg -> result
th_ :: arg -> result
th_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"th"
template_ :: Term arg result => arg -> result
template_ :: arg -> result
template_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"template"
thead_ :: Term arg result => arg -> result
thead_ :: arg -> result
thead_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"thead"
time_ :: Term arg result => arg -> result
time_ :: arg -> result
time_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"time"
title_ :: Term arg result => arg -> result
title_ :: arg -> result
title_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"title"
tr_ :: Term arg result => arg -> result
tr_ :: arg -> result
tr_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"tr"
track_ :: Applicative m => [Attribute] -> HtmlT m ()
track_ :: [Attribute] -> HtmlT m ()
track_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"track")
ul_ :: Term arg result => arg -> result
ul_ :: arg -> result
ul_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"ul"
var_ :: Term arg result => arg -> result
var_ :: arg -> result
var_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"var"
video_ :: Term arg result => arg -> result
video_ :: arg -> result
video_ = Text -> arg -> result
forall arg result. Term arg result => Text -> arg -> result
term Text
"video"
wbr_ :: Applicative m => [Attribute] -> HtmlT m ()
wbr_ :: [Attribute] -> HtmlT m ()
wbr_ = HtmlT m () -> [Attribute] -> HtmlT m ()
forall a. With a => a -> [Attribute] -> a
with (Text -> HtmlT m ()
forall (m :: * -> *). Applicative m => Text -> HtmlT m ()
makeElementNoEnd Text
"wbr")
accept_ :: Text -> Attribute
accept_ :: Text -> Attribute
accept_ = Text -> Text -> Attribute
makeAttribute Text
"accept"
acceptCharset_ :: Text -> Attribute
acceptCharset_ :: Text -> Attribute
acceptCharset_ = Text -> Text -> Attribute
makeAttribute Text
"accept-charset"
accesskey_ :: Text -> Attribute
accesskey_ :: Text -> Attribute
accesskey_ = Text -> Text -> Attribute
makeAttribute Text
"accesskey"
action_ :: Text -> Attribute
action_ :: Text -> Attribute
action_ = Text -> Text -> Attribute
makeAttribute Text
"action"
alt_ :: Text -> Attribute
alt_ :: Text -> Attribute
alt_ = Text -> Text -> Attribute
makeAttribute Text
"alt"
async_ :: Text -> Attribute
async_ :: Text -> Attribute
async_ = Text -> Text -> Attribute
makeAttribute Text
"async"
autocomplete_ :: Text -> Attribute
autocomplete_ :: Text -> Attribute
autocomplete_ = Text -> Text -> Attribute
makeAttribute Text
"autocomplete"
autofocus_ :: Attribute
autofocus_ :: Attribute
autofocus_ = Text -> Text -> Attribute
makeAttribute Text
"autofocus" Text
forall a. Monoid a => a
mempty
autoplay_ :: Text -> Attribute
autoplay_ :: Text -> Attribute
autoplay_ = Text -> Text -> Attribute
makeAttribute Text
"autoplay"
challenge_ :: Text -> Attribute
challenge_ :: Text -> Attribute
challenge_ = Text -> Text -> Attribute
makeAttribute Text
"challenge"
charset_ :: Text -> Attribute
charset_ :: Text -> Attribute
charset_ = Text -> Text -> Attribute
makeAttribute Text
"charset"
checked_ :: Attribute
checked_ :: Attribute
checked_ = Text -> Text -> Attribute
makeAttribute Text
"checked" Text
forall a. Monoid a => a
mempty
class_ :: Text -> Attribute
class_ :: Text -> Attribute
class_ = Text -> Text -> Attribute
makeAttribute Text
"class"
classes_ :: [Text] -> Attribute
classes_ :: [Text] -> Attribute
classes_ = Text -> Text -> Attribute
makeAttribute Text
"class" (Text -> Attribute) -> ([Text] -> Text) -> [Text] -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
Data.Text.unwords
cols_ :: Text -> Attribute
cols_ :: Text -> Attribute
cols_ = Text -> Text -> Attribute
makeAttribute Text
"cols"
colspan_ :: Text -> Attribute
colspan_ :: Text -> Attribute
colspan_ = Text -> Text -> Attribute
makeAttribute Text
"colspan"
content_ :: Text -> Attribute
content_ :: Text -> Attribute
content_ = Text -> Text -> Attribute
makeAttribute Text
"content"
contenteditable_ :: Text -> Attribute
contenteditable_ :: Text -> Attribute
contenteditable_ = Text -> Text -> Attribute
makeAttribute Text
"contenteditable"
contextmenu_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"contextmenu"
controls_ :: Text -> Attribute
controls_ :: Text -> Attribute
controls_ = Text -> Text -> Attribute
makeAttribute Text
"controls"
coords_ :: Text -> Attribute
coords_ :: Text -> Attribute
coords_ = Text -> Text -> Attribute
makeAttribute Text
"coords"
crossorigin_ :: Text -> Attribute
crossorigin_ :: Text -> Attribute
crossorigin_ = Text -> Text -> Attribute
makeAttribute Text
"crossorigin"
data_ :: Text -> Text -> Attribute
data_ :: Text -> Text -> Attribute
data_ Text
name = Text -> Text -> Attribute
makeAttribute (Text
"data-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name)
datetime_ :: Text -> Attribute
datetime_ :: Text -> Attribute
datetime_ = Text -> Text -> Attribute
makeAttribute Text
"datetime"
defer_ :: Text -> Attribute
defer_ :: Text -> Attribute
defer_ = Text -> Text -> Attribute
makeAttribute Text
"defer"
dir_ :: Text -> Attribute
dir_ :: Text -> Attribute
dir_ = Text -> Text -> Attribute
makeAttribute Text
"dir"
disabled_ :: Text -> Attribute
disabled_ :: Text -> Attribute
disabled_ = Text -> Text -> Attribute
makeAttribute Text
"disabled"
download_ :: Text -> Attribute
download_ :: Text -> Attribute
download_ = Text -> Text -> Attribute
makeAttribute Text
"download"
draggable_ :: Text -> Attribute
draggable_ :: Text -> Attribute
draggable_ = Text -> Text -> Attribute
makeAttribute Text
"draggable"
enctype_ :: Text -> Attribute
enctype_ :: Text -> Attribute
enctype_ = Text -> Text -> Attribute
makeAttribute Text
"enctype"
for_ :: Text -> Attribute
for_ :: Text -> Attribute
for_ = Text -> Text -> Attribute
makeAttribute Text
"for"
formaction_ :: Text -> Attribute
formaction_ :: Text -> Attribute
formaction_ = Text -> Text -> Attribute
makeAttribute Text
"formaction"
formenctype_ :: Text -> Attribute
formenctype_ :: Text -> Attribute
formenctype_ = Text -> Text -> Attribute
makeAttribute Text
"formenctype"
formmethod_ :: Text -> Attribute
formmethod_ :: Text -> Attribute
formmethod_ = Text -> Text -> Attribute
makeAttribute Text
"formmethod"
formnovalidate_ :: Text -> Attribute
formnovalidate_ :: Text -> Attribute
formnovalidate_ = Text -> Text -> Attribute
makeAttribute Text
"formnovalidate"
formtarget_ :: Text -> Attribute
formtarget_ :: Text -> Attribute
formtarget_ = Text -> Text -> Attribute
makeAttribute Text
"formtarget"
headers_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"headers"
height_ :: Text -> Attribute
height_ :: Text -> Attribute
height_ = Text -> Text -> Attribute
makeAttribute Text
"height"
hidden_ :: Text -> Attribute
hidden_ :: Text -> Attribute
hidden_ = Text -> Text -> Attribute
makeAttribute Text
"hidden"
high_ :: Text -> Attribute
high_ :: Text -> Attribute
high_ = Text -> Text -> Attribute
makeAttribute Text
"high"
href_ :: Text -> Attribute
href_ :: Text -> Attribute
href_ = Text -> Text -> Attribute
makeAttribute Text
"href"
hreflang_ :: Text -> Attribute
hreflang_ :: Text -> Attribute
hreflang_ = Text -> Text -> Attribute
makeAttribute Text
"hreflang"
httpEquiv_ :: Text -> Attribute
httpEquiv_ :: Text -> Attribute
httpEquiv_ = Text -> Text -> Attribute
makeAttribute Text
"http-equiv"
icon_ :: Text -> Attribute
icon_ :: Text -> Attribute
icon_ = Text -> Text -> Attribute
makeAttribute Text
"icon"
id_ :: Text -> Attribute
id_ :: Text -> Attribute
id_ = Text -> Text -> Attribute
makeAttribute Text
"id"
integrity_ :: Text -> Attribute
integrity_ :: Text -> Attribute
integrity_ = Text -> Text -> Attribute
makeAttribute Text
"integrity"
ismap_ :: Text -> Attribute
ismap_ :: Text -> Attribute
ismap_ = Text -> Text -> Attribute
makeAttribute Text
"ismap"
item_ :: Text -> Attribute
item_ :: Text -> Attribute
item_ = Text -> Text -> Attribute
makeAttribute Text
"item"
itemprop_ :: Text -> Attribute
itemprop_ :: Text -> Attribute
itemprop_ = Text -> Text -> Attribute
makeAttribute Text
"itemprop"
keytype_ :: Text -> Attribute
keytype_ :: Text -> Attribute
keytype_ = Text -> Text -> Attribute
makeAttribute Text
"keytype"
lang_ :: Text -> Attribute
lang_ :: Text -> Attribute
lang_ = Text -> Text -> Attribute
makeAttribute Text
"lang"
list_ :: Text -> Attribute
list_ :: Text -> Attribute
list_ = Text -> Text -> Attribute
makeAttribute Text
"list"
loop_ :: Text -> Attribute
loop_ :: Text -> Attribute
loop_ = Text -> Text -> Attribute
makeAttribute Text
"loop"
low_ :: Text -> Attribute
low_ :: Text -> Attribute
low_ = Text -> Text -> Attribute
makeAttribute Text
"low"
manifest_ :: Text -> Attribute
manifest_ :: Text -> Attribute
manifest_ = Text -> Text -> Attribute
makeAttribute Text
"manifest"
max_ :: Text -> Attribute
max_ :: Text -> Attribute
max_ = Text -> Text -> Attribute
makeAttribute Text
"max"
maxlength_ :: Text -> Attribute
maxlength_ :: Text -> Attribute
maxlength_ = Text -> Text -> Attribute
makeAttribute Text
"maxlength"
media_ :: Text -> Attribute
media_ :: Text -> Attribute
media_ = Text -> Text -> Attribute
makeAttribute Text
"media"
method_ :: Text -> Attribute
method_ :: Text -> Attribute
method_ = Text -> Text -> Attribute
makeAttribute Text
"method"
min_ :: Text -> Attribute
min_ :: Text -> Attribute
min_ = Text -> Text -> Attribute
makeAttribute Text
"min"
multiple_ :: Text -> Attribute
multiple_ :: Text -> Attribute
multiple_ = Text -> Text -> Attribute
makeAttribute Text
"multiple"
name_ :: Text -> Attribute
name_ :: Text -> Attribute
name_ = Text -> Text -> Attribute
makeAttribute Text
"name"
novalidate_ :: Text -> Attribute
novalidate_ :: Text -> Attribute
novalidate_ = Text -> Text -> Attribute
makeAttribute Text
"novalidate"
onbeforeonload_ :: Text -> Attribute
onbeforeonload_ :: Text -> Attribute
onbeforeonload_ = Text -> Text -> Attribute
makeAttribute Text
"onbeforeonload"
onbeforeprint_ :: Text -> Attribute
onbeforeprint_ :: Text -> Attribute
onbeforeprint_ = Text -> Text -> Attribute
makeAttribute Text
"onbeforeprint"
onblur_ :: Text -> Attribute
onblur_ :: Text -> Attribute
onblur_ = Text -> Text -> Attribute
makeAttribute Text
"onblur"
oncanplay_ :: Text -> Attribute
oncanplay_ :: Text -> Attribute
oncanplay_ = Text -> Text -> Attribute
makeAttribute Text
"oncanplay"
oncanplaythrough_ :: Text -> Attribute
oncanplaythrough_ :: Text -> Attribute
oncanplaythrough_ = Text -> Text -> Attribute
makeAttribute Text
"oncanplaythrough"
onchange_ :: Text -> Attribute
onchange_ :: Text -> Attribute
onchange_ = Text -> Text -> Attribute
makeAttribute Text
"onchange"
onclick_ :: Text -> Attribute
onclick_ :: Text -> Attribute
onclick_ = Text -> Text -> Attribute
makeAttribute Text
"onclick"
oncontextmenu_ :: Text -> Attribute
= Text -> Text -> Attribute
makeAttribute Text
"oncontextmenu"
ondblclick_ :: Text -> Attribute
ondblclick_ :: Text -> Attribute
ondblclick_ = Text -> Text -> Attribute
makeAttribute Text
"ondblclick"
ondrag_ :: Text -> Attribute
ondrag_ :: Text -> Attribute
ondrag_ = Text -> Text -> Attribute
makeAttribute Text
"ondrag"
ondragend_ :: Text -> Attribute
ondragend_ :: Text -> Attribute
ondragend_ = Text -> Text -> Attribute
makeAttribute Text
"ondragend"
ondragenter_ :: Text -> Attribute
ondragenter_ :: Text -> Attribute
ondragenter_ = Text -> Text -> Attribute
makeAttribute Text
"ondragenter"
ondragleave_ :: Text -> Attribute
ondragleave_ :: Text -> Attribute
ondragleave_ = Text -> Text -> Attribute
makeAttribute Text
"ondragleave"
ondragover_ :: Text -> Attribute
ondragover_ :: Text -> Attribute
ondragover_ = Text -> Text -> Attribute
makeAttribute Text
"ondragover"
ondragstart_ :: Text -> Attribute
ondragstart_ :: Text -> Attribute
ondragstart_ = Text -> Text -> Attribute
makeAttribute Text
"ondragstart"
ondrop_ :: Text -> Attribute
ondrop_ :: Text -> Attribute
ondrop_ = Text -> Text -> Attribute
makeAttribute Text
"ondrop"
ondurationchange_ :: Text -> Attribute
ondurationchange_ :: Text -> Attribute
ondurationchange_ = Text -> Text -> Attribute
makeAttribute Text
"ondurationchange"
onemptied_ :: Text -> Attribute
onemptied_ :: Text -> Attribute
onemptied_ = Text -> Text -> Attribute
makeAttribute Text
"onemptied"
onended_ :: Text -> Attribute
onended_ :: Text -> Attribute
onended_ = Text -> Text -> Attribute
makeAttribute Text
"onended"
onerror_ :: Text -> Attribute
onerror_ :: Text -> Attribute
onerror_ = Text -> Text -> Attribute
makeAttribute Text
"onerror"
onfocus_ :: Text -> Attribute
onfocus_ :: Text -> Attribute
onfocus_ = Text -> Text -> Attribute
makeAttribute Text
"onfocus"
onformchange_ :: Text -> Attribute
onformchange_ :: Text -> Attribute
onformchange_ = Text -> Text -> Attribute
makeAttribute Text
"onformchange"
onforminput_ :: Text -> Attribute
onforminput_ :: Text -> Attribute
onforminput_ = Text -> Text -> Attribute
makeAttribute Text
"onforminput"
onhaschange_ :: Text -> Attribute
onhaschange_ :: Text -> Attribute
onhaschange_ = Text -> Text -> Attribute
makeAttribute Text
"onhaschange"
oninput_ :: Text -> Attribute
oninput_ :: Text -> Attribute
oninput_ = Text -> Text -> Attribute
makeAttribute Text
"oninput"
oninvalid_ :: Text -> Attribute
oninvalid_ :: Text -> Attribute
oninvalid_ = Text -> Text -> Attribute
makeAttribute Text
"oninvalid"
onkeydown_ :: Text -> Attribute
onkeydown_ :: Text -> Attribute
onkeydown_ = Text -> Text -> Attribute
makeAttribute Text
"onkeydown"
onkeyup_ :: Text -> Attribute
onkeyup_ :: Text -> Attribute
onkeyup_ = Text -> Text -> Attribute
makeAttribute Text
"onkeyup"
onload_ :: Text -> Attribute
onload_ :: Text -> Attribute
onload_ = Text -> Text -> Attribute
makeAttribute Text
"onload"
onloadeddata_ :: Text -> Attribute
onloadeddata_ :: Text -> Attribute
onloadeddata_ = Text -> Text -> Attribute
makeAttribute Text
"onloadeddata"
onloadedmetadata_ :: Text -> Attribute
onloadedmetadata_ :: Text -> Attribute
onloadedmetadata_ = Text -> Text -> Attribute
makeAttribute Text
"onloadedmetadata"
onloadstart_ :: Text -> Attribute
onloadstart_ :: Text -> Attribute
onloadstart_ = Text -> Text -> Attribute
makeAttribute Text
"onloadstart"
onmessage_ :: Text -> Attribute
onmessage_ :: Text -> Attribute
onmessage_ = Text -> Text -> Attribute
makeAttribute Text
"onmessage"
onmousedown_ :: Text -> Attribute
onmousedown_ :: Text -> Attribute
onmousedown_ = Text -> Text -> Attribute
makeAttribute Text
"onmousedown"
onmousemove_ :: Text -> Attribute
onmousemove_ :: Text -> Attribute
onmousemove_ = Text -> Text -> Attribute
makeAttribute Text
"onmousemove"
onmouseout_ :: Text -> Attribute
onmouseout_ :: Text -> Attribute
onmouseout_ = Text -> Text -> Attribute
makeAttribute Text
"onmouseout"
onmouseover_ :: Text -> Attribute
onmouseover_ :: Text -> Attribute
onmouseover_ = Text -> Text -> Attribute
makeAttribute Text
"onmouseover"
onmouseup_ :: Text -> Attribute
onmouseup_ :: Text -> Attribute
onmouseup_ = Text -> Text -> Attribute
makeAttribute Text
"onmouseup"
onmousewheel_ :: Text -> Attribute
onmousewheel_ :: Text -> Attribute
onmousewheel_ = Text -> Text -> Attribute
makeAttribute Text
"onmousewheel"
ononline_ :: Text -> Attribute
ononline_ :: Text -> Attribute
ononline_ = Text -> Text -> Attribute
makeAttribute Text
"ononline"
onpagehide_ :: Text -> Attribute
onpagehide_ :: Text -> Attribute
onpagehide_ = Text -> Text -> Attribute
makeAttribute Text
"onpagehide"
onpageshow_ :: Text -> Attribute
onpageshow_ :: Text -> Attribute
onpageshow_ = Text -> Text -> Attribute
makeAttribute Text
"onpageshow"
onpause_ :: Text -> Attribute
onpause_ :: Text -> Attribute
onpause_ = Text -> Text -> Attribute
makeAttribute Text
"onpause"
onplay_ :: Text -> Attribute
onplay_ :: Text -> Attribute
onplay_ = Text -> Text -> Attribute
makeAttribute Text
"onplay"
onplaying_ :: Text -> Attribute
onplaying_ :: Text -> Attribute
onplaying_ = Text -> Text -> Attribute
makeAttribute Text
"onplaying"
onprogress_ :: Text -> Attribute
onprogress_ :: Text -> Attribute
onprogress_ = Text -> Text -> Attribute
makeAttribute Text
"onprogress"
onpropstate_ :: Text -> Attribute
onpropstate_ :: Text -> Attribute
onpropstate_ = Text -> Text -> Attribute
makeAttribute Text
"onpropstate"
onratechange_ :: Text -> Attribute
onratechange_ :: Text -> Attribute
onratechange_ = Text -> Text -> Attribute
makeAttribute Text
"onratechange"
onreadystatechange_ :: Text -> Attribute
onreadystatechange_ :: Text -> Attribute
onreadystatechange_ = Text -> Text -> Attribute
makeAttribute Text
"onreadystatechange"
onredo_ :: Text -> Attribute
onredo_ :: Text -> Attribute
onredo_ = Text -> Text -> Attribute
makeAttribute Text
"onredo"
onresize_ :: Text -> Attribute
onresize_ :: Text -> Attribute
onresize_ = Text -> Text -> Attribute
makeAttribute Text
"onresize"
onscroll_ :: Text -> Attribute
onscroll_ :: Text -> Attribute
onscroll_ = Text -> Text -> Attribute
makeAttribute Text
"onscroll"
onseeked_ :: Text -> Attribute
onseeked_ :: Text -> Attribute
onseeked_ = Text -> Text -> Attribute
makeAttribute Text
"onseeked"
onseeking_ :: Text -> Attribute
onseeking_ :: Text -> Attribute
onseeking_ = Text -> Text -> Attribute
makeAttribute Text
"onseeking"
onselect_ :: Text -> Attribute
onselect_ :: Text -> Attribute
onselect_ = Text -> Text -> Attribute
makeAttribute Text
"onselect"
onstalled_ :: Text -> Attribute
onstalled_ :: Text -> Attribute
onstalled_ = Text -> Text -> Attribute
makeAttribute Text
"onstalled"
onstorage_ :: Text -> Attribute
onstorage_ :: Text -> Attribute
onstorage_ = Text -> Text -> Attribute
makeAttribute Text
"onstorage"
onsubmit_ :: Text -> Attribute
onsubmit_ :: Text -> Attribute
onsubmit_ = Text -> Text -> Attribute
makeAttribute Text
"onsubmit"
onsuspend_ :: Text -> Attribute
onsuspend_ :: Text -> Attribute
onsuspend_ = Text -> Text -> Attribute
makeAttribute Text
"onsuspend"
ontimeupdate_ :: Text -> Attribute
ontimeupdate_ :: Text -> Attribute
ontimeupdate_ = Text -> Text -> Attribute
makeAttribute Text
"ontimeupdate"
onundo_ :: Text -> Attribute
onundo_ :: Text -> Attribute
onundo_ = Text -> Text -> Attribute
makeAttribute Text
"onundo"
onunload_ :: Text -> Attribute
onunload_ :: Text -> Attribute
onunload_ = Text -> Text -> Attribute
makeAttribute Text
"onunload"
onvolumechange_ :: Text -> Attribute
onvolumechange_ :: Text -> Attribute
onvolumechange_ = Text -> Text -> Attribute
makeAttribute Text
"onvolumechange"
onwaiting_ :: Text -> Attribute
onwaiting_ :: Text -> Attribute
onwaiting_ = Text -> Text -> Attribute
makeAttribute Text
"onwaiting"
open_ :: Text -> Attribute
open_ :: Text -> Attribute
open_ = Text -> Text -> Attribute
makeAttribute Text
"open"
optimum_ :: Text -> Attribute
optimum_ :: Text -> Attribute
optimum_ = Text -> Text -> Attribute
makeAttribute Text
"optimum"
pattern_ :: Text -> Attribute
pattern_ :: Text -> Attribute
pattern_ = Text -> Text -> Attribute
makeAttribute Text
"pattern"
ping_ :: Text -> Attribute
ping_ :: Text -> Attribute
ping_ = Text -> Text -> Attribute
makeAttribute Text
"ping"
placeholder_ :: Text -> Attribute
placeholder_ :: Text -> Attribute
placeholder_ = Text -> Text -> Attribute
makeAttribute Text
"placeholder"
preload_ :: Text -> Attribute
preload_ :: Text -> Attribute
preload_ = Text -> Text -> Attribute
makeAttribute Text
"preload"
pubdate_ :: Text -> Attribute
pubdate_ :: Text -> Attribute
pubdate_ = Text -> Text -> Attribute
makeAttribute Text
"pubdate"
radiogroup_ :: Text -> Attribute
radiogroup_ :: Text -> Attribute
radiogroup_ = Text -> Text -> Attribute
makeAttribute Text
"radiogroup"
readonly_ :: Text -> Attribute
readonly_ :: Text -> Attribute
readonly_ = Text -> Text -> Attribute
makeAttribute Text
"readonly"
rel_ :: Text -> Attribute
rel_ :: Text -> Attribute
rel_ = Text -> Text -> Attribute
makeAttribute Text
"rel"
required_ :: Text -> Attribute
required_ :: Text -> Attribute
required_ = Text -> Text -> Attribute
makeAttribute Text
"required"
reversed_ :: Text -> Attribute
reversed_ :: Text -> Attribute
reversed_ = Text -> Text -> Attribute
makeAttribute Text
"reversed"
role_ :: Text -> Attribute
role_ :: Text -> Attribute
role_ = Text -> Text -> Attribute
makeAttribute Text
"role"
rows_ :: Text -> Attribute
rows_ :: Text -> Attribute
rows_ = Text -> Text -> Attribute
makeAttribute Text
"rows"
rowspan_ :: Text -> Attribute
rowspan_ :: Text -> Attribute
rowspan_ = Text -> Text -> Attribute
makeAttribute Text
"rowspan"
sandbox_ :: Text -> Attribute
sandbox_ :: Text -> Attribute
sandbox_ = Text -> Text -> Attribute
makeAttribute Text
"sandbox"
scope_ :: Text -> Attribute
scope_ :: Text -> Attribute
scope_ = Text -> Text -> Attribute
makeAttribute Text
"scope"
scoped_ :: Text -> Attribute
scoped_ :: Text -> Attribute
scoped_ = Text -> Text -> Attribute
makeAttribute Text
"scoped"
seamless_ :: Text -> Attribute
seamless_ :: Text -> Attribute
seamless_ = Text -> Text -> Attribute
makeAttribute Text
"seamless"
selected_ :: Text -> Attribute
selected_ :: Text -> Attribute
selected_ = Text -> Text -> Attribute
makeAttribute Text
"selected"
shape_ :: Text -> Attribute
shape_ :: Text -> Attribute
shape_ = Text -> Text -> Attribute
makeAttribute Text
"shape"
size_ :: Text -> Attribute
size_ :: Text -> Attribute
size_ = Text -> Text -> Attribute
makeAttribute Text
"size"
sizes_ :: Text -> Attribute
sizes_ :: Text -> Attribute
sizes_ = Text -> Text -> Attribute
makeAttribute Text
"sizes"
spellcheck_ :: Text -> Attribute
spellcheck_ :: Text -> Attribute
spellcheck_ = Text -> Text -> Attribute
makeAttribute Text
"spellcheck"
src_ :: Text -> Attribute
src_ :: Text -> Attribute
src_ = Text -> Text -> Attribute
makeAttribute Text
"src"
srcdoc_ :: Text -> Attribute
srcdoc_ :: Text -> Attribute
srcdoc_ = Text -> Text -> Attribute
makeAttribute Text
"srcdoc"
start_ :: Text -> Attribute
start_ :: Text -> Attribute
start_ = Text -> Text -> Attribute
makeAttribute Text
"start"
step_ :: Text -> Attribute
step_ :: Text -> Attribute
step_ = Text -> Text -> Attribute
makeAttribute Text
"step"
subject_ :: Text -> Attribute
subject_ :: Text -> Attribute
subject_ = Text -> Text -> Attribute
makeAttribute Text
"subject"
tabindex_ :: Text -> Attribute
tabindex_ :: Text -> Attribute
tabindex_ = Text -> Text -> Attribute
makeAttribute Text
"tabindex"
target_ :: Text -> Attribute
target_ :: Text -> Attribute
target_ = Text -> Text -> Attribute
makeAttribute Text
"target"
type_ :: Text -> Attribute
type_ :: Text -> Attribute
type_ = Text -> Text -> Attribute
makeAttribute Text
"type"
usemap_ :: Text -> Attribute
usemap_ :: Text -> Attribute
usemap_ = Text -> Text -> Attribute
makeAttribute Text
"usemap"
value_ :: Text -> Attribute
value_ :: Text -> Attribute
value_ = Text -> Text -> Attribute
makeAttribute Text
"value"
width_ :: Text -> Attribute
width_ :: Text -> Attribute
width_ = Text -> Text -> Attribute
makeAttribute Text
"width"
wrap_ :: Text -> Attribute
wrap_ :: Text -> Attribute
wrap_ = Text -> Text -> Attribute
makeAttribute Text
"wrap"
xmlns_ :: Text -> Attribute
xmlns_ :: Text -> Attribute
xmlns_ = Text -> Text -> Attribute
makeAttribute Text
"xmlns"