{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# OPTIONS -fno-warn-type-defaults #-}

-- | Html5 terms.

module Lucid.Html5 where

import Lucid.Base

import Data.ByteString
import Data.Text (Text)

-------------------------------------------------------------------------------
-- Elements

-- | @DOCTYPE@ element
--
-- This is implemented as "raw output", because the doctype doesn't
-- accept attributes.
--
doctype_ :: Monad m => HtmlT m ()
doctype_ :: forall (m :: * -> *). Monad m => HtmlT m ()
doctype_ = forall a (m :: * -> *). (ToHtml a, Monad m) => a -> HtmlT m ()
toHtmlRaw (ByteString
"<!DOCTYPE HTML>" :: ByteString)

-- | @DOCTYPE@ element + @html@ element
doctypehtml_ :: Monad m => HtmlT m a -> HtmlT m a
doctypehtml_ :: forall (m :: * -> *) a. Monad m => HtmlT m a -> HtmlT m a
doctypehtml_ HtmlT m a
m = forall (m :: * -> *). Monad m => HtmlT m ()
doctype_ forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall arg result. Term arg result => arg -> result
html_ HtmlT m a
m

-- | @a@ element
a_ :: Term arg result => arg -> result
a_ :: forall arg result. Term arg result => arg -> result
a_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"a"

-- | @abbr@ element
abbr_ :: Term arg result => arg -> result
abbr_ :: forall arg result. Term arg result => arg -> result
abbr_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"abbr"

-- | @address@ element
address_ :: Term arg result => arg -> result
address_ :: forall arg result. Term arg result => arg -> result
address_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"address"

-- | @area@ element
area_ :: Monad m => [Attributes] -> HtmlT m ()
area_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
area_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"area"

-- | @article@ element
article_ :: Term arg result => arg -> result
article_ :: forall arg result. Term arg result => arg -> result
article_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"article"

-- | @aside@ element
aside_ :: Term arg result => arg -> result
aside_ :: forall arg result. Term arg result => arg -> result
aside_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"aside"

-- | @audio@ element
audio_ :: Term arg result => arg -> result
audio_ :: forall arg result. Term arg result => arg -> result
audio_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"audio"

-- | @b@ element
b_ :: Term arg result => arg -> result
b_ :: forall arg result. Term arg result => arg -> result
b_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"b"

-- | @base@ element
base_ :: Monad m => [Attributes] -> HtmlT m ()
base_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
base_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"base"

-- | @bdo@ element
bdo_ :: Term arg result => arg -> result
bdo_ :: forall arg result. Term arg result => arg -> result
bdo_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"bdo"

-- | @blockquote@ element
blockquote_ :: Term arg result => arg -> result
blockquote_ :: forall arg result. Term arg result => arg -> result
blockquote_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"blockquote"

-- | @body@ element
body_ :: Term arg result => arg -> result
body_ :: forall arg result. Term arg result => arg -> result
body_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"body"

-- | @br@ element
br_ :: Monad m => [Attributes] -> HtmlT m ()
br_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
br_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"br"

-- | @button@ element
button_ :: Term arg result => arg -> result
button_ :: forall arg result. Term arg result => arg -> result
button_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"button"

-- | @canvas@ element
canvas_ :: Term arg result => arg -> result
canvas_ :: forall arg result. Term arg result => arg -> result
canvas_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"canvas"

-- | @caption@ element
caption_ :: Term arg result => arg -> result
caption_ :: forall arg result. Term arg result => arg -> result
caption_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"caption"

-- | @cite@ element or @cite@ attribute.
cite_ :: Term arg result => arg -> result
cite_ :: forall arg result. Term arg result => arg -> result
cite_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"cite"

-- | @code@ element
code_ :: Term arg result => arg -> result
code_ :: forall arg result. Term arg result => arg -> result
code_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"code"

-- | @col@ element
col_ :: Monad m => [Attributes] -> HtmlT m ()
col_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
col_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"col"

-- | @colgroup@ element
colgroup_ :: Term arg result => arg -> result
colgroup_ :: forall arg result. Term arg result => arg -> result
colgroup_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"colgroup"

-- | @command@ element
command_ :: Term arg result => arg -> result
command_ :: forall arg result. Term arg result => arg -> result
command_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"command"

-- | @datalist@ element
datalist_ :: Term arg result => arg -> result
datalist_ :: forall arg result. Term arg result => arg -> result
datalist_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"datalist"

-- | @dd@ element
dd_ :: Term arg result => arg -> result
dd_ :: forall arg result. Term arg result => arg -> result
dd_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"dd"

-- | @del@ element
del_ :: Term arg result => arg -> result
del_ :: forall arg result. Term arg result => arg -> result
del_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"del"

-- | @details@ element
details_ :: Term arg result => arg -> result
details_ :: forall arg result. Term arg result => arg -> result
details_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"details"

-- | @dfn@ element
dfn_ :: Term arg result => arg -> result
dfn_ :: forall arg result. Term arg result => arg -> result
dfn_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"dfn"

-- | @div@ element
div_ :: Term arg result => arg -> result
div_ :: forall arg result. Term arg result => arg -> result
div_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"div"

-- | @dl@ element
dl_ :: Term arg result => arg -> result
dl_ :: forall arg result. Term arg result => arg -> result
dl_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"dl"

-- | @dt@ element
dt_ :: Term arg result => arg -> result
dt_ :: forall arg result. Term arg result => arg -> result
dt_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"dt"

-- | @em@ element
em_ :: Term arg result => arg -> result
em_ :: forall arg result. Term arg result => arg -> result
em_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"em"

-- | @embed@ element
embed_ :: Monad m => [Attributes] -> HtmlT m ()
embed_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
embed_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"embed"

-- | @fieldset@ element
fieldset_ :: Term arg result => arg -> result
fieldset_ :: forall arg result. Term arg result => arg -> result
fieldset_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"fieldset"

-- | @figcaption@ element
figcaption_ :: Term arg result => arg -> result
figcaption_ :: forall arg result. Term arg result => arg -> result
figcaption_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"figcaption"

-- | @figure@ element
figure_ :: Term arg result => arg -> result
figure_ :: forall arg result. Term arg result => arg -> result
figure_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"figure"

-- | @footer@ element
footer_ :: Term arg result => arg -> result
footer_ :: forall arg result. Term arg result => arg -> result
footer_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"footer"

-- | @form@ element or @form@ attribute
form_ :: Term arg result => arg -> result
form_ :: forall arg result. Term arg result => arg -> result
form_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"form"

-- | @h1@ element
h1_ :: Term arg result => arg -> result
h1_ :: forall arg result. Term arg result => arg -> result
h1_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h1"

-- | @h2@ element
h2_ :: Term arg result => arg -> result
h2_ :: forall arg result. Term arg result => arg -> result
h2_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h2"

-- | @h3@ element
h3_ :: Term arg result => arg -> result
h3_ :: forall arg result. Term arg result => arg -> result
h3_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h3"

-- | @h4@ element
h4_ :: Term arg result => arg -> result
h4_ :: forall arg result. Term arg result => arg -> result
h4_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h4"

-- | @h5@ element
h5_ :: Term arg result => arg -> result
h5_ :: forall arg result. Term arg result => arg -> result
h5_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h5"

-- | @h6@ element
h6_ :: Term arg result => arg -> result
h6_ :: forall arg result. Term arg result => arg -> result
h6_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"h6"

-- | @head@ element
head_ :: Term arg result => arg -> result
head_ :: forall arg result. Term arg result => arg -> result
head_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"head"

-- | @header@ element
header_ :: Term arg result => arg -> result
header_ :: forall arg result. Term arg result => arg -> result
header_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"header"

-- | @hgroup@ element
hgroup_ :: Term arg result => arg -> result
hgroup_ :: forall arg result. Term arg result => arg -> result
hgroup_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"hgroup"

-- | @hr@ element
hr_ :: Monad m => [Attributes] -> HtmlT m ()
hr_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
hr_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"hr"

-- | @html@ element
html_ :: Term arg result => arg -> result
html_ :: forall arg result. Term arg result => arg -> result
html_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"html"

-- | @i@ element
i_ :: Term arg result => arg -> result
i_ :: forall arg result. Term arg result => arg -> result
i_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"i"

-- | @iframe@ element
iframe_ :: Term arg result => arg -> result
iframe_ :: forall arg result. Term arg result => arg -> result
iframe_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"iframe"

-- | @img@ element
img_ :: Monad m => [Attributes] -> HtmlT m ()
img_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
img_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"img"

-- | @input@ element
input_ :: Monad m => [Attributes] -> HtmlT m ()
input_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
input_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"input"

-- | @ins@ element
ins_ :: Term arg result => arg -> result
ins_ :: forall arg result. Term arg result => arg -> result
ins_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"ins"

-- | @kbd@ element
kbd_ :: Term arg result => arg -> result
kbd_ :: forall arg result. Term arg result => arg -> result
kbd_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"kbd"

-- | @keygen@ element
keygen_ :: Monad m => [Attributes] -> HtmlT m ()
keygen_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
keygen_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"keygen"

-- | @label@ element or @label@ attribute
label_ :: Term arg result => arg -> result
label_ :: forall arg result. Term arg result => arg -> result
label_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"label"

-- | @legend@ element
legend_ :: Term arg result => arg -> result
legend_ :: forall arg result. Term arg result => arg -> result
legend_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"legend"

-- | @li@ element
li_ :: Term arg result => arg -> result
li_ :: forall arg result. Term arg result => arg -> result
li_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"li"

-- | @link@ element
link_ :: Monad m => [Attributes] -> HtmlT m ()
link_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
link_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"link"

-- | @map@ element
map_ :: Term arg result => arg -> result
map_ :: forall arg result. Term arg result => arg -> result
map_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"map"

-- | @main@ element
main_ :: Term arg result => arg -> result
main_ :: forall arg result. Term arg result => arg -> result
main_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"main"

-- | @mark@ element
mark_ :: Term arg result => arg -> result
mark_ :: forall arg result. Term arg result => arg -> result
mark_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"mark"

-- | @menu@ element
menu_ :: Term arg result => arg -> result
menu_ :: forall arg result. Term arg result => arg -> result
menu_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"menu"

-- | @menuitem@ element
menuitem_ :: Monad m => [Attributes] -> HtmlT m ()
menuitem_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
menuitem_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"menuitem"

-- | @meta@ element
meta_ :: Monad m => [Attributes] -> HtmlT m ()
meta_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
meta_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"meta"

-- | @meter@ element
meter_ :: Term arg result => arg -> result
meter_ :: forall arg result. Term arg result => arg -> result
meter_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"meter"

-- | @nav@ element
nav_ :: Term arg result => arg -> result
nav_ :: forall arg result. Term arg result => arg -> result
nav_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"nav"

-- | @noscript@ element
noscript_ :: Term arg result => arg -> result
noscript_ :: forall arg result. Term arg result => arg -> result
noscript_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"noscript"

-- | @object@ element
object_ :: Term arg result => arg -> result
object_ :: forall arg result. Term arg result => arg -> result
object_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"object"

-- | @ol@ element
ol_ :: Term arg result => arg -> result
ol_ :: forall arg result. Term arg result => arg -> result
ol_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"ol"

-- | @optgroup@ element
optgroup_ :: Term arg result => arg -> result
optgroup_ :: forall arg result. Term arg result => arg -> result
optgroup_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"optgroup"

-- | @option@ element
option_ :: Term arg result => arg -> result
option_ :: forall arg result. Term arg result => arg -> result
option_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"option"

-- | @output@ element
output_ :: Term arg result => arg -> result
output_ :: forall arg result. Term arg result => arg -> result
output_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"output"

-- | @p@ element
p_ :: Term arg result => arg -> result
p_ :: forall arg result. Term arg result => arg -> result
p_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"p"

-- | @param@ element
param_ :: Monad m => [Attributes] -> HtmlT m ()
param_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
param_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"param"

-- | The @svg@ attribute.
svg_ :: Term arg result => arg -> result
svg_ :: forall arg result. Term arg result => arg -> result
svg_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"svg"

-- | @pre@ element
pre_ :: Term arg result => arg -> result
pre_ :: forall arg result. Term arg result => arg -> result
pre_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"pre"

-- | @progress@ element
progress_ :: Term arg result => arg -> result
progress_ :: forall arg result. Term arg result => arg -> result
progress_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"progress"

-- | @q@ element
q_ :: Term arg result => arg -> result
q_ :: forall arg result. Term arg result => arg -> result
q_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"q"

-- | @rp@ element
rp_ :: Term arg result => arg -> result
rp_ :: forall arg result. Term arg result => arg -> result
rp_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"rp"

-- | @rt@ element
rt_ :: Term arg result => arg -> result
rt_ :: forall arg result. Term arg result => arg -> result
rt_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"rt"

-- | @ruby@ element
ruby_ :: Term arg result => arg -> result
ruby_ :: forall arg result. Term arg result => arg -> result
ruby_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"ruby"

-- | @samp@ element
samp_ :: Term arg result => arg -> result
samp_ :: forall arg result. Term arg result => arg -> result
samp_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"samp"

-- | @script@ element
script_ :: TermRaw arg result => arg -> result
script_ :: forall arg result. TermRaw arg result => arg -> result
script_ = forall arg result. TermRaw arg result => Text -> arg -> result
termRaw Text
"script"

-- | @section@ element
section_ :: Term arg result => arg -> result
section_ :: forall arg result. Term arg result => arg -> result
section_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"section"

-- | @select@ element
select_ :: Term arg result => arg -> result
select_ :: forall arg result. Term arg result => arg -> result
select_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"select"

-- | @small@ element
small_ :: Term arg result => arg -> result
small_ :: forall arg result. Term arg result => arg -> result
small_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"small"

-- | @source@ element
source_ :: Monad m => [Attributes] -> HtmlT m ()
source_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
source_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"source"

-- | @span@ element or @span@ attribute
span_ :: Term arg result => arg -> result
span_ :: forall arg result. Term arg result => arg -> result
span_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"span"

-- | @strong@ element
strong_ :: Term arg result => arg -> result
strong_ :: forall arg result. Term arg result => arg -> result
strong_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"strong"

-- | @style@ element or @style@ attribute
style_ :: TermRaw arg result => arg -> result
style_ :: forall arg result. TermRaw arg result => arg -> result
style_ = forall arg result. TermRaw arg result => Text -> arg -> result
termRaw Text
"style"

-- | @sub@ element
sub_ :: Term arg result => arg -> result
sub_ :: forall arg result. Term arg result => arg -> result
sub_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"sub"

-- | @summary@ element or @summary@ attribute
summary_ :: Term arg result => arg -> result
summary_ :: forall arg result. Term arg result => arg -> result
summary_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"summary"

-- | @sup@ element
sup_ :: Term arg result => arg -> result
sup_ :: forall arg result. Term arg result => arg -> result
sup_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"sup"

-- | @table@ element
table_ :: Term arg result => arg -> result
table_ :: forall arg result. Term arg result => arg -> result
table_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"table"

-- | @tbody@ element
tbody_ :: Term arg result => arg -> result
tbody_ :: forall arg result. Term arg result => arg -> result
tbody_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"tbody"

-- | @td@ element
td_ :: Term arg result => arg -> result
td_ :: forall arg result. Term arg result => arg -> result
td_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"td"

-- | @textarea@ element
textarea_ :: Term arg result => arg -> result
textarea_ :: forall arg result. Term arg result => arg -> result
textarea_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"textarea"

-- | @tfoot@ element
tfoot_ :: Term arg result => arg -> result
tfoot_ :: forall arg result. Term arg result => arg -> result
tfoot_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"tfoot"

-- | @th@ element
th_ :: Term arg result => arg -> result
th_ :: forall arg result. Term arg result => arg -> result
th_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"th"

-- | @template@ element
template_ :: Term arg result => arg -> result
template_ :: forall arg result. Term arg result => arg -> result
template_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"template"

-- | @thead@ element
thead_ :: Term arg result => arg -> result
thead_ :: forall arg result. Term arg result => arg -> result
thead_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"thead"

-- | @time@ element
time_ :: Term arg result => arg -> result
time_ :: forall arg result. Term arg result => arg -> result
time_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"time"

-- | @title@ element or @title@ attribute
title_ :: Term arg result => arg -> result
title_ :: forall arg result. Term arg result => arg -> result
title_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"title"

-- | @tr@ element
tr_ :: Term arg result => arg -> result
tr_ :: forall arg result. Term arg result => arg -> result
tr_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"tr"

-- | @track@ element
track_ :: Monad m => [Attributes] -> HtmlT m ()
track_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
track_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"track"

-- | @ul@ element
ul_ :: Term arg result => arg -> result
ul_ :: forall arg result. Term arg result => arg -> result
ul_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"ul"

-- | @var@ element
var_ :: Term arg result => arg -> result
var_ :: forall arg result. Term arg result => arg -> result
var_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"var"

-- | @video@ element
video_ :: Term arg result => arg -> result
video_ :: forall arg result. Term arg result => arg -> result
video_ = forall arg result. Term arg result => Text -> arg -> result
term Text
"video"

-- | @wbr@ element
wbr_ :: Monad m => [Attributes] -> HtmlT m ()
wbr_ :: forall (m :: * -> *). Monad m => [Attributes] -> HtmlT m ()
wbr_ = forall (m :: * -> *). Monad m => Text -> [Attributes] -> HtmlT m ()
makeElementNoEnd Text
"wbr"

-------------------------------------------------------------------------------
-- Attributes

-- | The @accept@ attribute.
accept_ :: Text -> Attributes
accept_ :: Text -> Attributes
accept_ = Text -> Text -> Attributes
makeAttributes Text
"accept"

-- | The @acceptCharset@ attribute.
acceptCharset_ :: Text -> Attributes
acceptCharset_ :: Text -> Attributes
acceptCharset_ = Text -> Text -> Attributes
makeAttributes Text
"accept-charset"

-- | The @accesskey@ attribute.
accesskey_ :: Text -> Attributes
accesskey_ :: Text -> Attributes
accesskey_ = Text -> Text -> Attributes
makeAttributes Text
"accesskey"

-- | The @action@ attribute.
action_ :: Text -> Attributes
action_ :: Text -> Attributes
action_ = Text -> Text -> Attributes
makeAttributes Text
"action"

-- | The @alt@ attribute.
alt_ :: Text -> Attributes
alt_ :: Text -> Attributes
alt_ = Text -> Text -> Attributes
makeAttributes Text
"alt"

-- | The @async@ attribute.
async_ :: Text -> Attributes
async_ :: Text -> Attributes
async_ = Text -> Text -> Attributes
makeAttributes Text
"async"

-- | The @autocomplete@ attribute.
autocomplete_ :: Text -> Attributes
autocomplete_ :: Text -> Attributes
autocomplete_ = Text -> Text -> Attributes
makeAttributes Text
"autocomplete"

-- | The @autofocus@ attribute.
autofocus_ :: Attributes
autofocus_ :: Attributes
autofocus_ = Text -> Text -> Attributes
makeAttributes Text
"autofocus" forall a. Monoid a => a
mempty

-- | The @autoplay@ attribute.
autoplay_ :: Text -> Attributes
autoplay_ :: Text -> Attributes
autoplay_ = Text -> Text -> Attributes
makeAttributes Text
"autoplay"

-- | The @challenge@ attribute.
challenge_ :: Text -> Attributes
challenge_ :: Text -> Attributes
challenge_ = Text -> Text -> Attributes
makeAttributes Text
"challenge"

-- | The @charset@ attribute.
charset_ :: Text -> Attributes
charset_ :: Text -> Attributes
charset_ = Text -> Text -> Attributes
makeAttributes Text
"charset"

-- | The @checked@ attribute.
checked_ :: Attributes
checked_ :: Attributes
checked_ = Text -> Text -> Attributes
makeAttributes Text
"checked" forall a. Monoid a => a
mempty

-- | The @class@ attribute.
class_ :: Text -> Attributes
class_ :: Text -> Attributes
class_ = Text -> Text -> Attributes
makeAttributes Text
"class"

-- | The @cols@ attribute.
cols_ :: Text -> Attributes
cols_ :: Text -> Attributes
cols_ = Text -> Text -> Attributes
makeAttributes Text
"cols"

-- | The @colspan@ attribute.
colspan_ :: Text -> Attributes
colspan_ :: Text -> Attributes
colspan_ = Text -> Text -> Attributes
makeAttributes Text
"colspan"

-- | The @content@ attribute.
content_ :: Text -> Attributes
content_ :: Text -> Attributes
content_ = Text -> Text -> Attributes
makeAttributes Text
"content"

-- | The @contenteditable@ attribute.
contenteditable_ :: Text -> Attributes
contenteditable_ :: Text -> Attributes
contenteditable_ = Text -> Text -> Attributes
makeAttributes Text
"contenteditable"

-- | The @contextmenu@ attribute.
contextmenu_ :: Text -> Attributes
contextmenu_ :: Text -> Attributes
contextmenu_ = Text -> Text -> Attributes
makeAttributes Text
"contextmenu"

-- | The @controls@ attribute.
controls_ :: Text -> Attributes
controls_ :: Text -> Attributes
controls_ = Text -> Text -> Attributes
makeAttributes Text
"controls"

-- | The @coords@ attribute.
coords_ :: Text -> Attributes
coords_ :: Text -> Attributes
coords_ = Text -> Text -> Attributes
makeAttributes Text
"coords"

-- | The @crossorigin@ attribute.
--
-- @since 2.9.8
crossorigin_ :: Text -> Attributes
crossorigin_ :: Text -> Attributes
crossorigin_ = Text -> Text -> Attributes
makeAttributes Text
"crossorigin"

-- | The @data@ attribute.
data_ :: Text -> Text -> Attributes
data_ :: Text -> Text -> Attributes
data_ Text
name = Text -> Text -> Attributes
makeAttributes (Text
"data-" forall a. Semigroup a => a -> a -> a
<> Text
name)

-- | The @datetime@ attribute.
datetime_ :: Text -> Attributes
datetime_ :: Text -> Attributes
datetime_ = Text -> Text -> Attributes
makeAttributes Text
"datetime"

-- | The @defer@ attribute.
defer_ :: Text -> Attributes
defer_ :: Text -> Attributes
defer_ = Text -> Text -> Attributes
makeAttributes Text
"defer"

-- | The @dir@ attribute.
dir_ :: Text -> Attributes
dir_ :: Text -> Attributes
dir_ = Text -> Text -> Attributes
makeAttributes Text
"dir"

-- | The @disabled@ attribute.
disabled_ :: Text -> Attributes
disabled_ :: Text -> Attributes
disabled_ = Text -> Text -> Attributes
makeAttributes Text
"disabled"

-- | The @download@ attribute.
download_ :: Text -> Attributes
download_ :: Text -> Attributes
download_ = Text -> Text -> Attributes
makeAttributes Text
"download"

-- | The @draggable@ attribute.
draggable_ :: Text -> Attributes
draggable_ :: Text -> Attributes
draggable_ = Text -> Text -> Attributes
makeAttributes Text
"draggable"

-- | The @enctype@ attribute.
enctype_ :: Text -> Attributes
enctype_ :: Text -> Attributes
enctype_ = Text -> Text -> Attributes
makeAttributes Text
"enctype"

-- | The @for@ attribute.
for_ :: Text -> Attributes
for_ :: Text -> Attributes
for_ = Text -> Text -> Attributes
makeAttributes Text
"for"

-- | The @formaction@ attribute.
formaction_ :: Text -> Attributes
formaction_ :: Text -> Attributes
formaction_ = Text -> Text -> Attributes
makeAttributes Text
"formaction"

-- | The @formenctype@ attribute.
formenctype_ :: Text -> Attributes
formenctype_ :: Text -> Attributes
formenctype_ = Text -> Text -> Attributes
makeAttributes Text
"formenctype"

-- | The @formmethod@ attribute.
formmethod_ :: Text -> Attributes
formmethod_ :: Text -> Attributes
formmethod_ = Text -> Text -> Attributes
makeAttributes Text
"formmethod"

-- | The @formnovalidate@ attribute.
formnovalidate_ :: Text -> Attributes
formnovalidate_ :: Text -> Attributes
formnovalidate_ = Text -> Text -> Attributes
makeAttributes Text
"formnovalidate"

-- | The @formtarget@ attribute.
formtarget_ :: Text -> Attributes
formtarget_ :: Text -> Attributes
formtarget_ = Text -> Text -> Attributes
makeAttributes Text
"formtarget"

-- | The @headers@ attribute.
headers_ :: Text -> Attributes
headers_ :: Text -> Attributes
headers_ = Text -> Text -> Attributes
makeAttributes Text
"headers"

-- | The @height@ attribute.
height_ :: Text -> Attributes
height_ :: Text -> Attributes
height_ = Text -> Text -> Attributes
makeAttributes Text
"height"

-- | The @hidden@ attribute.
hidden_ :: Text -> Attributes
hidden_ :: Text -> Attributes
hidden_ = Text -> Text -> Attributes
makeAttributes Text
"hidden"

-- | The @high@ attribute.
high_ :: Text -> Attributes
high_ :: Text -> Attributes
high_ = Text -> Text -> Attributes
makeAttributes Text
"high"

-- | The @href@ attribute.
href_ :: Text -> Attributes
href_ :: Text -> Attributes
href_ = Text -> Text -> Attributes
makeAttributes Text
"href"

-- | The @hreflang@ attribute.
hreflang_ :: Text -> Attributes
hreflang_ :: Text -> Attributes
hreflang_ = Text -> Text -> Attributes
makeAttributes Text
"hreflang"

-- | The @httpEquiv@ attribute.
httpEquiv_ :: Text -> Attributes
httpEquiv_ :: Text -> Attributes
httpEquiv_ = Text -> Text -> Attributes
makeAttributes Text
"http-equiv"

-- | The @icon@ attribute.
icon_ :: Text -> Attributes
icon_ :: Text -> Attributes
icon_ = Text -> Text -> Attributes
makeAttributes Text
"icon"

-- | The @id@ attribute.
id_ :: Text -> Attributes
id_ :: Text -> Attributes
id_ = Text -> Text -> Attributes
makeAttributes Text
"id"

-- | The @integrity@ attribute.
--
-- @since 2.9.8
integrity_ :: Text -> Attributes
integrity_ :: Text -> Attributes
integrity_ = Text -> Text -> Attributes
makeAttributes Text
"integrity"

-- | The @ismap@ attribute.
ismap_ :: Text -> Attributes
ismap_ :: Text -> Attributes
ismap_ = Text -> Text -> Attributes
makeAttributes Text
"ismap"

-- | The @item@ attribute.
item_ :: Text -> Attributes
item_ :: Text -> Attributes
item_ = Text -> Text -> Attributes
makeAttributes Text
"item"

-- | The @itemprop@ attribute.
itemprop_ :: Text -> Attributes
itemprop_ :: Text -> Attributes
itemprop_ = Text -> Text -> Attributes
makeAttributes Text
"itemprop"

-- | The @keytype@ attribute.
keytype_ :: Text -> Attributes
keytype_ :: Text -> Attributes
keytype_ = Text -> Text -> Attributes
makeAttributes Text
"keytype"

-- | The @lang@ attribute.
lang_ :: Text -> Attributes
lang_ :: Text -> Attributes
lang_ = Text -> Text -> Attributes
makeAttributes Text
"lang"

-- | The @list@ attribute.
list_ :: Text -> Attributes
list_ :: Text -> Attributes
list_ = Text -> Text -> Attributes
makeAttributes Text
"list"

-- | The @loading@ attribute.
loading_ :: Text -> Attributes
loading_ :: Text -> Attributes
loading_ = Text -> Text -> Attributes
makeAttributes Text
"loading"

-- | The @loop@ attribute.
loop_ :: Text -> Attributes
loop_ :: Text -> Attributes
loop_ = Text -> Text -> Attributes
makeAttributes Text
"loop"

-- | The @low@ attribute.
low_ :: Text -> Attributes
low_ :: Text -> Attributes
low_ = Text -> Text -> Attributes
makeAttributes Text
"low"

-- | The @manifest@ attribute.
manifest_ :: Text -> Attributes
manifest_ :: Text -> Attributes
manifest_ = Text -> Text -> Attributes
makeAttributes Text
"manifest"

-- | The @max@ attribute.
max_ :: Text -> Attributes
max_ :: Text -> Attributes
max_ = Text -> Text -> Attributes
makeAttributes Text
"max"

-- | The @maxlength@ attribute.
maxlength_ :: Text -> Attributes
maxlength_ :: Text -> Attributes
maxlength_ = Text -> Text -> Attributes
makeAttributes Text
"maxlength"

-- | The @media@ attribute.
media_ :: Text -> Attributes
media_ :: Text -> Attributes
media_ = Text -> Text -> Attributes
makeAttributes Text
"media"

-- | The @method@ attribute.
method_ :: Text -> Attributes
method_ :: Text -> Attributes
method_ = Text -> Text -> Attributes
makeAttributes Text
"method"

-- | The @min@ attribute.
min_ :: Text -> Attributes
min_ :: Text -> Attributes
min_ = Text -> Text -> Attributes
makeAttributes Text
"min"

-- | The @minlength@ attribute.
minlength_ :: Text -> Attributes
minlength_ :: Text -> Attributes
minlength_ = Text -> Text -> Attributes
makeAttributes Text
"minlength"

-- | The @multiple@ attribute.
multiple_ :: Text -> Attributes
multiple_ :: Text -> Attributes
multiple_ = Text -> Text -> Attributes
makeAttributes Text
"multiple"

-- | The @name@ attribute.
name_ :: Text -> Attributes
name_ :: Text -> Attributes
name_ = Text -> Text -> Attributes
makeAttributes Text
"name"

-- | The @novalidate@ attribute.
novalidate_ :: Text -> Attributes
novalidate_ :: Text -> Attributes
novalidate_ = Text -> Text -> Attributes
makeAttributes Text
"novalidate"

-- | The @onbeforeonload@ attribute.
onbeforeonload_ :: Text -> Attributes
onbeforeonload_ :: Text -> Attributes
onbeforeonload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onbeforeonload"

-- | The @onbeforeprint@ attribute.
onbeforeprint_ :: Text -> Attributes
onbeforeprint_ :: Text -> Attributes
onbeforeprint_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onbeforeprint"

-- | The @onblur@ attribute.
onblur_ :: Text -> Attributes
onblur_ :: Text -> Attributes
onblur_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onblur"

-- | The @oncanplay@ attribute.
oncanplay_ :: Text -> Attributes
oncanplay_ :: Text -> Attributes
oncanplay_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oncanplay"

-- | The @oncanplaythrough@ attribute.
oncanplaythrough_ :: Text -> Attributes
oncanplaythrough_ :: Text -> Attributes
oncanplaythrough_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oncanplaythrough"

-- | The @onchange@ attribute.
onchange_ :: Text -> Attributes
onchange_ :: Text -> Attributes
onchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onchange"

-- | The @onclick@ attribute.
onclick_ :: Text -> Attributes
onclick_ :: Text -> Attributes
onclick_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onclick"

-- | The @oncontextmenu@ attribute.
oncontextmenu_ :: Text -> Attributes
oncontextmenu_ :: Text -> Attributes
oncontextmenu_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oncontextmenu"

-- | The @ondblclick@ attribute.
ondblclick_ :: Text -> Attributes
ondblclick_ :: Text -> Attributes
ondblclick_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondblclick"

-- | The @ondrag@ attribute.
ondrag_ :: Text -> Attributes
ondrag_ :: Text -> Attributes
ondrag_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondrag"

-- | The @ondragend@ attribute.
ondragend_ :: Text -> Attributes
ondragend_ :: Text -> Attributes
ondragend_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragend"

-- | The @ondragenter@ attribute.
ondragenter_ :: Text -> Attributes
ondragenter_ :: Text -> Attributes
ondragenter_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragenter"

-- | The @ondragleave@ attribute.
ondragleave_ :: Text -> Attributes
ondragleave_ :: Text -> Attributes
ondragleave_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragleave"

-- | The @ondragover@ attribute.
ondragover_ :: Text -> Attributes
ondragover_ :: Text -> Attributes
ondragover_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragover"

-- | The @ondragstart@ attribute.
ondragstart_ :: Text -> Attributes
ondragstart_ :: Text -> Attributes
ondragstart_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondragstart"

-- | The @ondrop@ attribute.
ondrop_ :: Text -> Attributes
ondrop_ :: Text -> Attributes
ondrop_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondrop"

-- | The @ondurationchange@ attribute.
ondurationchange_ :: Text -> Attributes
ondurationchange_ :: Text -> Attributes
ondurationchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ondurationchange"

-- | The @onemptied@ attribute.
onemptied_ :: Text -> Attributes
onemptied_ :: Text -> Attributes
onemptied_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onemptied"

-- | The @onended@ attribute.
onended_ :: Text -> Attributes
onended_ :: Text -> Attributes
onended_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onended"

-- | The @onerror@ attribute.
onerror_ :: Text -> Attributes
onerror_ :: Text -> Attributes
onerror_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onerror"

-- | The @onfocus@ attribute.
onfocus_ :: Text -> Attributes
onfocus_ :: Text -> Attributes
onfocus_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onfocus"

-- | The @onformchange@ attribute.
onformchange_ :: Text -> Attributes
onformchange_ :: Text -> Attributes
onformchange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onformchange"

-- | The @onforminput@ attribute.
onforminput_ :: Text -> Attributes
onforminput_ :: Text -> Attributes
onforminput_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onforminput"

-- | The @onhaschange@ attribute.
onhaschange_ :: Text -> Attributes
onhaschange_ :: Text -> Attributes
onhaschange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onhaschange"

-- | The @oninput@ attribute.
oninput_ :: Text -> Attributes
oninput_ :: Text -> Attributes
oninput_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oninput"

-- | The @oninvalid@ attribute.
oninvalid_ :: Text -> Attributes
oninvalid_ :: Text -> Attributes
oninvalid_ = Text -> Text -> Attributes
makeAttributesRaw Text
"oninvalid"

-- | The @onkeydown@ attribute.
onkeydown_ :: Text -> Attributes
onkeydown_ :: Text -> Attributes
onkeydown_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onkeydown"

-- | The @onkeyup@ attribute.
onkeyup_ :: Text -> Attributes
onkeyup_ :: Text -> Attributes
onkeyup_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onkeyup"

-- | The @onload@ attribute.
onload_ :: Text -> Attributes
onload_ :: Text -> Attributes
onload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onload"

-- | The @onloadeddata@ attribute.
onloadeddata_ :: Text -> Attributes
onloadeddata_ :: Text -> Attributes
onloadeddata_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadeddata"

-- | The @onloadedmetadata@ attribute.
onloadedmetadata_ :: Text -> Attributes
onloadedmetadata_ :: Text -> Attributes
onloadedmetadata_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadedmetadata"

-- | The @onloadstart@ attribute.
onloadstart_ :: Text -> Attributes
onloadstart_ :: Text -> Attributes
onloadstart_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onloadstart"

-- | The @onmessage@ attribute.
onmessage_ :: Text -> Attributes
onmessage_ :: Text -> Attributes
onmessage_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmessage"

-- | The @onmousedown@ attribute.
onmousedown_ :: Text -> Attributes
onmousedown_ :: Text -> Attributes
onmousedown_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousedown"

-- | The @onmousemove@ attribute.
onmousemove_ :: Text -> Attributes
onmousemove_ :: Text -> Attributes
onmousemove_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousemove"

-- | The @onmouseout@ attribute.
onmouseout_ :: Text -> Attributes
onmouseout_ :: Text -> Attributes
onmouseout_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseout"

-- | The @onmouseover@ attribute.
onmouseover_ :: Text -> Attributes
onmouseover_ :: Text -> Attributes
onmouseover_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseover"

-- | The @onmouseup@ attribute.
onmouseup_ :: Text -> Attributes
onmouseup_ :: Text -> Attributes
onmouseup_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmouseup"

-- | The @onmousewheel@ attribute.
onmousewheel_ :: Text -> Attributes
onmousewheel_ :: Text -> Attributes
onmousewheel_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onmousewheel"

-- | The @ononline@ attribute.
ononline_ :: Text -> Attributes
ononline_ :: Text -> Attributes
ononline_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ononline"

-- | The @onpagehide@ attribute.
onpagehide_ :: Text -> Attributes
onpagehide_ :: Text -> Attributes
onpagehide_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpagehide"

-- | The @onpageshow@ attribute.
onpageshow_ :: Text -> Attributes
onpageshow_ :: Text -> Attributes
onpageshow_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpageshow"

-- | The @onpause@ attribute.
onpause_ :: Text -> Attributes
onpause_ :: Text -> Attributes
onpause_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpause"

-- | The @onplay@ attribute.
onplay_ :: Text -> Attributes
onplay_ :: Text -> Attributes
onplay_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onplay"

-- | The @onplaying@ attribute.
onplaying_ :: Text -> Attributes
onplaying_ :: Text -> Attributes
onplaying_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onplaying"

-- | The @onprogress@ attribute.
onprogress_ :: Text -> Attributes
onprogress_ :: Text -> Attributes
onprogress_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onprogress"

-- | The @onpropstate@ attribute.
onpropstate_ :: Text -> Attributes
onpropstate_ :: Text -> Attributes
onpropstate_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onpropstate"

-- | The @onratechange@ attribute.
onratechange_ :: Text -> Attributes
onratechange_ :: Text -> Attributes
onratechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onratechange"

-- | The @onreadystatechange@ attribute.
onreadystatechange_ :: Text -> Attributes
onreadystatechange_ :: Text -> Attributes
onreadystatechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onreadystatechange"

-- | The @onredo@ attribute.
onredo_ :: Text -> Attributes
onredo_ :: Text -> Attributes
onredo_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onredo"

-- | The @onresize@ attribute.
onresize_ :: Text -> Attributes
onresize_ :: Text -> Attributes
onresize_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onresize"

-- | The @onscroll@ attribute.
onscroll_ :: Text -> Attributes
onscroll_ :: Text -> Attributes
onscroll_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onscroll"

-- | The @onseeked@ attribute.
onseeked_ :: Text -> Attributes
onseeked_ :: Text -> Attributes
onseeked_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onseeked"

-- | The @onseeking@ attribute.
onseeking_ :: Text -> Attributes
onseeking_ :: Text -> Attributes
onseeking_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onseeking"

-- | The @onselect@ attribute.
onselect_ :: Text -> Attributes
onselect_ :: Text -> Attributes
onselect_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onselect"

-- | The @onstalled@ attribute.
onstalled_ :: Text -> Attributes
onstalled_ :: Text -> Attributes
onstalled_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onstalled"

-- | The @onstorage@ attribute.
onstorage_ :: Text -> Attributes
onstorage_ :: Text -> Attributes
onstorage_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onstorage"

-- | The @onsubmit@ attribute.
onsubmit_ :: Text -> Attributes
onsubmit_ :: Text -> Attributes
onsubmit_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onsubmit"

-- | The @onsuspend@ attribute.
onsuspend_ :: Text -> Attributes
onsuspend_ :: Text -> Attributes
onsuspend_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onsuspend"

-- | The @ontimeupdate@ attribute.
ontimeupdate_ :: Text -> Attributes
ontimeupdate_ :: Text -> Attributes
ontimeupdate_ = Text -> Text -> Attributes
makeAttributesRaw Text
"ontimeupdate"

-- | The @onundo@ attribute.
onundo_ :: Text -> Attributes
onundo_ :: Text -> Attributes
onundo_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onundo"

-- | The @onunload@ attribute.
onunload_ :: Text -> Attributes
onunload_ :: Text -> Attributes
onunload_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onunload"

-- | The @onvolumechange@ attribute.
onvolumechange_ :: Text -> Attributes
onvolumechange_ :: Text -> Attributes
onvolumechange_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onvolumechange"

-- | The @onwaiting@ attribute.
onwaiting_ :: Text -> Attributes
onwaiting_ :: Text -> Attributes
onwaiting_ = Text -> Text -> Attributes
makeAttributesRaw Text
"onwaiting"

-- | The @open@ attribute.
open_ :: Text -> Attributes
open_ :: Text -> Attributes
open_ = Text -> Text -> Attributes
makeAttributes Text
"open"

-- | The @optimum@ attribute.
optimum_ :: Text -> Attributes
optimum_ :: Text -> Attributes
optimum_ = Text -> Text -> Attributes
makeAttributes Text
"optimum"

-- | The @pattern@ attribute.
pattern_ :: Text -> Attributes
pattern_ :: Text -> Attributes
pattern_ = Text -> Text -> Attributes
makeAttributes Text
"pattern"

-- | The @ping@ attribute.
ping_ :: Text -> Attributes
ping_ :: Text -> Attributes
ping_ = Text -> Text -> Attributes
makeAttributes Text
"ping"

-- | The @placeholder@ attribute.
placeholder_ :: Text -> Attributes
placeholder_ :: Text -> Attributes
placeholder_ = Text -> Text -> Attributes
makeAttributes Text
"placeholder"

-- | The @poster@ attribute.
poster_ :: Text -> Attributes
poster_ :: Text -> Attributes
poster_ = Text -> Text -> Attributes
makeAttributes Text
"poster"

-- | The @preload@ attribute.
preload_ :: Text -> Attributes
preload_ :: Text -> Attributes
preload_ = Text -> Text -> Attributes
makeAttributes Text
"preload"

-- | The @pubdate@ attribute.
pubdate_ :: Text -> Attributes
pubdate_ :: Text -> Attributes
pubdate_ = Text -> Text -> Attributes
makeAttributes Text
"pubdate"

-- | The @radiogroup@ attribute.
radiogroup_ :: Text -> Attributes
radiogroup_ :: Text -> Attributes
radiogroup_ = Text -> Text -> Attributes
makeAttributes Text
"radiogroup"

-- | The @readonly@ attribute.
readonly_ :: Text -> Attributes
readonly_ :: Text -> Attributes
readonly_ = Text -> Text -> Attributes
makeAttributes Text
"readonly"

-- | The @rel@ attribute.
rel_ :: Text -> Attributes
rel_ :: Text -> Attributes
rel_ = Text -> Text -> Attributes
makeAttributes Text
"rel"

-- | The @required@ attribute.
required_ :: Text -> Attributes
required_ :: Text -> Attributes
required_ = Text -> Text -> Attributes
makeAttributes Text
"required"

-- | The @reversed@ attribute.
reversed_ :: Text -> Attributes
reversed_ :: Text -> Attributes
reversed_ = Text -> Text -> Attributes
makeAttributes Text
"reversed"

-- | The @role@ attribute.
role_ :: Text -> Attributes
role_ :: Text -> Attributes
role_ = Text -> Text -> Attributes
makeAttributes Text
"role"

-- | The @rows@ attribute.
rows_ :: Text -> Attributes
rows_ :: Text -> Attributes
rows_ = Text -> Text -> Attributes
makeAttributes Text
"rows"

-- | The @rowspan@ attribute.
rowspan_ :: Text -> Attributes
rowspan_ :: Text -> Attributes
rowspan_ = Text -> Text -> Attributes
makeAttributes Text
"rowspan"

-- | The @sandbox@ attribute.
sandbox_ :: Text -> Attributes
sandbox_ :: Text -> Attributes
sandbox_ = Text -> Text -> Attributes
makeAttributes Text
"sandbox"

-- | The @scope@ attribute.
scope_ :: Text -> Attributes
scope_ :: Text -> Attributes
scope_ = Text -> Text -> Attributes
makeAttributes Text
"scope"

-- | The @scoped@ attribute.
scoped_ :: Text -> Attributes
scoped_ :: Text -> Attributes
scoped_ = Text -> Text -> Attributes
makeAttributes Text
"scoped"

-- | The @seamless@ attribute.
seamless_ :: Text -> Attributes
seamless_ :: Text -> Attributes
seamless_ = Text -> Text -> Attributes
makeAttributes Text
"seamless"

-- | The @selected@ attribute.
selected_ :: Text -> Attributes
selected_ :: Text -> Attributes
selected_ = Text -> Text -> Attributes
makeAttributes Text
"selected"

-- | The @shape@ attribute.
shape_ :: Text -> Attributes
shape_ :: Text -> Attributes
shape_ = Text -> Text -> Attributes
makeAttributes Text
"shape"

-- | The @size@ attribute.
size_ :: Text -> Attributes
size_ :: Text -> Attributes
size_ = Text -> Text -> Attributes
makeAttributes Text
"size"

-- | The @sizes@ attribute.
sizes_ :: Text -> Attributes
sizes_ :: Text -> Attributes
sizes_ = Text -> Text -> Attributes
makeAttributes Text
"sizes"

-- | The @spellcheck@ attribute.
spellcheck_ :: Text -> Attributes
spellcheck_ :: Text -> Attributes
spellcheck_ = Text -> Text -> Attributes
makeAttributes Text
"spellcheck"

-- | The @src@ attribute.
src_ :: Text -> Attributes
src_ :: Text -> Attributes
src_ = Text -> Text -> Attributes
makeAttributes Text
"src"

-- | The @srcdoc@ attribute.
srcdoc_ :: Text -> Attributes
srcdoc_ :: Text -> Attributes
srcdoc_ = Text -> Text -> Attributes
makeAttributes Text
"srcdoc"

-- | The @start@ attribute.
start_ :: Text -> Attributes
start_ :: Text -> Attributes
start_ = Text -> Text -> Attributes
makeAttributes Text
"start"

-- | The @step@ attribute.
step_ :: Text -> Attributes
step_ :: Text -> Attributes
step_ = Text -> Text -> Attributes
makeAttributes Text
"step"

-- | The @subject@ attribute.
subject_ :: Text -> Attributes
subject_ :: Text -> Attributes
subject_ = Text -> Text -> Attributes
makeAttributes Text
"subject"

-- | The @tabindex@ attribute.
tabindex_ :: Text -> Attributes
tabindex_ :: Text -> Attributes
tabindex_ = Text -> Text -> Attributes
makeAttributes Text
"tabindex"

-- | The @target@ attribute.
target_ :: Text -> Attributes
target_ :: Text -> Attributes
target_ = Text -> Text -> Attributes
makeAttributes Text
"target"

-- | The @type@ attribute.
type_ :: Text -> Attributes
type_ :: Text -> Attributes
type_ = Text -> Text -> Attributes
makeAttributes Text
"type"

-- | The @usemap@ attribute.
usemap_ :: Text -> Attributes
usemap_ :: Text -> Attributes
usemap_ = Text -> Text -> Attributes
makeAttributes Text
"usemap"

-- | The @value@ attribute.
value_ :: Text -> Attributes
value_ :: Text -> Attributes
value_ = Text -> Text -> Attributes
makeAttributes Text
"value"

-- | The @width@ attribute.
width_ :: Text -> Attributes
width_ :: Text -> Attributes
width_ = Text -> Text -> Attributes
makeAttributes Text
"width"

-- | The @wrap@ attribute.
wrap_ :: Text -> Attributes
wrap_ :: Text -> Attributes
wrap_ = Text -> Text -> Attributes
makeAttributes Text
"wrap"

-- | The @xmlns@ attribute.
xmlns_ :: Text -> Attributes
xmlns_ :: Text -> Attributes
xmlns_ = Text -> Text -> Attributes
makeAttributes Text
"xmlns"