{-# LANGUAGE NoImplicitPrelude #-}

module Blizzard.Html.Attributes
    ( accept
    , acceptCharset
    , accesskey
    , action
    , alt
    , async
    , autocomplete
    , autofocus
    , autoplay
    , challenge
    , charset
    , checked
    , cite
    , css
    , cols
    , colspan
    , content
    , contenteditable
    , contextmenu
    , controls
    , coords
    , data_
    , datetime
    , defer
    , dir
    , disabled
    , draggable
    , enctype
    , for
    , form
    , formaction
    , formenctype
    , formmethod
    , formnovalidate
    , formtarget
    , headers
    , height
    , hidden
    , high
    , href
    , hreflang
    , httpEquiv
    , icon
    , id
    , ismap
    , item
    , itemprop
    , itemscope
    , itemtype
    , keytype
    , label
    , lang
    , list
    , loop
    , low
    , manifest
    , max
    , maxlength
    , media
    , method
    , min
    , multiple
    , name
    , novalidate
    , onbeforeonload
    , onbeforeprint
    , onblur
    , oncanplay
    , oncanplaythrough
    , onchange
    , onclick
    , oncontextmenu
    , ondblclick
    , ondrag
    , ondragend
    , ondragenter
    , ondragleave
    , ondragover
    , ondragstart
    , ondrop
    , ondurationchange
    , onemptied
    , onended
    , onerror
    , onfocus
    , onformchange
    , onforminput
    , onhaschange
    , oninput
    , oninvalid
    , onkeydown
    , onkeyup
    , onload
    , onloadeddata
    , onloadedmetadata
    , onloadstart
    , onmessage
    , onmousedown
    , onmousemove
    , onmouseout
    , onmouseover
    , onmouseup
    , onmousewheel
    , ononline
    , onpagehide
    , onpageshow
    , onpause
    , onplay
    , onplaying
    , onprogress
    , onpropstate
    , onratechange
    , onreadystatechange
    , onredo
    , onresize
    , onscroll
    , onseeked
    , onseeking
    , onselect
    , onstalled
    , onstorage
    , onsubmit
    , onsuspend
    , ontimeupdate
    , onundo
    , onunload
    , onvolumechange
    , onwaiting
    , open
    , optimum
    , pattern
    , ping
    , placeholder
    , preload
    , pubdate
    , radiogroup
    , readonly
    , rel
    , required
    , reversed
    , role
    , rows
    , rowspan
    , sandbox
    , scope
    , scoped
    , seamless
    , selected
    , shape
    , size
    , sizes
    , span
    , spellcheck
    , src
    , srcdoc
    , start
    , step
    , style
    , subject
    , summary
    , tabindex
    , target
    , title
    , type_
    , usemap
    , value
    , width
    , wrap
    , xmlns
    ) where


import Data.Text (Text, unwords)
import Prelude ((.))
import Text.Blaze.Html5 (Attribute, textValue)

import qualified Text.Blaze.Html5.Attributes as Attr


accept :: Text -> Attribute
accept :: Text -> Attribute
accept = AttributeValue -> Attribute
Attr.accept (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


acceptCharset :: Text -> Attribute
acceptCharset :: Text -> Attribute
acceptCharset = AttributeValue -> Attribute
Attr.acceptCharset (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


accesskey :: Text -> Attribute
accesskey :: Text -> Attribute
accesskey = AttributeValue -> Attribute
Attr.accesskey (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


action :: Text -> Attribute
action :: Text -> Attribute
action = AttributeValue -> Attribute
Attr.action (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


alt :: Text -> Attribute
alt :: Text -> Attribute
alt = AttributeValue -> Attribute
Attr.alt (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


async :: Text -> Attribute
async :: Text -> Attribute
async = AttributeValue -> Attribute
Attr.async (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


autocomplete :: Text -> Attribute
autocomplete :: Text -> Attribute
autocomplete = AttributeValue -> Attribute
Attr.autocomplete (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


autofocus :: Text -> Attribute
autofocus :: Text -> Attribute
autofocus = AttributeValue -> Attribute
Attr.autofocus (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


autoplay :: Text -> Attribute
autoplay :: Text -> Attribute
autoplay = AttributeValue -> Attribute
Attr.autoplay (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


challenge :: Text -> Attribute
challenge :: Text -> Attribute
challenge = AttributeValue -> Attribute
Attr.challenge (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


charset :: Text -> Attribute
charset :: Text -> Attribute
charset = AttributeValue -> Attribute
Attr.charset (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


checked :: Text -> Attribute
checked :: Text -> Attribute
checked = AttributeValue -> Attribute
Attr.checked (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


cite :: Text -> Attribute
cite :: Text -> Attribute
cite = AttributeValue -> Attribute
Attr.cite (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


css :: [Text] -> Attribute
css :: [Text] -> Attribute
css = AttributeValue -> Attribute
Attr.class_ (AttributeValue -> Attribute)
-> ([Text] -> AttributeValue) -> [Text] -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue (Text -> AttributeValue)
-> ([Text] -> Text) -> [Text] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
unwords


cols :: Text -> Attribute
cols :: Text -> Attribute
cols = AttributeValue -> Attribute
Attr.cols (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


colspan :: Text -> Attribute
colspan :: Text -> Attribute
colspan = AttributeValue -> Attribute
Attr.colspan (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


content :: Text -> Attribute
content :: Text -> Attribute
content = AttributeValue -> Attribute
Attr.content (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


contenteditable :: Text -> Attribute
contenteditable :: Text -> Attribute
contenteditable = AttributeValue -> Attribute
Attr.contenteditable (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


contextmenu :: Text -> Attribute
contextmenu :: Text -> Attribute
contextmenu = AttributeValue -> Attribute
Attr.contextmenu (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


controls :: Text -> Attribute
controls :: Text -> Attribute
controls = AttributeValue -> Attribute
Attr.controls (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


coords :: Text -> Attribute
coords :: Text -> Attribute
coords = AttributeValue -> Attribute
Attr.coords (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


data_ :: Text -> Attribute
data_ :: Text -> Attribute
data_ = AttributeValue -> Attribute
Attr.data_ (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


datetime :: Text -> Attribute
datetime :: Text -> Attribute
datetime = AttributeValue -> Attribute
Attr.datetime (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


defer :: Text -> Attribute
defer :: Text -> Attribute
defer = AttributeValue -> Attribute
Attr.defer (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


dir :: Text -> Attribute
dir :: Text -> Attribute
dir = AttributeValue -> Attribute
Attr.dir (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


disabled :: Text -> Attribute
disabled :: Text -> Attribute
disabled = AttributeValue -> Attribute
Attr.disabled (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


draggable :: Text -> Attribute
draggable :: Text -> Attribute
draggable = AttributeValue -> Attribute
Attr.draggable (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


enctype :: Text -> Attribute
enctype :: Text -> Attribute
enctype = AttributeValue -> Attribute
Attr.enctype (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


for :: Text -> Attribute
for :: Text -> Attribute
for = AttributeValue -> Attribute
Attr.for (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


form :: Text -> Attribute
form :: Text -> Attribute
form = AttributeValue -> Attribute
Attr.form (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


formaction :: Text -> Attribute
formaction :: Text -> Attribute
formaction = AttributeValue -> Attribute
Attr.formaction (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


formenctype :: Text -> Attribute
formenctype :: Text -> Attribute
formenctype = AttributeValue -> Attribute
Attr.formenctype (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


formmethod :: Text -> Attribute
formmethod :: Text -> Attribute
formmethod = AttributeValue -> Attribute
Attr.formmethod (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


formnovalidate :: Text -> Attribute
formnovalidate :: Text -> Attribute
formnovalidate = AttributeValue -> Attribute
Attr.formnovalidate (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


formtarget :: Text -> Attribute
formtarget :: Text -> Attribute
formtarget = AttributeValue -> Attribute
Attr.formtarget (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


headers :: Text -> Attribute
headers :: Text -> Attribute
headers = AttributeValue -> Attribute
Attr.headers (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


height :: Text -> Attribute
height :: Text -> Attribute
height = AttributeValue -> Attribute
Attr.height (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


hidden :: Text -> Attribute
hidden :: Text -> Attribute
hidden = AttributeValue -> Attribute
Attr.hidden (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


high :: Text -> Attribute
high :: Text -> Attribute
high = AttributeValue -> Attribute
Attr.high (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


href :: Text -> Attribute
href :: Text -> Attribute
href = AttributeValue -> Attribute
Attr.href (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


hreflang :: Text -> Attribute
hreflang :: Text -> Attribute
hreflang = AttributeValue -> Attribute
Attr.hreflang (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


httpEquiv :: Text -> Attribute
httpEquiv :: Text -> Attribute
httpEquiv = AttributeValue -> Attribute
Attr.httpEquiv (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


icon :: Text -> Attribute
icon :: Text -> Attribute
icon = AttributeValue -> Attribute
Attr.icon (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


id :: Text -> Attribute
id :: Text -> Attribute
id = AttributeValue -> Attribute
Attr.id (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ismap :: Text -> Attribute
ismap :: Text -> Attribute
ismap = AttributeValue -> Attribute
Attr.ismap (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


item :: Text -> Attribute
item :: Text -> Attribute
item = AttributeValue -> Attribute
Attr.item (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


itemprop :: Text -> Attribute
itemprop :: Text -> Attribute
itemprop = AttributeValue -> Attribute
Attr.itemprop (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


itemscope :: Text -> Attribute
itemscope :: Text -> Attribute
itemscope = AttributeValue -> Attribute
Attr.itemscope (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


itemtype :: Text -> Attribute
itemtype :: Text -> Attribute
itemtype = AttributeValue -> Attribute
Attr.itemtype (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


keytype :: Text -> Attribute
keytype :: Text -> Attribute
keytype = AttributeValue -> Attribute
Attr.keytype (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


label :: Text -> Attribute
label :: Text -> Attribute
label = AttributeValue -> Attribute
Attr.label (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


lang :: Text -> Attribute
lang :: Text -> Attribute
lang = AttributeValue -> Attribute
Attr.lang (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


list :: Text -> Attribute
list :: Text -> Attribute
list = AttributeValue -> Attribute
Attr.list (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


loop :: Text -> Attribute
loop :: Text -> Attribute
loop = AttributeValue -> Attribute
Attr.loop (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


low :: Text -> Attribute
low :: Text -> Attribute
low = AttributeValue -> Attribute
Attr.low (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


manifest :: Text -> Attribute
manifest :: Text -> Attribute
manifest = AttributeValue -> Attribute
Attr.manifest (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


max :: Text -> Attribute
max :: Text -> Attribute
max = AttributeValue -> Attribute
Attr.max (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


maxlength :: Text -> Attribute
maxlength :: Text -> Attribute
maxlength = AttributeValue -> Attribute
Attr.maxlength (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


media :: Text -> Attribute
media :: Text -> Attribute
media = AttributeValue -> Attribute
Attr.media (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


method :: Text -> Attribute
method :: Text -> Attribute
method = AttributeValue -> Attribute
Attr.method (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


min :: Text -> Attribute
min :: Text -> Attribute
min = AttributeValue -> Attribute
Attr.min (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


multiple :: Text -> Attribute
multiple :: Text -> Attribute
multiple = AttributeValue -> Attribute
Attr.multiple (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


name :: Text -> Attribute
name :: Text -> Attribute
name = AttributeValue -> Attribute
Attr.name (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


novalidate :: Text -> Attribute
novalidate :: Text -> Attribute
novalidate = AttributeValue -> Attribute
Attr.novalidate (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onbeforeonload :: Text -> Attribute
onbeforeonload :: Text -> Attribute
onbeforeonload = AttributeValue -> Attribute
Attr.onbeforeonload (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onbeforeprint :: Text -> Attribute
onbeforeprint :: Text -> Attribute
onbeforeprint = AttributeValue -> Attribute
Attr.onbeforeprint (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onblur :: Text -> Attribute
onblur :: Text -> Attribute
onblur = AttributeValue -> Attribute
Attr.onblur (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


oncanplay :: Text -> Attribute
oncanplay :: Text -> Attribute
oncanplay = AttributeValue -> Attribute
Attr.oncanplay (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


oncanplaythrough :: Text -> Attribute
oncanplaythrough :: Text -> Attribute
oncanplaythrough = AttributeValue -> Attribute
Attr.oncanplaythrough (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onchange :: Text -> Attribute
onchange :: Text -> Attribute
onchange = AttributeValue -> Attribute
Attr.onchange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onclick :: Text -> Attribute
onclick :: Text -> Attribute
onclick = AttributeValue -> Attribute
Attr.onclick (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


oncontextmenu :: Text -> Attribute
oncontextmenu :: Text -> Attribute
oncontextmenu = AttributeValue -> Attribute
Attr.oncontextmenu (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondblclick :: Text -> Attribute
ondblclick :: Text -> Attribute
ondblclick = AttributeValue -> Attribute
Attr.ondblclick (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondrag :: Text -> Attribute
ondrag :: Text -> Attribute
ondrag = AttributeValue -> Attribute
Attr.ondrag (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondragend :: Text -> Attribute
ondragend :: Text -> Attribute
ondragend = AttributeValue -> Attribute
Attr.ondragend (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondragenter :: Text -> Attribute
ondragenter :: Text -> Attribute
ondragenter = AttributeValue -> Attribute
Attr.ondragenter (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondragleave :: Text -> Attribute
ondragleave :: Text -> Attribute
ondragleave = AttributeValue -> Attribute
Attr.ondragleave (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondragover :: Text -> Attribute
ondragover :: Text -> Attribute
ondragover = AttributeValue -> Attribute
Attr.ondragover (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondragstart :: Text -> Attribute
ondragstart :: Text -> Attribute
ondragstart = AttributeValue -> Attribute
Attr.ondragstart (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondrop :: Text -> Attribute
ondrop :: Text -> Attribute
ondrop = AttributeValue -> Attribute
Attr.ondrop (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ondurationchange :: Text -> Attribute
ondurationchange :: Text -> Attribute
ondurationchange = AttributeValue -> Attribute
Attr.ondurationchange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onemptied :: Text -> Attribute
onemptied :: Text -> Attribute
onemptied = AttributeValue -> Attribute
Attr.onemptied (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onended :: Text -> Attribute
onended :: Text -> Attribute
onended = AttributeValue -> Attribute
Attr.onended (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onerror :: Text -> Attribute
onerror :: Text -> Attribute
onerror = AttributeValue -> Attribute
Attr.onerror (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onfocus :: Text -> Attribute
onfocus :: Text -> Attribute
onfocus = AttributeValue -> Attribute
Attr.onfocus (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onformchange :: Text -> Attribute
onformchange :: Text -> Attribute
onformchange = AttributeValue -> Attribute
Attr.onformchange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onforminput :: Text -> Attribute
onforminput :: Text -> Attribute
onforminput = AttributeValue -> Attribute
Attr.onforminput (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onhaschange :: Text -> Attribute
onhaschange :: Text -> Attribute
onhaschange = AttributeValue -> Attribute
Attr.onhaschange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


oninput :: Text -> Attribute
oninput :: Text -> Attribute
oninput = AttributeValue -> Attribute
Attr.oninput (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


oninvalid :: Text -> Attribute
oninvalid :: Text -> Attribute
oninvalid = AttributeValue -> Attribute
Attr.oninvalid (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onkeydown :: Text -> Attribute
onkeydown :: Text -> Attribute
onkeydown = AttributeValue -> Attribute
Attr.onkeydown (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onkeyup :: Text -> Attribute
onkeyup :: Text -> Attribute
onkeyup = AttributeValue -> Attribute
Attr.onkeyup (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onload :: Text -> Attribute
onload :: Text -> Attribute
onload = AttributeValue -> Attribute
Attr.onload (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onloadeddata :: Text -> Attribute
onloadeddata :: Text -> Attribute
onloadeddata = AttributeValue -> Attribute
Attr.onloadeddata (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onloadedmetadata :: Text -> Attribute
onloadedmetadata :: Text -> Attribute
onloadedmetadata = AttributeValue -> Attribute
Attr.onloadedmetadata (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onloadstart :: Text -> Attribute
onloadstart :: Text -> Attribute
onloadstart = AttributeValue -> Attribute
Attr.onloadstart (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmessage :: Text -> Attribute
onmessage :: Text -> Attribute
onmessage = AttributeValue -> Attribute
Attr.onmessage (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmousedown :: Text -> Attribute
onmousedown :: Text -> Attribute
onmousedown = AttributeValue -> Attribute
Attr.onmousedown (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmousemove :: Text -> Attribute
onmousemove :: Text -> Attribute
onmousemove = AttributeValue -> Attribute
Attr.onmousemove (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmouseout :: Text -> Attribute
onmouseout :: Text -> Attribute
onmouseout = AttributeValue -> Attribute
Attr.onmouseout (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmouseover :: Text -> Attribute
onmouseover :: Text -> Attribute
onmouseover = AttributeValue -> Attribute
Attr.onmouseover (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmouseup :: Text -> Attribute
onmouseup :: Text -> Attribute
onmouseup = AttributeValue -> Attribute
Attr.onmouseup (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onmousewheel :: Text -> Attribute
onmousewheel :: Text -> Attribute
onmousewheel = AttributeValue -> Attribute
Attr.onmousewheel (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ononline :: Text -> Attribute
ononline :: Text -> Attribute
ononline = AttributeValue -> Attribute
Attr.ononline (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onpagehide :: Text -> Attribute
onpagehide :: Text -> Attribute
onpagehide = AttributeValue -> Attribute
Attr.onpagehide (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onpageshow :: Text -> Attribute
onpageshow :: Text -> Attribute
onpageshow = AttributeValue -> Attribute
Attr.onpageshow (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onpause :: Text -> Attribute
onpause :: Text -> Attribute
onpause = AttributeValue -> Attribute
Attr.onpause (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onplay :: Text -> Attribute
onplay :: Text -> Attribute
onplay = AttributeValue -> Attribute
Attr.onplay (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onplaying :: Text -> Attribute
onplaying :: Text -> Attribute
onplaying = AttributeValue -> Attribute
Attr.onplaying (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onprogress :: Text -> Attribute
onprogress :: Text -> Attribute
onprogress = AttributeValue -> Attribute
Attr.onprogress (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onpropstate :: Text -> Attribute
onpropstate :: Text -> Attribute
onpropstate = AttributeValue -> Attribute
Attr.onpropstate (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onratechange :: Text -> Attribute
onratechange :: Text -> Attribute
onratechange = AttributeValue -> Attribute
Attr.onratechange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onreadystatechange :: Text -> Attribute
onreadystatechange :: Text -> Attribute
onreadystatechange = AttributeValue -> Attribute
Attr.onreadystatechange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onredo :: Text -> Attribute
onredo :: Text -> Attribute
onredo = AttributeValue -> Attribute
Attr.onredo (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onresize :: Text -> Attribute
onresize :: Text -> Attribute
onresize = AttributeValue -> Attribute
Attr.onresize (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onscroll :: Text -> Attribute
onscroll :: Text -> Attribute
onscroll = AttributeValue -> Attribute
Attr.onscroll (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onseeked :: Text -> Attribute
onseeked :: Text -> Attribute
onseeked = AttributeValue -> Attribute
Attr.onseeked (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onseeking :: Text -> Attribute
onseeking :: Text -> Attribute
onseeking = AttributeValue -> Attribute
Attr.onseeking (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onselect :: Text -> Attribute
onselect :: Text -> Attribute
onselect = AttributeValue -> Attribute
Attr.onselect (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onstalled :: Text -> Attribute
onstalled :: Text -> Attribute
onstalled = AttributeValue -> Attribute
Attr.onstalled (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onstorage :: Text -> Attribute
onstorage :: Text -> Attribute
onstorage = AttributeValue -> Attribute
Attr.onstorage (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onsubmit :: Text -> Attribute
onsubmit :: Text -> Attribute
onsubmit = AttributeValue -> Attribute
Attr.onsubmit (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onsuspend :: Text -> Attribute
onsuspend :: Text -> Attribute
onsuspend = AttributeValue -> Attribute
Attr.onsuspend (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ontimeupdate :: Text -> Attribute
ontimeupdate :: Text -> Attribute
ontimeupdate = AttributeValue -> Attribute
Attr.ontimeupdate (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onundo :: Text -> Attribute
onundo :: Text -> Attribute
onundo = AttributeValue -> Attribute
Attr.onundo (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onunload :: Text -> Attribute
onunload :: Text -> Attribute
onunload = AttributeValue -> Attribute
Attr.onunload (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onvolumechange :: Text -> Attribute
onvolumechange :: Text -> Attribute
onvolumechange = AttributeValue -> Attribute
Attr.onvolumechange (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


onwaiting :: Text -> Attribute
onwaiting :: Text -> Attribute
onwaiting = AttributeValue -> Attribute
Attr.onwaiting (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


open :: Text -> Attribute
open :: Text -> Attribute
open = AttributeValue -> Attribute
Attr.open (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


optimum :: Text -> Attribute
optimum :: Text -> Attribute
optimum = AttributeValue -> Attribute
Attr.optimum (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


pattern :: Text -> Attribute
pattern :: Text -> Attribute
pattern = AttributeValue -> Attribute
Attr.pattern (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


ping :: Text -> Attribute
ping :: Text -> Attribute
ping = AttributeValue -> Attribute
Attr.ping (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


placeholder :: Text -> Attribute
placeholder :: Text -> Attribute
placeholder = AttributeValue -> Attribute
Attr.placeholder (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


preload :: Text -> Attribute
preload :: Text -> Attribute
preload = AttributeValue -> Attribute
Attr.preload (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


pubdate :: Text -> Attribute
pubdate :: Text -> Attribute
pubdate = AttributeValue -> Attribute
Attr.pubdate (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


radiogroup :: Text -> Attribute
radiogroup :: Text -> Attribute
radiogroup = AttributeValue -> Attribute
Attr.radiogroup (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


readonly :: Text -> Attribute
readonly :: Text -> Attribute
readonly = AttributeValue -> Attribute
Attr.readonly (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


rel :: Text -> Attribute
rel :: Text -> Attribute
rel = AttributeValue -> Attribute
Attr.rel (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


required :: Text -> Attribute
required :: Text -> Attribute
required = AttributeValue -> Attribute
Attr.required (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


reversed :: Text -> Attribute
reversed :: Text -> Attribute
reversed = AttributeValue -> Attribute
Attr.reversed (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


role :: Text -> Attribute
role :: Text -> Attribute
role = AttributeValue -> Attribute
Attr.role (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


rows :: Text -> Attribute
rows :: Text -> Attribute
rows = AttributeValue -> Attribute
Attr.rows (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


rowspan :: Text -> Attribute
rowspan :: Text -> Attribute
rowspan = AttributeValue -> Attribute
Attr.rowspan (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


sandbox :: Text -> Attribute
sandbox :: Text -> Attribute
sandbox = AttributeValue -> Attribute
Attr.sandbox (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


scope :: Text -> Attribute
scope :: Text -> Attribute
scope = AttributeValue -> Attribute
Attr.scope (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


scoped :: Text -> Attribute
scoped :: Text -> Attribute
scoped = AttributeValue -> Attribute
Attr.scoped (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


seamless :: Text -> Attribute
seamless :: Text -> Attribute
seamless = AttributeValue -> Attribute
Attr.seamless (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


selected :: Text -> Attribute
selected :: Text -> Attribute
selected = AttributeValue -> Attribute
Attr.selected (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


shape :: Text -> Attribute
shape :: Text -> Attribute
shape = AttributeValue -> Attribute
Attr.shape (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


size :: Text -> Attribute
size :: Text -> Attribute
size = AttributeValue -> Attribute
Attr.size (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


sizes :: Text -> Attribute
sizes :: Text -> Attribute
sizes = AttributeValue -> Attribute
Attr.sizes (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


span :: Text -> Attribute
span :: Text -> Attribute
span = AttributeValue -> Attribute
Attr.span (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


spellcheck :: Text -> Attribute
spellcheck :: Text -> Attribute
spellcheck = AttributeValue -> Attribute
Attr.spellcheck (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


src :: Text -> Attribute
src :: Text -> Attribute
src = AttributeValue -> Attribute
Attr.src (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


srcdoc :: Text -> Attribute
srcdoc :: Text -> Attribute
srcdoc = AttributeValue -> Attribute
Attr.srcdoc (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


start :: Text -> Attribute
start :: Text -> Attribute
start = AttributeValue -> Attribute
Attr.start (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


step :: Text -> Attribute
step :: Text -> Attribute
step = AttributeValue -> Attribute
Attr.step (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


style :: [Text] -> Attribute
style :: [Text] -> Attribute
style = AttributeValue -> Attribute
Attr.style (AttributeValue -> Attribute)
-> ([Text] -> AttributeValue) -> [Text] -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue (Text -> AttributeValue)
-> ([Text] -> Text) -> [Text] -> AttributeValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
unwords


subject :: Text -> Attribute
subject :: Text -> Attribute
subject = AttributeValue -> Attribute
Attr.subject (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


summary :: Text -> Attribute
summary :: Text -> Attribute
summary = AttributeValue -> Attribute
Attr.summary (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


tabindex :: Text -> Attribute
tabindex :: Text -> Attribute
tabindex = AttributeValue -> Attribute
Attr.tabindex (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


target :: Text -> Attribute
target :: Text -> Attribute
target = AttributeValue -> Attribute
Attr.target (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


title :: Text -> Attribute
title :: Text -> Attribute
title = AttributeValue -> Attribute
Attr.title (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


type_ :: Text -> Attribute
type_ :: Text -> Attribute
type_ = AttributeValue -> Attribute
Attr.type_ (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


usemap :: Text -> Attribute
usemap :: Text -> Attribute
usemap = AttributeValue -> Attribute
Attr.usemap (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


value :: Text -> Attribute
value :: Text -> Attribute
value = AttributeValue -> Attribute
Attr.value (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


width :: Text -> Attribute
width :: Text -> Attribute
width = AttributeValue -> Attribute
Attr.width (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


wrap :: Text -> Attribute
wrap :: Text -> Attribute
wrap = AttributeValue -> Attribute
Attr.wrap (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue


xmlns :: Text -> Attribute
xmlns :: Text -> Attribute
xmlns = AttributeValue -> Attribute
Attr.xmlns (AttributeValue -> Attribute)
-> (Text -> AttributeValue) -> Text -> Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AttributeValue
textValue