{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS -fno-warn-type-defaults #-}
module Lucid.Html5 where
import Lucid.Base
import Data.ByteString
import Data.Text (Text)
doctype_ :: Monad m => HtmlT m ()
doctype_ :: HtmlT m ()
doctype_ = ByteString -> HtmlT m ()
forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtmlRaw (ByteString
"<!DOCTYPE HTML>" :: ByteString)
doctypehtml_ :: Monad m => HtmlT m a -> HtmlT m a
doctypehtml_ :: HtmlT m a -> HtmlT m a
doctypehtml_ HtmlT m a
m = HtmlT m ()
forall (m :: * -> *). Monad 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_ :: Monad m => [Attributes] -> HtmlT m ()
area_ :: [Attributes] -> HtmlT m ()
area_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
base_ :: [Attributes] -> HtmlT m ()
base_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
br_ :: [Attributes] -> HtmlT m ()
br_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
col_ :: [Attributes] -> HtmlT m ()
col_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
embed_ :: [Attributes] -> HtmlT m ()
embed_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
hr_ :: [Attributes] -> HtmlT m ()
hr_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
img_ :: [Attributes] -> HtmlT m ()
img_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"img"
input_ :: Monad m => [Attributes] -> HtmlT m ()
input_ :: [Attributes] -> HtmlT m ()
input_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
keygen_ :: [Attributes] -> HtmlT m ()
keygen_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
link_ :: [Attributes] -> HtmlT m ()
link_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
= Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"menuitem"
meta_ :: Monad m => [Attributes] -> HtmlT m ()
meta_ :: [Attributes] -> HtmlT m ()
meta_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
param_ :: [Attributes] -> HtmlT m ()
param_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
source_ :: [Attributes] -> HtmlT m ()
source_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
track_ :: [Attributes] -> HtmlT m ()
track_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> 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_ :: Monad m => [Attributes] -> HtmlT m ()
wbr_ :: [Attributes] -> HtmlT m ()
wbr_ = Text -> [Attributes] -> HtmlT m ()
forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"wbr"
accept_ :: Text -> Attributes
accept_ :: Text -> Attributes
accept_ = Text -> Text -> Attributes
makeAttributes Text
"accept"
acceptCharset_ :: Text -> Attributes
acceptCharset_ :: Text -> Attributes
acceptCharset_ = Text -> Text -> Attributes
makeAttributes Text
"accept-charset"
accesskey_ :: Text -> Attributes
accesskey_ :: Text -> Attributes
accesskey_ = Text -> Text -> Attributes
makeAttributes Text
"accesskey"
action_ :: Text -> Attributes
action_ :: Text -> Attributes
action_ = Text -> Text -> Attributes
makeAttributes Text
"action"
alt_ :: Text -> Attributes
alt_ :: Text -> Attributes
alt_ = Text -> Text -> Attributes
makeAttributes Text
"alt"
async_ :: Text -> Attributes
async_ :: Text -> Attributes
async_ = Text -> Text -> Attributes
makeAttributes Text
"async"
autocomplete_ :: Text -> Attributes
autocomplete_ :: Text -> Attributes
autocomplete_ = Text -> Text -> Attributes
makeAttributes Text
"autocomplete"
autofocus_ :: Attributes
autofocus_ :: Attributes
autofocus_ = Text -> Text -> Attributes
makeAttributes Text
"autofocus" Text
forall a. Monoid a => a
mempty
autoplay_ :: Text -> Attributes
autoplay_ :: Text -> Attributes
autoplay_ = Text -> Text -> Attributes
makeAttributes Text
"autoplay"
challenge_ :: Text -> Attributes
challenge_ :: Text -> Attributes
challenge_ = Text -> Text -> Attributes
makeAttributes Text
"challenge"
charset_ :: Text -> Attributes
charset_ :: Text -> Attributes
charset_ = Text -> Text -> Attributes
makeAttributes Text
"charset"
checked_ :: Attributes
checked_ :: Attributes
checked_ = Text -> Text -> Attributes
makeAttributes Text
"checked" Text
forall a. Monoid a => a
mempty
class_ :: Text -> Attributes
class_ :: Text -> Attributes
class_ = Text -> Text -> Attributes
makeAttributes Text
"class"
cols_ :: Text -> Attributes
cols_ :: Text -> Attributes
cols_ = Text -> Text -> Attributes
makeAttributes Text
"cols"
colspan_ :: Text -> Attributes
colspan_ :: Text -> Attributes
colspan_ = Text -> Text -> Attributes
makeAttributes Text
"colspan"
content_ :: Text -> Attributes
content_ :: Text -> Attributes
content_ = Text -> Text -> Attributes
makeAttributes Text
"content"
contenteditable_ :: Text -> Attributes
contenteditable_ :: Text -> Attributes
contenteditable_ = Text -> Text -> Attributes
makeAttributes Text
"contenteditable"
contextmenu_ :: Text -> Attributes
= Text -> Text -> Attributes
makeAttributes Text
"contextmenu"
controls_ :: Text -> Attributes
controls_ :: Text -> Attributes
controls_ = Text -> Text -> Attributes
makeAttributes Text
"controls"
coords_ :: Text -> Attributes
coords_ :: Text -> Attributes
coords_ = Text -> Text -> Attributes
makeAttributes Text
"coords"
crossorigin_ :: Text -> Attributes
crossorigin_ :: Text -> Attributes
crossorigin_ = Text -> Text -> Attributes
makeAttributes Text
"crossorigin"
data_ :: Text -> Text -> Attributes
data_ :: Text -> Text -> Attributes
data_ Text
name = Text -> Text -> Attributes
makeAttributes (Text
"data-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name)
datetime_ :: Text -> Attributes
datetime_ :: Text -> Attributes
datetime_ = Text -> Text -> Attributes
makeAttributes Text
"datetime"
defer_ :: Text -> Attributes
defer_ :: Text -> Attributes
defer_ = Text -> Text -> Attributes
makeAttributes Text
"defer"
dir_ :: Text -> Attributes
dir_ :: Text -> Attributes
dir_ = Text -> Text -> Attributes
makeAttributes Text
"dir"
disabled_ :: Text -> Attributes
disabled_ :: Text -> Attributes
disabled_ = Text -> Text -> Attributes
makeAttributes Text
"disabled"
download_ :: Text -> Attributes
download_ :: Text -> Attributes
download_ = Text -> Text -> Attributes
makeAttributes Text
"download"
draggable_ :: Text -> Attributes
draggable_ :: Text -> Attributes
draggable_ = Text -> Text -> Attributes
makeAttributes Text
"draggable"
enctype_ :: Text -> Attributes
enctype_ :: Text -> Attributes
enctype_ = Text -> Text -> Attributes
makeAttributes Text
"enctype"
for_ :: Text -> Attributes
for_ :: Text -> Attributes
for_ = Text -> Text -> Attributes
makeAttributes Text
"for"
formaction_ :: Text -> Attributes
formaction_ :: Text -> Attributes
formaction_ = Text -> Text -> Attributes
makeAttributes Text
"formaction"
formenctype_ :: Text -> Attributes
formenctype_ :: Text -> Attributes
formenctype_ = Text -> Text -> Attributes
makeAttributes Text
"formenctype"
formmethod_ :: Text -> Attributes
formmethod_ :: Text -> Attributes
formmethod_ = Text -> Text -> Attributes
makeAttributes Text
"formmethod"
formnovalidate_ :: Text -> Attributes
formnovalidate_ :: Text -> Attributes
formnovalidate_ = Text -> Text -> Attributes
makeAttributes Text
"formnovalidate"
formtarget_ :: Text -> Attributes
formtarget_ :: Text -> Attributes
formtarget_ = Text -> Text -> Attributes
makeAttributes Text
"formtarget"
headers_ :: Text -> Attributes
= Text -> Text -> Attributes
makeAttributes Text
"headers"
height_ :: Text -> Attributes
height_ :: Text -> Attributes
height_ = Text -> Text -> Attributes
makeAttributes Text
"height"
hidden_ :: Text -> Attributes
hidden_ :: Text -> Attributes
hidden_ = Text -> Text -> Attributes
makeAttributes Text
"hidden"
high_ :: Text -> Attributes
high_ :: Text -> Attributes
high_ = Text -> Text -> Attributes
makeAttributes Text
"high"
href_ :: Text -> Attributes
href_ :: Text -> Attributes
href_ = Text -> Text -> Attributes
makeAttributes Text
"href"
hreflang_ :: Text -> Attributes
hreflang_ :: Text -> Attributes
hreflang_ = Text -> Text -> Attributes
makeAttributes Text
"hreflang"
httpEquiv_ :: Text -> Attributes
httpEquiv_ :: Text -> Attributes
httpEquiv_ = Text -> Text -> Attributes
makeAttributes Text
"http-equiv"
icon_ :: Text -> Attributes
icon_ :: Text -> Attributes
icon_ = Text -> Text -> Attributes
makeAttributes Text
"icon"
id_ :: Text -> Attributes
id_ :: Text -> Attributes
id_ = Text -> Text -> Attributes
makeAttributes Text
"id"
integrity_ :: Text -> Attributes
integrity_ :: Text -> Attributes
integrity_ = Text -> Text -> Attributes
makeAttributes Text
"integrity"
ismap_ :: Text -> Attributes
ismap_ :: Text -> Attributes
ismap_ = Text -> Text -> Attributes
makeAttributes Text
"ismap"
item_ :: Text -> Attributes
item_ :: Text -> Attributes
item_ = Text -> Text -> Attributes
makeAttributes Text
"item"
itemprop_ :: Text -> Attributes
itemprop_ :: Text -> Attributes
itemprop_ = Text -> Text -> Attributes
makeAttributes Text
"itemprop"
keytype_ :: Text -> Attributes
keytype_ :: Text -> Attributes
keytype_ = Text -> Text -> Attributes
makeAttributes Text
"keytype"
lang_ :: Text -> Attributes
lang_ :: Text -> Attributes
lang_ = Text -> Text -> Attributes
makeAttributes Text
"lang"
list_ :: Text -> Attributes
list_ :: Text -> Attributes
list_ = Text -> Text -> Attributes
makeAttributes Text
"list"
loading_ :: Text -> Attributes
loading_ :: Text -> Attributes
loading_ = Text -> Text -> Attributes
makeAttributes Text
"loading"
loop_ :: Text -> Attributes
loop_ :: Text -> Attributes
loop_ = Text -> Text -> Attributes
makeAttributes Text
"loop"
low_ :: Text -> Attributes
low_ :: Text -> Attributes
low_ = Text -> Text -> Attributes
makeAttributes Text
"low"
manifest_ :: Text -> Attributes
manifest_ :: Text -> Attributes
manifest_ = Text -> Text -> Attributes
makeAttributes Text
"manifest"
max_ :: Text -> Attributes
max_ :: Text -> Attributes
max_ = Text -> Text -> Attributes
makeAttributes Text
"max"
maxlength_ :: Text -> Attributes
maxlength_ :: Text -> Attributes
maxlength_ = Text -> Text -> Attributes
makeAttributes Text
"maxlength"
media_ :: Text -> Attributes
media_ :: Text -> Attributes
media_ = Text -> Text -> Attributes
makeAttributes Text
"media"
method_ :: Text -> Attributes
method_ :: Text -> Attributes
method_ = Text -> Text -> Attributes
makeAttributes Text
"method"
min_ :: Text -> Attributes
min_ :: Text -> Attributes
min_ = Text -> Text -> Attributes
makeAttributes Text
"min"
minlength_ :: Text -> Attributes
minlength_ :: Text -> Attributes
minlength_ = Text -> Text -> Attributes
makeAttributes Text
"minlength"
multiple_ :: Text -> Attributes
multiple_ :: Text -> Attributes
multiple_ = Text -> Text -> Attributes
makeAttributes Text
"multiple"
name_ :: Text -> Attributes
name_ :: Text -> Attributes
name_ = Text -> Text -> Attributes
makeAttributes Text
"name"
novalidate_ :: Text -> Attributes
novalidate_ :: Text -> Attributes
novalidate_ = Text -> Text -> Attributes
makeAttributes Text
"novalidate"
onbeforeonload_ :: Text -> Attributes
onbeforeonload_ :: Text -> Attributes
onbeforeonload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onbeforeonload"
onbeforeprint_ :: Text -> Attributes
onbeforeprint_ :: Text -> Attributes
onbeforeprint_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onbeforeprint"
onblur_ :: Text -> Attributes
onblur_ :: Text -> Attributes
onblur_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onblur"
oncanplay_ :: Text -> Attributes
oncanplay_ :: Text -> Attributes
oncanplay_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oncanplay"
oncanplaythrough_ :: Text -> Attributes
oncanplaythrough_ :: Text -> Attributes
oncanplaythrough_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oncanplaythrough"
onchange_ :: Text -> Attributes
onchange_ :: Text -> Attributes
onchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onchange"
onclick_ :: Text -> Attributes
onclick_ :: Text -> Attributes
onclick_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onclick"
oncontextmenu_ :: Text -> Attributes
= Text -> Text -> Attributes
makeAttributesRaw Text
"oncontextmenu"
ondblclick_ :: Text -> Attributes
ondblclick_ :: Text -> Attributes
ondblclick_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondblclick"
ondrag_ :: Text -> Attributes
ondrag_ :: Text -> Attributes
ondrag_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondrag"
ondragend_ :: Text -> Attributes
ondragend_ :: Text -> Attributes
ondragend_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragend"
ondragenter_ :: Text -> Attributes
ondragenter_ :: Text -> Attributes
ondragenter_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragenter"
ondragleave_ :: Text -> Attributes
ondragleave_ :: Text -> Attributes
ondragleave_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragleave"
ondragover_ :: Text -> Attributes
ondragover_ :: Text -> Attributes
ondragover_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragover"
ondragstart_ :: Text -> Attributes
ondragstart_ :: Text -> Attributes
ondragstart_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragstart"
ondrop_ :: Text -> Attributes
ondrop_ :: Text -> Attributes
ondrop_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondrop"
ondurationchange_ :: Text -> Attributes
ondurationchange_ :: Text -> Attributes
ondurationchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondurationchange"
onemptied_ :: Text -> Attributes
onemptied_ :: Text -> Attributes
onemptied_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onemptied"
onended_ :: Text -> Attributes
onended_ :: Text -> Attributes
onended_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onended"
onerror_ :: Text -> Attributes
onerror_ :: Text -> Attributes
onerror_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onerror"
onfocus_ :: Text -> Attributes
onfocus_ :: Text -> Attributes
onfocus_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onfocus"
onformchange_ :: Text -> Attributes
onformchange_ :: Text -> Attributes
onformchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onformchange"
onforminput_ :: Text -> Attributes
onforminput_ :: Text -> Attributes
onforminput_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onforminput"
onhaschange_ :: Text -> Attributes
onhaschange_ :: Text -> Attributes
onhaschange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onhaschange"
oninput_ :: Text -> Attributes
oninput_ :: Text -> Attributes
oninput_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oninput"
oninvalid_ :: Text -> Attributes
oninvalid_ :: Text -> Attributes
oninvalid_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oninvalid"
onkeydown_ :: Text -> Attributes
onkeydown_ :: Text -> Attributes
onkeydown_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onkeydown"
onkeyup_ :: Text -> Attributes
onkeyup_ :: Text -> Attributes
onkeyup_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onkeyup"
onload_ :: Text -> Attributes
onload_ :: Text -> Attributes
onload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onload"
onloadeddata_ :: Text -> Attributes
onloadeddata_ :: Text -> Attributes
onloadeddata_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadeddata"
onloadedmetadata_ :: Text -> Attributes
onloadedmetadata_ :: Text -> Attributes
onloadedmetadata_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadedmetadata"
onloadstart_ :: Text -> Attributes
onloadstart_ :: Text -> Attributes
onloadstart_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadstart"
onmessage_ :: Text -> Attributes
onmessage_ :: Text -> Attributes
onmessage_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmessage"
onmousedown_ :: Text -> Attributes
onmousedown_ :: Text -> Attributes
onmousedown_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousedown"
onmousemove_ :: Text -> Attributes
onmousemove_ :: Text -> Attributes
onmousemove_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousemove"
onmouseout_ :: Text -> Attributes
onmouseout_ :: Text -> Attributes
onmouseout_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseout"
onmouseover_ :: Text -> Attributes
onmouseover_ :: Text -> Attributes
onmouseover_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseover"
onmouseup_ :: Text -> Attributes
onmouseup_ :: Text -> Attributes
onmouseup_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseup"
onmousewheel_ :: Text -> Attributes
onmousewheel_ :: Text -> Attributes
onmousewheel_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousewheel"
ononline_ :: Text -> Attributes
ononline_ :: Text -> Attributes
ononline_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ononline"
onpagehide_ :: Text -> Attributes
onpagehide_ :: Text -> Attributes
onpagehide_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpagehide"
onpageshow_ :: Text -> Attributes
onpageshow_ :: Text -> Attributes
onpageshow_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpageshow"
onpause_ :: Text -> Attributes
onpause_ :: Text -> Attributes
onpause_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpause"
onplay_ :: Text -> Attributes
onplay_ :: Text -> Attributes
onplay_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onplay"
onplaying_ :: Text -> Attributes
onplaying_ :: Text -> Attributes
onplaying_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onplaying"
onprogress_ :: Text -> Attributes
onprogress_ :: Text -> Attributes
onprogress_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onprogress"
onpropstate_ :: Text -> Attributes
onpropstate_ :: Text -> Attributes
onpropstate_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpropstate"
onratechange_ :: Text -> Attributes
onratechange_ :: Text -> Attributes
onratechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onratechange"
onreadystatechange_ :: Text -> Attributes
onreadystatechange_ :: Text -> Attributes
onreadystatechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onreadystatechange"
onredo_ :: Text -> Attributes
onredo_ :: Text -> Attributes
onredo_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onredo"
onresize_ :: Text -> Attributes
onresize_ :: Text -> Attributes
onresize_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onresize"
onscroll_ :: Text -> Attributes
onscroll_ :: Text -> Attributes
onscroll_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onscroll"
onseeked_ :: Text -> Attributes
onseeked_ :: Text -> Attributes
onseeked_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onseeked"
onseeking_ :: Text -> Attributes
onseeking_ :: Text -> Attributes
onseeking_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onseeking"
onselect_ :: Text -> Attributes
onselect_ :: Text -> Attributes
onselect_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onselect"
onstalled_ :: Text -> Attributes
onstalled_ :: Text -> Attributes
onstalled_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onstalled"
onstorage_ :: Text -> Attributes
onstorage_ :: Text -> Attributes
onstorage_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onstorage"
onsubmit_ :: Text -> Attributes
onsubmit_ :: Text -> Attributes
onsubmit_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onsubmit"
onsuspend_ :: Text -> Attributes
onsuspend_ :: Text -> Attributes
onsuspend_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onsuspend"
ontimeupdate_ :: Text -> Attributes
ontimeupdate_ :: Text -> Attributes
ontimeupdate_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ontimeupdate"
onundo_ :: Text -> Attributes
onundo_ :: Text -> Attributes
onundo_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onundo"
onunload_ :: Text -> Attributes
onunload_ :: Text -> Attributes
onunload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onunload"
onvolumechange_ :: Text -> Attributes
onvolumechange_ :: Text -> Attributes
onvolumechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onvolumechange"
onwaiting_ :: Text -> Attributes
onwaiting_ :: Text -> Attributes
onwaiting_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onwaiting"
open_ :: Text -> Attributes
open_ :: Text -> Attributes
open_ = Text -> Text -> Attributes
makeAttributes Text
"open"
optimum_ :: Text -> Attributes
optimum_ :: Text -> Attributes
optimum_ = Text -> Text -> Attributes
makeAttributes Text
"optimum"
pattern_ :: Text -> Attributes
pattern_ :: Text -> Attributes
pattern_ = Text -> Text -> Attributes
makeAttributes Text
"pattern"
ping_ :: Text -> Attributes
ping_ :: Text -> Attributes
ping_ = Text -> Text -> Attributes
makeAttributes Text
"ping"
placeholder_ :: Text -> Attributes
placeholder_ :: Text -> Attributes
placeholder_ = Text -> Text -> Attributes
makeAttributes Text
"placeholder"
poster_ :: Text -> Attributes
poster_ :: Text -> Attributes
poster_ = Text -> Text -> Attributes
makeAttributes Text
"poster"
preload_ :: Text -> Attributes
preload_ :: Text -> Attributes
preload_ = Text -> Text -> Attributes
makeAttributes Text
"preload"
pubdate_ :: Text -> Attributes
pubdate_ :: Text -> Attributes
pubdate_ = Text -> Text -> Attributes
makeAttributes Text
"pubdate"
radiogroup_ :: Text -> Attributes
radiogroup_ :: Text -> Attributes
radiogroup_ = Text -> Text -> Attributes
makeAttributes Text
"radiogroup"
readonly_ :: Text -> Attributes
readonly_ :: Text -> Attributes
readonly_ = Text -> Text -> Attributes
makeAttributes Text
"readonly"
rel_ :: Text -> Attributes
rel_ :: Text -> Attributes
rel_ = Text -> Text -> Attributes
makeAttributes Text
"rel"
required_ :: Text -> Attributes
required_ :: Text -> Attributes
required_ = Text -> Text -> Attributes
makeAttributes Text
"required"
reversed_ :: Text -> Attributes
reversed_ :: Text -> Attributes
reversed_ = Text -> Text -> Attributes
makeAttributes Text
"reversed"
role_ :: Text -> Attributes
role_ :: Text -> Attributes
role_ = Text -> Text -> Attributes
makeAttributes Text
"role"
rows_ :: Text -> Attributes
rows_ :: Text -> Attributes
rows_ = Text -> Text -> Attributes
makeAttributes Text
"rows"
rowspan_ :: Text -> Attributes
rowspan_ :: Text -> Attributes
rowspan_ = Text -> Text -> Attributes
makeAttributes Text
"rowspan"
sandbox_ :: Text -> Attributes
sandbox_ :: Text -> Attributes
sandbox_ = Text -> Text -> Attributes
makeAttributes Text
"sandbox"
scope_ :: Text -> Attributes
scope_ :: Text -> Attributes
scope_ = Text -> Text -> Attributes
makeAttributes Text
"scope"
scoped_ :: Text -> Attributes
scoped_ :: Text -> Attributes
scoped_ = Text -> Text -> Attributes
makeAttributes Text
"scoped"
seamless_ :: Text -> Attributes
seamless_ :: Text -> Attributes
seamless_ = Text -> Text -> Attributes
makeAttributes Text
"seamless"
selected_ :: Text -> Attributes
selected_ :: Text -> Attributes
selected_ = Text -> Text -> Attributes
makeAttributes Text
"selected"
shape_ :: Text -> Attributes
shape_ :: Text -> Attributes
shape_ = Text -> Text -> Attributes
makeAttributes Text
"shape"
size_ :: Text -> Attributes
size_ :: Text -> Attributes
size_ = Text -> Text -> Attributes
makeAttributes Text
"size"
sizes_ :: Text -> Attributes
sizes_ :: Text -> Attributes
sizes_ = Text -> Text -> Attributes
makeAttributes Text
"sizes"
spellcheck_ :: Text -> Attributes
spellcheck_ :: Text -> Attributes
spellcheck_ = Text -> Text -> Attributes
makeAttributes Text
"spellcheck"
src_ :: Text -> Attributes
src_ :: Text -> Attributes
src_ = Text -> Text -> Attributes
makeAttributes Text
"src"
srcdoc_ :: Text -> Attributes
srcdoc_ :: Text -> Attributes
srcdoc_ = Text -> Text -> Attributes
makeAttributes Text
"srcdoc"
start_ :: Text -> Attributes
start_ :: Text -> Attributes
start_ = Text -> Text -> Attributes
makeAttributes Text
"start"
step_ :: Text -> Attributes
step_ :: Text -> Attributes
step_ = Text -> Text -> Attributes
makeAttributes Text
"step"
subject_ :: Text -> Attributes
subject_ :: Text -> Attributes
subject_ = Text -> Text -> Attributes
makeAttributes Text
"subject"
tabindex_ :: Text -> Attributes
tabindex_ :: Text -> Attributes
tabindex_ = Text -> Text -> Attributes
makeAttributes Text
"tabindex"
target_ :: Text -> Attributes
target_ :: Text -> Attributes
target_ = Text -> Text -> Attributes
makeAttributes Text
"target"
type_ :: Text -> Attributes
type_ :: Text -> Attributes
type_ = Text -> Text -> Attributes
makeAttributes Text
"type"
usemap_ :: Text -> Attributes
usemap_ :: Text -> Attributes
usemap_ = Text -> Text -> Attributes
makeAttributes Text
"usemap"
value_ :: Text -> Attributes
value_ :: Text -> Attributes
value_ = Text -> Text -> Attributes
makeAttributes Text
"value"
width_ :: Text -> Attributes
width_ :: Text -> Attributes
width_ = Text -> Text -> Attributes
makeAttributes Text
"width"
wrap_ :: Text -> Attributes
wrap_ :: Text -> Attributes
wrap_ = Text -> Text -> Attributes
makeAttributes Text
"wrap"
xmlns_ :: Text -> Attributes
xmlns_ :: Text -> Attributes
xmlns_ = Text -> Text -> Attributes
makeAttributes Text
"xmlns"