module Halogen.HTML.Elements where
import DOM.HTML.Indexed qualified as I
import Data.Coerce
import HPrelude hiding (div, head, map)
import Halogen.HTML.Core (HTML (..))
import Halogen.HTML.Properties hiding (style, title)
import Halogen.VDom qualified as VDom
import Halogen.VDom.Types
type Node r w msg = [IProp r msg] -> [HTML w msg] -> HTML w msg
type Leaf r w msg = [IProp r msg] -> HTML w msg
type Array a = [a]
element :: forall r w i. ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element :: forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element ElemName
en Array (IProp r i)
props Array (HTML w i)
htmls =
VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (VDom [Prop (Input i)] w -> HTML w i)
-> VDom [Prop (Input i)] w -> HTML w i
forall a b. (a -> b) -> a -> b
$ Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [VDom [Prop (Input i)] w]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [VDom a w] -> VDom a w
VDom.Elem Maybe Namespace
forall a. Maybe a
Nothing ElemName
en (Array (IProp r i) -> [Prop (Input i)]
forall a b. Coercible a b => a -> b
coerce Array (IProp r i)
props) ((HTML w i -> VDom [Prop (Input i)] w)
-> Array (HTML w i) -> [VDom [Prop (Input i)] w]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (.unHTML) Array (HTML w i)
htmls)
elementNS :: forall r w i. Namespace -> ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
elementNS :: forall (r :: Row (*)) w i.
Namespace
-> ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
elementNS Namespace
ns ElemName
en Array (IProp r i)
props Array (HTML w i)
htmls =
VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (VDom [Prop (Input i)] w -> HTML w i)
-> VDom [Prop (Input i)] w -> HTML w i
forall a b. (a -> b) -> a -> b
$ Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [VDom [Prop (Input i)] w]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [VDom a w] -> VDom a w
VDom.Elem (Namespace -> Maybe Namespace
forall a. a -> Maybe a
Just Namespace
ns) ElemName
en (Array (IProp r i) -> [Prop (Input i)]
forall a b. Coercible a b => a -> b
coerce Array (IProp r i)
props) ((HTML w i -> VDom [Prop (Input i)] w)
-> Array (HTML w i) -> [VDom [Prop (Input i)] w]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (.unHTML) Array (HTML w i)
htmls)
keyed :: forall r w i. ElemName -> Array (IProp r i) -> Array (Text, HTML w i) -> HTML w i
keyed :: forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (Text, HTML w i) -> HTML w i
keyed ElemName
_name Array (IProp r i)
props Array (Text, HTML w i)
children =
VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (VDom [Prop (Input i)] w -> HTML w i)
-> VDom [Prop (Input i)] w -> HTML w i
forall a b. (a -> b) -> a -> b
$ Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [(Text, VDom [Prop (Input i)] w)]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [(Text, VDom a w)] -> VDom a w
VDom.Keyed Maybe Namespace
forall a. Maybe a
Nothing ElemName
_name (Array (IProp r i) -> [Prop (Input i)]
forall a b. Coercible a b => a -> b
coerce Array (IProp r i)
props) (((Text, HTML w i) -> (Text, VDom [Prop (Input i)] w))
-> Array (Text, HTML w i) -> [(Text, VDom [Prop (Input i)] w)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((HTML w i -> VDom [Prop (Input i)] w)
-> (Text, HTML w i) -> (Text, VDom [Prop (Input i)] w)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (.unHTML)) Array (Text, HTML w i)
children)
keyedNS :: forall r w i. Namespace -> ElemName -> Array (IProp r i) -> Array (Text, HTML w i) -> HTML w i
keyedNS :: forall (r :: Row (*)) w i.
Namespace
-> ElemName
-> Array (IProp r i)
-> Array (Text, HTML w i)
-> HTML w i
keyedNS Namespace
ns ElemName
_name Array (IProp r i)
props Array (Text, HTML w i)
children =
VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (VDom [Prop (Input i)] w -> HTML w i)
-> VDom [Prop (Input i)] w -> HTML w i
forall a b. (a -> b) -> a -> b
$ Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [(Text, VDom [Prop (Input i)] w)]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [(Text, VDom a w)] -> VDom a w
VDom.Keyed (Namespace -> Maybe Namespace
forall a. a -> Maybe a
Just Namespace
ns) ElemName
_name (Array (IProp r i) -> [Prop (Input i)]
forall a b. Coercible a b => a -> b
coerce Array (IProp r i)
props) (((Text, HTML w i) -> (Text, VDom [Prop (Input i)] w))
-> Array (Text, HTML w i) -> [(Text, VDom [Prop (Input i)] w)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((HTML w i -> VDom [Prop (Input i)] w)
-> (Text, HTML w i) -> (Text, VDom [Prop (Input i)] w)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (.unHTML)) Array (Text, HTML w i)
children)
withKeys :: forall r w i. (Array (IProp r i) -> Array (HTML w i) -> HTML w i) -> Array (IProp r i) -> Array (Text, HTML w i) -> HTML w i
withKeys :: forall (r :: Row (*)) w i.
(Array (IProp r i) -> Array (HTML w i) -> HTML w i)
-> Array (IProp r i) -> Array (Text, HTML w i) -> HTML w i
withKeys Array (IProp r i) -> Array (HTML w i) -> HTML w i
ctor Array (IProp r i)
props Array (Text, HTML w i)
children =
case Array (IProp r i) -> Array (HTML w i) -> HTML w i
ctor Array (IProp r i)
props [] of
HTML (VDom.Elem Maybe Namespace
x ElemName
y [Prop (Input i)]
z [VDom [Prop (Input i)] w]
_) -> VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [(Text, VDom [Prop (Input i)] w)]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [(Text, VDom a w)] -> VDom a w
VDom.Keyed Maybe Namespace
x ElemName
y [Prop (Input i)]
z (Array (Text, HTML w i) -> [(Text, VDom [Prop (Input i)] w)]
forall a b. Coercible a b => a -> b
coerce Array (Text, HTML w i)
children))
HTML w i
h -> HTML w i
h
withKeys_ :: forall w i. (Array (HTML w i) -> HTML w i) -> Array (Text, HTML w i) -> HTML w i
withKeys_ :: forall w i.
(Array (HTML w i) -> HTML w i)
-> Array (Text, HTML w i) -> HTML w i
withKeys_ Array (HTML w i) -> HTML w i
ctor Array (Text, HTML w i)
children =
case Array (HTML w i) -> HTML w i
ctor [] of
HTML (VDom.Elem Maybe Namespace
x ElemName
y [Prop (Input i)]
z [VDom [Prop (Input i)] w]
_) -> VDom [Prop (Input i)] w -> HTML w i
forall w i. VDom [Prop (Input i)] w -> HTML w i
HTML (Maybe Namespace
-> ElemName
-> [Prop (Input i)]
-> [(Text, VDom [Prop (Input i)] w)]
-> VDom [Prop (Input i)] w
forall a w.
Maybe Namespace -> ElemName -> a -> [(Text, VDom a w)] -> VDom a w
VDom.Keyed Maybe Namespace
x ElemName
y [Prop (Input i)]
z (Array (Text, HTML w i) -> [(Text, VDom [Prop (Input i)] w)]
forall a b. Coercible a b => a -> b
coerce Array (Text, HTML w i)
children))
HTML w i
h -> HTML w i
h
a :: forall w i. Node I.HTMLa w i
a :: forall w i. Node HTMLa w i
a = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"download" ':-> Text, "draggable" ':-> Bool, "hidden" ':-> Bool,
"href" ':-> Text, "hrefLang" ':-> Text, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"rel" ':-> Text, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "target" ':-> Text, "title" ':-> Text,
"type" ':-> MediaType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"a")
a_ :: forall w i. Array (HTML w i) -> HTML w i
a_ :: forall w i. Array (HTML w i) -> HTML w i
a_ = Node HTMLa w i
forall w i. Node HTMLa w i
a []
abbr :: forall w i. Node I.HTMLabbr w i
abbr :: forall w i. Node HTMLabbr w i
abbr = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"abbr")
abbr_ :: forall w i. Array (HTML w i) -> HTML w i
abbr_ :: forall w i. Array (HTML w i) -> HTML w i
abbr_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
abbr []
address :: forall w i. Node I.HTMLaddress w i
address :: forall w i. Node HTMLaddress w i
address = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"address")
address_ :: forall w i. Array (HTML w i) -> HTML w i
address_ :: forall w i. Array (HTML w i) -> HTML w i
address_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
address []
area :: forall w i. Leaf I.HTMLarea w i
area :: forall w i. Leaf HTMLarea w i
area [IProp HTMLarea i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "coords" ':-> Text,
"dir" ':-> DirValue, "download" ':-> Text, "draggable" ':-> Bool,
"hidden" ':-> Bool, "href" ':-> Text, "hrefLang" ':-> Text,
"id" ':-> Text, "lang" ':-> Text, "media" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"rel" ':-> Text, "shape" ':-> Text, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "target" ':-> Text,
"title" ':-> Text, "type" ':-> MediaType])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"area") [IProp HTMLarea i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "coords" ':-> Text,
"dir" ':-> DirValue, "download" ':-> Text, "draggable" ':-> Bool,
"hidden" ':-> Bool, "href" ':-> Text, "hrefLang" ':-> Text,
"id" ':-> Text, "lang" ':-> Text, "media" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"rel" ':-> Text, "shape" ':-> Text, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "target" ':-> Text,
"title" ':-> Text, "type" ':-> MediaType])
i)
props []
article :: forall w i. Node I.HTMLarticle w i
article :: forall w i. Node HTMLabbr w i
article = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"article")
article_ :: forall w i. Array (HTML w i) -> HTML w i
article_ :: forall w i. Array (HTML w i) -> HTML w i
article_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
article []
aside :: forall w i. Node I.HTMLaside w i
aside :: forall w i. Node HTMLabbr w i
aside = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"aside")
aside_ :: forall w i. Array (HTML w i) -> HTML w i
aside_ :: forall w i. Array (HTML w i) -> HTML w i
aside_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
aside []
audio :: forall w i. Node I.HTMLaudio w i
audio :: forall w i. Node HTMLaudio w i
audio = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "autoplay" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "controls" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "loop" ':-> Bool,
"muted" ':-> Bool, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onError" ':-> Event,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"preload" ':-> PreloadValue, "spellcheck" ':-> Bool,
"src" ':-> Text, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"audio")
audio_ :: forall w i. Array (HTML w i) -> HTML w i
audio_ :: forall w i. Array (HTML w i) -> HTML w i
audio_ = Node HTMLaudio w i
forall w i. Node HTMLaudio w i
audio []
b :: forall w i. Node I.HTMLb w i
b :: forall w i. Node HTMLabbr w i
b = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"b")
b_ :: forall w i. Array (HTML w i) -> HTML w i
b_ :: forall w i. Array (HTML w i) -> HTML w i
b_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
b []
base :: forall w i. Leaf I.HTMLbase w i
base :: forall w i. Leaf HTMLbase w i
base [IProp HTMLbase i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "href" ':-> Text,
"id" ':-> Text, "lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"target" ':-> Text, "title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"base") [IProp HTMLbase i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "href" ':-> Text,
"id" ':-> Text, "lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"target" ':-> Text, "title" ':-> Text])
i)
props []
bdi :: forall w i. Node I.HTMLbdi w i
bdi :: forall w i. Node HTMLabbr w i
bdi = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"bdi")
bdi_ :: forall w i. Array (HTML w i) -> HTML w i
bdi_ :: forall w i. Array (HTML w i) -> HTML w i
bdi_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
bdi []
bdo :: forall w i. Node I.HTMLbdo w i
bdo :: forall w i. Node HTMLbdo w i
bdo = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"bdo")
bdo_ :: forall w i. Array (HTML w i) -> HTML w i
bdo_ :: forall w i. Array (HTML w i) -> HTML w i
bdo_ = Node HTMLbdo w i
forall w i. Node HTMLbdo w i
bdo []
blockquote :: forall w i. Node I.HTMLblockquote w i
blockquote :: forall w i. Node HTMLblockquote w i
blockquote = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "cite" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"blockquote")
blockquote_ :: forall w i. Array (HTML w i) -> HTML w i
blockquote_ :: forall w i. Array (HTML w i) -> HTML w i
blockquote_ = Node HTMLblockquote w i
forall w i. Node HTMLblockquote w i
blockquote []
body :: forall w i. Node I.HTMLbody w i
body :: forall w i. Node HTMLbody w i
body = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBeforeUnload" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onHashChange" ':-> Event,
"onInput" ':-> Event, "onKeyDown" ':-> KeyboardEvent,
"onKeyPress" ':-> KeyboardEvent, "onKeyUp" ':-> KeyboardEvent,
"onLoad" ':-> Event, "onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPageHide" ':-> Event,
"onPageShow" ':-> Event, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onResize" ':-> Event, "onScroll" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onUnload" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"body")
body_ :: forall w i. Array (HTML w i) -> HTML w i
body_ :: forall w i. Array (HTML w i) -> HTML w i
body_ = Node HTMLbody w i
forall w i. Node HTMLbody w i
body []
br :: forall w i. Leaf I.HTMLbr w i
br :: forall w i. Leaf HTMLbdo w i
br [IProp HTMLbdo i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"br") [IProp HTMLbdo i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []
br_ :: forall w i. HTML w i
br_ :: forall w i. HTML w i
br_ = Leaf HTMLbdo w i
forall w i. Leaf HTMLbdo w i
br []
button :: forall w i. Node I.HTMLbutton w i
button :: forall w i. Node HTMLbutton w i
button = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "autofocus" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"formAction" ':-> Text, "formEncType" ':-> MediaType,
"formMethod" ':-> FormMethod, "formNoValidate" ':-> Bool,
"formTarget" ':-> Text, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "name" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "type" ':-> ButtonType, "value" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"button")
button_ :: forall w i. Array (HTML w i) -> HTML w i
button_ :: forall w i. Array (HTML w i) -> HTML w i
button_ = Node HTMLbutton w i
forall w i. Node HTMLbutton w i
button []
canvas :: forall w i. Leaf I.HTMLcanvas w i
canvas :: forall w i. Leaf HTMLcanvas w i
canvas [IProp HTMLcanvas i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "width" ':-> Int])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"canvas") [IProp HTMLcanvas i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "width" ':-> Int])
i)
props []
caption :: forall w i. Node I.HTMLcaption w i
caption :: forall w i. Node HTMLaddress w i
caption = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"caption")
caption_ :: forall w i. Array (HTML w i) -> HTML w i
caption_ :: forall w i. Array (HTML w i) -> HTML w i
caption_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
caption []
cite :: forall w i. Node I.HTMLcite w i
cite :: forall w i. Node HTMLabbr w i
cite = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"cite")
cite_ :: forall w i. Array (HTML w i) -> HTML w i
cite_ :: forall w i. Array (HTML w i) -> HTML w i
cite_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
cite []
code :: forall w i. Node I.HTMLcode w i
code :: forall w i. Node HTMLabbr w i
code = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"code")
code_ :: forall w i. Array (HTML w i) -> HTML w i
code_ :: forall w i. Array (HTML w i) -> HTML w i
code_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
code []
col :: forall w i. Leaf I.HTMLcol w i
col :: forall w i. Leaf HTMLabbr w i
col [IProp HTMLabbr i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"col") [IProp HTMLabbr i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []
colgroup :: forall w i. Node I.HTMLcolgroup w i
colgroup :: forall w i. Node HTMLcolgroup w i
colgroup = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"span" ':-> Int, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"colgroup")
colgroup_ :: forall w i. Array (HTML w i) -> HTML w i
colgroup_ :: forall w i. Array (HTML w i) -> HTML w i
colgroup_ = Node HTMLcolgroup w i
forall w i. Node HTMLcolgroup w i
colgroup []
command :: forall w i. Leaf I.HTMLcommand w i
command :: forall w i. Leaf HTMLabbr w i
command [IProp HTMLabbr i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"command") [IProp HTMLabbr i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []
datalist :: forall w i. Node I.HTMLdatalist w i
datalist :: forall w i. Node HTMLabbr w i
datalist = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"datalist")
datalist_ :: forall w i. Array (HTML w i) -> HTML w i
datalist_ :: forall w i. Array (HTML w i) -> HTML w i
datalist_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
datalist []
dd :: forall w i. Node I.HTMLdd w i
dd :: forall w i. Node HTMLaddress w i
dd = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"dd")
dd_ :: forall w i. Array (HTML w i) -> HTML w i
dd_ :: forall w i. Array (HTML w i) -> HTML w i
dd_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
dd []
del :: forall w i. Node I.HTMLdel w i
del :: forall w i. Node HTMLdel w i
del = ElemName
-> Array
(IProp
('R
'["UTCTime" ':-> Text, "accessKey" ':-> Text, "cite" ':-> Text,
"class" ':-> Text, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"del")
del_ :: forall w i. Array (HTML w i) -> HTML w i
del_ :: forall w i. Array (HTML w i) -> HTML w i
del_ = Node HTMLdel w i
forall w i. Node HTMLdel w i
del []
details :: forall w i. Node I.HTMLdetails w i
details :: forall w i. Node HTMLdetails w i
details = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"open" ':-> Bool, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"details")
details_ :: forall w i. Array (HTML w i) -> HTML w i
details_ :: forall w i. Array (HTML w i) -> HTML w i
details_ = Node HTMLdetails w i
forall w i. Node HTMLdetails w i
details []
dfn :: forall w i. Node I.HTMLdfn w i
dfn :: forall w i. Node HTMLabbr w i
dfn = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"dfn")
dfn_ :: forall w i. Array (HTML w i) -> HTML w i
dfn_ :: forall w i. Array (HTML w i) -> HTML w i
dfn_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
dfn []
dialog :: forall w i. Node I.HTMLdialog w i
dialog :: forall w i. Node HTMLdetails w i
dialog = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"open" ':-> Bool, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"dialog")
dialog_ :: forall w i. Array (HTML w i) -> HTML w i
dialog_ :: forall w i. Array (HTML w i) -> HTML w i
dialog_ = Node HTMLdetails w i
forall w i. Node HTMLdetails w i
dialog []
div :: forall w i. Node I.HTMLdiv w i
div :: forall w i. Node HTMLaddress w i
div = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"div")
div_ :: forall w i. Array (HTML w i) -> HTML w i
div_ :: forall w i. Array (HTML w i) -> HTML w i
div_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
div []
dl :: forall w i. Node I.HTMLdl w i
dl :: forall w i. Node HTMLaddress w i
dl = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"dl")
dl_ :: forall w i. Array (HTML w i) -> HTML w i
dl_ :: forall w i. Array (HTML w i) -> HTML w i
dl_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
dl []
dt :: forall w i. Node (I.HTMLdt) w i
dt :: forall w i. Node HTMLaddress w i
dt = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"dt")
dt_ :: forall w i. Array (HTML w i) -> HTML w i
dt_ :: forall w i. Array (HTML w i) -> HTML w i
dt_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
dt []
em :: forall w i. Node I.HTMLem w i
em :: forall w i. Node HTMLabbr w i
em = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"em")
em_ :: forall w i. Array (HTML w i) -> HTML w i
em_ :: forall w i. Array (HTML w i) -> HTML w i
em_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
em []
embed :: forall w i. Node I.HTMLembed w i
embed :: forall w i. Node HTMLembed w i
embed = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> MediaType,
"width" ':-> Int])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"embed")
embed_ :: forall w i. Array (HTML w i) -> HTML w i
embed_ :: forall w i. Array (HTML w i) -> HTML w i
embed_ = Node HTMLembed w i
forall w i. Node HTMLembed w i
embed []
fieldset :: forall w i. Node I.HTMLfieldset w i
fieldset :: forall w i. Node HTMLfieldset w i
fieldset = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"name" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"fieldset")
fieldset_ :: forall w i. Array (HTML w i) -> HTML w i
fieldset_ :: forall w i. Array (HTML w i) -> HTML w i
fieldset_ = Node HTMLfieldset w i
forall w i. Node HTMLfieldset w i
fieldset []
figcaption :: forall w i. Node I.HTMLfigcaption w i
figcaption :: forall w i. Node HTMLabbr w i
figcaption = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"figcaption")
figcaption_ :: forall w i. Array (HTML w i) -> HTML w i
figcaption_ :: forall w i. Array (HTML w i) -> HTML w i
figcaption_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
figcaption []
figure :: forall w i. Node I.HTMLfigure w i
figure :: forall w i. Node HTMLabbr w i
figure = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"figure")
figure_ :: forall w i. Array (HTML w i) -> HTML w i
figure_ :: forall w i. Array (HTML w i) -> HTML w i
figure_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
figure []
footer :: forall w i. Node I.HTMLfooter w i
= ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"footer")
footer_ :: forall w i. Array (HTML w i) -> HTML w i
= Node HTMLabbr w i
forall w i. Node HTMLabbr w i
footer []
form :: forall w i. Node I.HTMLform w i
form :: forall w i. Node HTMLform w i
form = ElemName
-> Array
(IProp
('R
'["acceptCharset" ':-> Text, "accessKey" ':-> Text,
"action" ':-> Text, "autocomplete" ':-> AutocompleteType,
"class" ':-> Text, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool,
"enctype" ':-> MediaType, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "method" ':-> FormMethod, "name" ':-> Text,
"noValidate" ':-> Bool, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onReset" ':-> Event, "onScroll" ':-> Event, "onSubmit" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"target" ':-> Text, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"form")
form_ :: forall w i. Array (HTML w i) -> HTML w i
form_ :: forall w i. Array (HTML w i) -> HTML w i
form_ = Node HTMLform w i
forall w i. Node HTMLform w i
form []
h1 :: forall w i. Node I.HTMLh1 w i
h1 :: forall w i. Node HTMLaddress w i
h1 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h1")
h1_ :: forall w i. Array (HTML w i) -> HTML w i
h1_ :: forall w i. Array (HTML w i) -> HTML w i
h1_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h1 []
h2 :: forall w i. Node I.HTMLh2 w i
h2 :: forall w i. Node HTMLaddress w i
h2 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h2")
h2_ :: forall w i. Array (HTML w i) -> HTML w i
h2_ :: forall w i. Array (HTML w i) -> HTML w i
h2_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h2 []
h3 :: forall w i. Node I.HTMLh3 w i
h3 :: forall w i. Node HTMLaddress w i
h3 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h3")
h3_ :: forall w i. Array (HTML w i) -> HTML w i
h3_ :: forall w i. Array (HTML w i) -> HTML w i
h3_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h3 []
h4 :: forall w i. Node I.HTMLh4 w i
h4 :: forall w i. Node HTMLaddress w i
h4 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h4")
h4_ :: forall w i. Array (HTML w i) -> HTML w i
h4_ :: forall w i. Array (HTML w i) -> HTML w i
h4_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h4 []
h5 :: forall w i. Node I.HTMLh5 w i
h5 :: forall w i. Node HTMLaddress w i
h5 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h5")
h5_ :: forall w i. Array (HTML w i) -> HTML w i
h5_ :: forall w i. Array (HTML w i) -> HTML w i
h5_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h5 []
h6 :: forall w i. Node I.HTMLh6 w i
h6 :: forall w i. Node HTMLaddress w i
h6 = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"h6")
h6_ :: forall w i. Array (HTML w i) -> HTML w i
h6_ :: forall w i. Array (HTML w i) -> HTML w i
h6_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
h6 []
head :: forall w i. Node I.HTMLhead w i
head :: forall w i. Node HTMLbdo w i
head = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"head")
head_ :: forall w i. Array (HTML w i) -> HTML w i
head_ :: forall w i. Array (HTML w i) -> HTML w i
head_ = Node HTMLbdo w i
forall w i. Node HTMLbdo w i
head []
header :: forall w i. Node I.HTMLheader w i
= ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"header")
header_ :: forall w i. Array (HTML w i) -> HTML w i
= Node HTMLabbr w i
forall w i. Node HTMLabbr w i
header []
hr :: forall w i. Leaf I.HTMLhr w i
hr :: forall w i. Leaf HTMLabbr w i
hr [IProp HTMLabbr i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"hr") [IProp HTMLabbr i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []
hr_ :: forall w i. HTML w i
hr_ :: forall w i. HTML w i
hr_ = Leaf HTMLabbr w i
forall w i. Leaf HTMLabbr w i
hr []
html :: forall w i. Node I.HTMLhtml w i
html :: forall w i. Node HTMLhtml w i
html = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "manifest" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"xmlns" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"html")
html_ :: forall w i. Array (HTML w i) -> HTML w i
html_ :: forall w i. Array (HTML w i) -> HTML w i
html_ = Node HTMLhtml w i
forall w i. Node HTMLhtml w i
html []
i :: forall w i. Node I.HTMLi w i
i :: forall w i. Node HTMLabbr w i
i = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"i")
i_ :: forall w i. Array (HTML w i) -> HTML w i
i_ :: forall w i. Array (HTML w i) -> HTML w i
i_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
i []
iframe :: forall w i. Leaf I.HTMLiframe w i
iframe :: forall w i. Leaf HTMLiframe w i
iframe [IProp HTMLiframe i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "name" ':-> Text,
"onBeforeInput" ':-> Event, "onContextMenu" ':-> Event,
"onInput" ':-> Event, "onLoad" ':-> Event, "sandbox" ':-> Text,
"spellcheck" ':-> Bool, "src" ':-> Text, "srcDoc" ':-> Text,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"width" ':-> Int])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"iframe") [IProp HTMLiframe i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "name" ':-> Text,
"onBeforeInput" ':-> Event, "onContextMenu" ':-> Event,
"onInput" ':-> Event, "onLoad" ':-> Event, "sandbox" ':-> Text,
"spellcheck" ':-> Bool, "src" ':-> Text, "srcDoc" ':-> Text,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"width" ':-> Int])
i)
props []
img :: forall w i. Leaf I.HTMLimg w i
img :: forall w i. Leaf HTMLimg w i
img [IProp HTMLimg i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "alt" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "crossOrigin" ':-> CrossOriginValue,
"dir" ':-> DirValue, "draggable" ':-> Bool, "height" ':-> Int,
"hidden" ':-> Bool, "id" ':-> Text, "isMap" ':-> Bool,
"lang" ':-> Text, "longDesc" ':-> Text, "onAbort" ':-> Event,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onError" ':-> Event, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent, "onLoad" ':-> Event,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "useMap" ':-> Text,
"width" ':-> Int])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"img") [IProp HTMLimg i]
Array
(IProp
('R
'["accessKey" ':-> Text, "alt" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "crossOrigin" ':-> CrossOriginValue,
"dir" ':-> DirValue, "draggable" ':-> Bool, "height" ':-> Int,
"hidden" ':-> Bool, "id" ':-> Text, "isMap" ':-> Bool,
"lang" ':-> Text, "longDesc" ':-> Text, "onAbort" ':-> Event,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onError" ':-> Event, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent, "onLoad" ':-> Event,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "useMap" ':-> Text,
"width" ':-> Int])
i)
props []
input :: forall w i. Leaf I.HTMLinput w i
input :: forall w i. Leaf HTMLinput w i
input [IProp HTMLinput i]
props = ElemName
-> Array
(IProp
('R
'["accept" ':-> InputAcceptType, "accessKey" ':-> Text,
"autocomplete" ':-> AutocompleteType, "autofocus" ':-> Bool,
"checked" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"formAction" ':-> Text, "formEncType" ':-> MediaType,
"formMethod" ':-> FormMethod, "formNoValidate" ':-> Bool,
"formTarget" ':-> Text, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "list" ':-> Text,
"max" ':-> Double, "maxLength" ':-> Int, "min" ':-> Double,
"minLength" ':-> Int, "multiple" ':-> Bool, "name" ':-> Text,
"onAbort" ':-> Event, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onChange" ':-> Event, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onError" ':-> Event, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onInvalid" ':-> Event, "onKeyDown" ':-> KeyboardEvent,
"onKeyPress" ':-> KeyboardEvent, "onKeyUp" ':-> KeyboardEvent,
"onLoad" ':-> Event, "onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onSearch" ':-> Event, "onSelect" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"pattern" ':-> Text, "placeholder" ':-> Text, "readOnly" ':-> Bool,
"required" ':-> Bool, "size" ':-> Int, "spellcheck" ':-> Bool,
"src" ':-> Text, "step" ':-> StepValue, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> InputType,
"value" ':-> Text, "width" ':-> Int])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"input") [IProp HTMLinput i]
Array
(IProp
('R
'["accept" ':-> InputAcceptType, "accessKey" ':-> Text,
"autocomplete" ':-> AutocompleteType, "autofocus" ':-> Bool,
"checked" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"formAction" ':-> Text, "formEncType" ':-> MediaType,
"formMethod" ':-> FormMethod, "formNoValidate" ':-> Bool,
"formTarget" ':-> Text, "height" ':-> Int, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "list" ':-> Text,
"max" ':-> Double, "maxLength" ':-> Int, "min" ':-> Double,
"minLength" ':-> Int, "multiple" ':-> Bool, "name" ':-> Text,
"onAbort" ':-> Event, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onChange" ':-> Event, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onError" ':-> Event, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onInvalid" ':-> Event, "onKeyDown" ':-> KeyboardEvent,
"onKeyPress" ':-> KeyboardEvent, "onKeyUp" ':-> KeyboardEvent,
"onLoad" ':-> Event, "onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onSearch" ':-> Event, "onSelect" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"pattern" ':-> Text, "placeholder" ':-> Text, "readOnly" ':-> Bool,
"required" ':-> Bool, "size" ':-> Int, "spellcheck" ':-> Bool,
"src" ':-> Text, "step" ':-> StepValue, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> InputType,
"value" ':-> Text, "width" ':-> Int])
i)
props []
ins :: forall w i. Node I.HTMLins w i
ins :: forall w i. Node HTMLins w i
ins = ElemName
-> Array
(IProp
('R
'["UTCTime" ':-> UTCTime, "accessKey" ':-> Text, "cite" ':-> Text,
"class" ':-> Text, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"ins")
ins_ :: forall w i. Array (HTML w i) -> HTML w i
ins_ :: forall w i. Array (HTML w i) -> HTML w i
ins_ = Node HTMLins w i
forall w i. Node HTMLins w i
ins []
kbd :: forall w i. Node I.HTMLkbd w i
kbd :: forall w i. Node HTMLabbr w i
kbd = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"kbd")
kbd_ :: forall w i. Array (HTML w i) -> HTML w i
kbd_ :: forall w i. Array (HTML w i) -> HTML w i
kbd_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
kbd []
label :: forall w i. Node I.HTMLlabel w i
label :: forall w i. Node HTMLlabel w i
label = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "for" ':-> Text, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"label")
label_ :: forall w i. Array (HTML w i) -> HTML w i
label_ :: forall w i. Array (HTML w i) -> HTML w i
label_ = Node HTMLlabel w i
forall w i. Node HTMLlabel w i
label []
legend :: forall w i. Node I.HTMLlegend w i
legend :: forall w i. Node HTMLabbr w i
legend = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"legend")
legend_ :: forall w i. Array (HTML w i) -> HTML w i
legend_ :: forall w i. Array (HTML w i) -> HTML w i
legend_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
legend []
li :: forall w i. Node I.HTMLli w i
li :: forall w i. Node HTMLli w i
li = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"value" ':-> Int])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"li")
li_ :: forall w i. Array (HTML w i) -> HTML w i
li_ :: forall w i. Array (HTML w i) -> HTML w i
li_ = Node HTMLli w i
forall w i. Node HTMLli w i
li []
link :: forall w i. Leaf I.HTMLlink w i
link :: forall w i. Leaf HTMLlink w i
link [IProp HTMLlink i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "crossOrigin" ':-> CrossOriginValue,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"href" ':-> Text, "hreflang" ':-> Text, "id" ':-> Text,
"lang" ':-> Text, "media" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"onLoad" ':-> Event, "rel" ':-> Text, "sizes" ':-> Text,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "type" ':-> MediaType])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"link") [IProp HTMLlink i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "crossOrigin" ':-> CrossOriginValue,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"href" ':-> Text, "hreflang" ':-> Text, "id" ':-> Text,
"lang" ':-> Text, "media" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"onLoad" ':-> Event, "rel" ':-> Text, "sizes" ':-> Text,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "type" ':-> MediaType])
i)
props []
main :: forall w i. Node I.HTMLmain w i
main :: forall w i. Node HTMLabbr w i
main = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"main")
main_ :: forall w i. Array (HTML w i) -> HTML w i
main_ :: forall w i. Array (HTML w i) -> HTML w i
main_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
main []
map :: forall w i. Node I.HTMLmap w i
map :: forall w i. Node HTMLmap w i
map = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "name" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"map")
map_ :: forall w i. Array (HTML w i) -> HTML w i
map_ :: forall w i. Array (HTML w i) -> HTML w i
map_ = Node HTMLmap w i
forall w i. Node HTMLmap w i
map []
mark :: forall w i. Node I.HTMLmark w i
mark :: forall w i. Node HTMLabbr w i
mark = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"mark")
mark_ :: forall w i. Array (HTML w i) -> HTML w i
mark_ :: forall w i. Array (HTML w i) -> HTML w i
mark_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
mark []
menu :: forall w i. Node I.HTMLmenu w i
= ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"label" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"type" ':-> MenuType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"menu")
menu_ :: forall w i. Array (HTML w i) -> HTML w i
= Node HTMLmenu w i
forall w i. Node HTMLmenu w i
menu []
menuitem :: forall w i. Node I.HTMLmenuitem w i
= ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "checked" ':-> Bool, "class" ':-> Text,
"command" ':-> Text, "contentEditable" ':-> Bool,
"default" ':-> Bool, "dir" ':-> DirValue, "disabled" ':-> Bool,
"draggable" ':-> Bool, "hidden" ':-> Bool, "icon" ':-> Text,
"id" ':-> Text, "label" ':-> Text, "lang" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"radioGroup" ':-> Text, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> MenuitemType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"menuitem")
menuitem_ :: forall w i. Array (HTML w i) -> HTML w i
= Node HTMLmenuitem w i
forall w i. Node HTMLmenuitem w i
menuitem []
meta :: forall w i. Leaf I.HTMLmeta w i
meta :: forall w i. Leaf HTMLmeta w i
meta [IProp HTMLmeta i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "charset" ':-> Text, "class" ':-> Text,
"content" ':-> Text, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"httpEquiv" ':-> Text, "id" ':-> Text, "lang" ':-> Text,
"name" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"meta") [IProp HTMLmeta i]
Array
(IProp
('R
'["accessKey" ':-> Text, "charset" ':-> Text, "class" ':-> Text,
"content" ':-> Text, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"httpEquiv" ':-> Text, "id" ':-> Text, "lang" ':-> Text,
"name" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []
meter :: forall w i. Node I.HTMLmeter w i
meter :: forall w i. Node HTMLmeter w i
meter = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "form" ':-> Text, "hidden" ':-> Bool,
"high" ':-> Double, "id" ':-> Text, "lang" ':-> Text,
"low" ':-> Double, "max" ':-> Double, "min" ':-> Double,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"optimum" ':-> Double, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "value" ':-> Double])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"meter")
meter_ :: forall w i. Array (HTML w i) -> HTML w i
meter_ :: forall w i. Array (HTML w i) -> HTML w i
meter_ = Node HTMLmeter w i
forall w i. Node HTMLmeter w i
meter []
nav :: forall w i. Node I.HTMLnav w i
nav :: forall w i. Node HTMLabbr w i
nav = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"nav")
nav_ :: forall w i. Array (HTML w i) -> HTML w i
nav_ :: forall w i. Array (HTML w i) -> HTML w i
nav_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
nav []
noscript :: forall w i. Node I.HTMLnoscript w i
noscript :: forall w i. Node HTMLabbr w i
noscript = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"noscript")
noscript_ :: forall w i. Array (HTML w i) -> HTML w i
noscript_ :: forall w i. Array (HTML w i) -> HTML w i
noscript_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
noscript []
object :: forall w i. Node I.HTMLobject w i
object :: forall w i. Node HTMLobject w i
object = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "data" ':-> Text, "dir" ':-> DirValue,
"draggable" ':-> Bool, "form" ':-> Text, "height" ':-> Int,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"name" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onError" ':-> Event,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"type" ':-> MediaType, "useMap" ':-> Text, "width" ':-> Int])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"object")
object_ :: forall w i. Array (HTML w i) -> HTML w i
object_ :: forall w i. Array (HTML w i) -> HTML w i
object_ = Node HTMLobject w i
forall w i. Node HTMLobject w i
object []
ol :: forall w i. Node I.HTMLol w i
ol :: forall w i. Node HTMLol w i
ol = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "reversed" ':-> Bool,
"spellcheck" ':-> Bool, "start" ':-> Int, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text,
"type" ':-> OrderedListType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"ol")
ol_ :: forall w i. Array (HTML w i) -> HTML w i
ol_ :: forall w i. Array (HTML w i) -> HTML w i
ol_ = Node HTMLol w i
forall w i. Node HTMLol w i
ol []
optgroup :: forall w i. Node I.HTMLoptgroup w i
optgroup :: forall w i. Node HTMLoptgroup w i
optgroup = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "label" ':-> Text, "lang" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"optgroup")
optgroup_ :: forall w i. Array (HTML w i) -> HTML w i
optgroup_ :: forall w i. Array (HTML w i) -> HTML w i
optgroup_ = Node HTMLoptgroup w i
forall w i. Node HTMLoptgroup w i
optgroup []
option :: forall w i. Node I.HTMLoption w i
option :: forall w i. Node HTMLoption w i
option = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "label" ':-> Text, "lang" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"selected" ':-> Bool, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "value" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"option")
option_ :: forall w i. Array (HTML w i) -> HTML w i
option_ :: forall w i. Array (HTML w i) -> HTML w i
option_ = Node HTMLoption w i
forall w i. Node HTMLoption w i
option []
output :: forall w i. Node I.HTMLoutput w i
output :: forall w i. Node HTMLoutput w i
output = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "for" ':-> Text, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"name" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"output")
output_ :: forall w i. Array (HTML w i) -> HTML w i
output_ :: forall w i. Array (HTML w i) -> HTML w i
output_ = Node HTMLoutput w i
forall w i. Node HTMLoutput w i
output []
p :: forall w i. Node I.HTMLp w i
p :: forall w i. Node HTMLaddress w i
p = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"p")
p_ :: forall w i. Array (HTML w i) -> HTML w i
p_ :: forall w i. Array (HTML w i) -> HTML w i
p_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
p []
param :: forall w i. Leaf I.HTMLparam w i
param :: forall w i. Leaf HTMLparam w i
param [IProp HTMLparam i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "name" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "value" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"param") [IProp HTMLparam i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "name" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "value" ':-> Text])
i)
props []
pre :: forall w i. Node I.HTMLpre w i
pre :: forall w i. Node HTMLaddress w i
pre = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"pre")
pre_ :: forall w i. Array (HTML w i) -> HTML w i
pre_ :: forall w i. Array (HTML w i) -> HTML w i
pre_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
pre []
progress :: forall w i. Node I.HTMLprogress w i
progress :: forall w i. Node HTMLprogress w i
progress = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "max" ':-> Double, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "value" ':-> Double])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"progress")
progress_ :: forall w i. Array (HTML w i) -> HTML w i
progress_ :: forall w i. Array (HTML w i) -> HTML w i
progress_ = Node HTMLprogress w i
forall w i. Node HTMLprogress w i
progress []
q :: forall w i. Node I.HTMLq w i
q :: forall w i. Node HTMLq w i
q = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "cite" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"q")
q_ :: forall w i. Array (HTML w i) -> HTML w i
q_ :: forall w i. Array (HTML w i) -> HTML w i
q_ = Node HTMLq w i
forall w i. Node HTMLq w i
q []
rp :: forall w i. Node I.HTMLrp w i
rp :: forall w i. Node HTMLabbr w i
rp = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"rp")
rp_ :: forall w i. Array (HTML w i) -> HTML w i
rp_ :: forall w i. Array (HTML w i) -> HTML w i
rp_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
rp []
rt :: forall w i. Node I.HTMLrt w i
rt :: forall w i. Node HTMLabbr w i
rt = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"rt")
rt_ :: forall w i. Array (HTML w i) -> HTML w i
rt_ :: forall w i. Array (HTML w i) -> HTML w i
rt_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
rt []
ruby :: forall w i. Node I.HTMLruby w i
ruby :: forall w i. Node HTMLabbr w i
ruby = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"ruby")
ruby_ :: forall w i. Array (HTML w i) -> HTML w i
ruby_ :: forall w i. Array (HTML w i) -> HTML w i
ruby_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
ruby []
samp :: forall w i. Node I.HTMLsamp w i
samp :: forall w i. Node HTMLabbr w i
samp = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"samp")
samp_ :: forall w i. Array (HTML w i) -> HTML w i
samp_ :: forall w i. Array (HTML w i) -> HTML w i
samp_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
samp []
script :: forall w i. Node I.HTMLscript w i
script :: forall w i. Node HTMLscript w i
script = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "async" ':-> Bool, "charset" ':-> Text,
"class" ':-> Text, "contentEditable" ':-> Bool, "defer" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onError" ':-> Event,
"onInput" ':-> Event, "onLoad" ':-> Event, "spellcheck" ':-> Bool,
"src" ':-> Text, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "type" ':-> MediaType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"script")
script_ :: forall w i. Array (HTML w i) -> HTML w i
script_ :: forall w i. Array (HTML w i) -> HTML w i
script_ = Node HTMLscript w i
forall w i. Node HTMLscript w i
script []
section :: forall w i. Node I.HTMLsection w i
section :: forall w i. Node HTMLabbr w i
section = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"section")
section_ :: forall w i. Array (HTML w i) -> HTML w i
section_ :: forall w i. Array (HTML w i) -> HTML w i
section_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
section []
select :: forall w i. Node I.HTMLselect w i
select :: forall w i. Node HTMLselect w i
select = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "autofocus" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"multiple" ':-> Bool, "name" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onChange" ':-> Event,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "required" ':-> Bool,
"selectedIndex" ':-> Int, "size" ':-> Int, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"value" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"select")
select_ :: forall w i. Array (HTML w i) -> HTML w i
select_ :: forall w i. Array (HTML w i) -> HTML w i
select_ = Node HTMLselect w i
forall w i. Node HTMLselect w i
select []
small :: forall w i. Node I.HTMLsmall w i
small :: forall w i. Node HTMLabbr w i
small = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"small")
small_ :: forall w i. Array (HTML w i) -> HTML w i
small_ :: forall w i. Array (HTML w i) -> HTML w i
small_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
small []
source :: forall w i. Leaf I.HTMLsource w i
source :: forall w i. Leaf HTMLsource w i
source [IProp HTMLsource i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "media" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> MediaType])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"source") [IProp HTMLsource i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "media" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> MediaType])
i)
props []
span :: forall w i. Node I.HTMLspan w i
span :: forall w i. Node HTMLabbr w i
span = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"span")
span_ :: forall w i. Array (HTML w i) -> HTML w i
span_ :: forall w i. Array (HTML w i) -> HTML w i
span_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
span []
strong :: forall w i. Node I.HTMLstrong w i
strong :: forall w i. Node HTMLabbr w i
strong = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"strong")
strong_ :: forall w i. Array (HTML w i) -> HTML w i
strong_ :: forall w i. Array (HTML w i) -> HTML w i
strong_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
strong []
style :: forall w i. Node I.HTMLstyle w i
style :: forall w i. Node HTMLstyle w i
style = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "media" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onError" ':-> Event,
"onInput" ':-> Event, "onLoad" ':-> Event, "scoped" ':-> Bool,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text, "type" ':-> MediaType])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"style")
style_ :: forall w i. Array (HTML w i) -> HTML w i
style_ :: forall w i. Array (HTML w i) -> HTML w i
style_ = Node HTMLstyle w i
forall w i. Node HTMLstyle w i
style []
sub :: forall w i. Node I.HTMLsub w i
sub :: forall w i. Node HTMLabbr w i
sub = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"sub")
sub_ :: forall w i. Array (HTML w i) -> HTML w i
sub_ :: forall w i. Array (HTML w i) -> HTML w i
sub_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
sub []
summary :: forall w i. Node I.HTMLsummary w i
summary :: forall w i. Node HTMLabbr w i
summary = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"summary")
summary_ :: forall w i. Array (HTML w i) -> HTML w i
summary_ :: forall w i. Array (HTML w i) -> HTML w i
summary_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
summary []
sup :: forall w i. Node I.HTMLsup w i
sup :: forall w i. Node HTMLabbr w i
sup = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"sup")
sup_ :: forall w i. Array (HTML w i) -> HTML w i
sup_ :: forall w i. Array (HTML w i) -> HTML w i
sup_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
sup []
table :: forall w i. Node I.HTMLtable w i
table :: forall w i. Node HTMLtable w i
table = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"sortable" ':-> Bool, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"table")
table_ :: forall w i. Array (HTML w i) -> HTML w i
table_ :: forall w i. Array (HTML w i) -> HTML w i
table_ = Node HTMLtable w i
forall w i. Node HTMLtable w i
table []
tbody :: forall w i. Node I.HTMLtbody w i
tbody :: forall w i. Node HTMLaddress w i
tbody = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"tbody")
tbody_ :: forall w i. Array (HTML w i) -> HTML w i
tbody_ :: forall w i. Array (HTML w i) -> HTML w i
tbody_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
tbody []
td :: forall w i. Node I.HTMLtd w i
td :: forall w i. Node HTMLtd w i
td = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text, "colSpan" ':-> Int,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "headers" ':-> Text, "hidden" ':-> Bool,
"id" ':-> Text, "lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"rowSpan" ':-> Int, "spellcheck" ':-> Bool, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"td")
td_ :: forall w i. Array (HTML w i) -> HTML w i
td_ :: forall w i. Array (HTML w i) -> HTML w i
td_ = Node HTMLtd w i
forall w i. Node HTMLtd w i
td []
textarea :: forall w i. Leaf I.HTMLtextarea w i
textarea :: forall w i. Leaf HTMLtextarea w i
textarea [IProp HTMLtextarea i]
es = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "autofocus" ':-> Bool, "class" ':-> Text,
"cols" ':-> Int, "contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"maxLength" ':-> Int, "name" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onChange" ':-> Event,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onSelect" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"placeholder" ':-> Text, "readOnly" ':-> Bool,
"required" ':-> Bool, "rows" ':-> Int, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"value" ':-> Text, "wrap" ':-> WrapValue])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"textarea") [IProp HTMLtextarea i]
Array
(IProp
('R
'["accessKey" ':-> Text, "autofocus" ':-> Bool, "class" ':-> Text,
"cols" ':-> Int, "contentEditable" ':-> Bool, "dir" ':-> DirValue,
"disabled" ':-> Bool, "draggable" ':-> Bool, "form" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"maxLength" ':-> Int, "name" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onChange" ':-> Event,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onSelect" ':-> Event,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"placeholder" ':-> Text, "readOnly" ':-> Bool,
"required" ':-> Bool, "rows" ':-> Int, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text,
"value" ':-> Text, "wrap" ':-> WrapValue])
i)
es []
tfoot :: forall w i. Node I.HTMLtfoot w i
= ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"tfoot")
tfoot_ :: forall w i. Array (HTML w i) -> HTML w i
= Node HTMLaddress w i
forall w i. Node HTMLaddress w i
tfoot []
th :: forall w i. Node I.HTMLth w i
th :: forall w i. Node HTMLth w i
th = ElemName
-> Array
(IProp
('R
'["abbr" ':-> Text, "accessKey" ':-> Text, "class" ':-> Text,
"colSpan" ':-> Int, "contentEditable" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "headers" ':-> Text,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"onAuxClick" ':-> MouseEvent, "onBeforeInput" ':-> Event,
"onBlur" ':-> FocusEvent, "onClick" ':-> MouseEvent,
"onContextMenu" ':-> Event, "onCopy" ':-> ClipboardEvent,
"onCut" ':-> ClipboardEvent, "onDoubleClick" ':-> MouseEvent,
"onDrag" ':-> DragEvent, "onDragEnd" ':-> DragEvent,
"onDragEnter" ':-> DragEvent, "onDragExit" ':-> DragEvent,
"onDragLeave" ':-> DragEvent, "onDragOver" ':-> DragEvent,
"onDragStart" ':-> DragEvent, "onDrop" ':-> DragEvent,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"rowSpan" ':-> Int, "scope" ':-> ScopeValue, "sorted" ':-> Bool,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"th")
th_ :: forall w i. Array (HTML w i) -> HTML w i
th_ :: forall w i. Array (HTML w i) -> HTML w i
th_ = Node HTMLth w i
forall w i. Node HTMLth w i
th []
thead :: forall w i. Node I.HTMLthead w i
thead :: forall w i. Node HTMLabbr w i
thead = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"thead")
thead_ :: forall w i. Array (HTML w i) -> HTML w i
thead_ :: forall w i. Array (HTML w i) -> HTML w i
thead_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
thead []
time :: forall w i. Node I.HTMLtime w i
time :: forall w i. Node HTMLtime w i
time = ElemName
-> Array
(IProp
('R
'["UTCTime" ':-> UTCTime, "accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"time")
time_ :: forall w i. Array (HTML w i) -> HTML w i
time_ :: forall w i. Array (HTML w i) -> HTML w i
time_ = Node HTMLtime w i
forall w i. Node HTMLtime w i
time []
title :: forall w i. Node I.HTMLtitle w i
title :: forall w i. Node HTMLbdo w i
title = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onBeforeInput" ':-> Event,
"onContextMenu" ':-> Event, "onInput" ':-> Event,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"title")
title_ :: forall w i. Array (HTML w i) -> HTML w i
title_ :: forall w i. Array (HTML w i) -> HTML w i
title_ = Node HTMLbdo w i
forall w i. Node HTMLbdo w i
title []
tr :: forall w i. Node I.HTMLtr w i
tr :: forall w i. Node HTMLabbr w i
tr = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"tr")
tr_ :: forall w i. Array (HTML w i) -> HTML w i
tr_ :: forall w i. Array (HTML w i) -> HTML w i
tr_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
tr []
track :: forall w i. Leaf I.HTMLtrack w i
track :: forall w i. Leaf HTMLtrack w i
track [IProp HTMLtrack i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "default" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "kind" ':-> KindValue, "label" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "srcLang" ':-> Text,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"track") [IProp HTMLtrack i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "default" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "hidden" ':-> Bool,
"id" ':-> Text, "kind" ':-> KindValue, "label" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "src" ':-> Text, "srcLang" ':-> Text,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
props []
u :: forall w i. Node I.HTMLu w i
u :: forall w i. Node HTMLabbr w i
u = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"u")
u_ :: forall w i. Array (HTML w i) -> HTML w i
u_ :: forall w i. Array (HTML w i) -> HTML w i
u_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
u []
ul :: forall w i. Node I.HTMLul w i
ul :: forall w i. Node HTMLaddress w i
ul = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onScroll" ':-> Event, "onTouchCancel" ':-> TouchEvent,
"onTouchEnd" ':-> TouchEvent, "onTouchEnter" ':-> TouchEvent,
"onTouchLeave" ':-> TouchEvent, "onTouchMove" ':-> TouchEvent,
"onTouchStart" ':-> TouchEvent, "onTransitionEnd" ':-> Event,
"onWheel" ':-> WheelEvent, "spellcheck" ':-> Bool,
"style" ':-> Text, "tabIndex" ':-> Int, "title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"ul")
ul_ :: forall w i. Array (HTML w i) -> HTML w i
ul_ :: forall w i. Array (HTML w i) -> HTML w i
ul_ = Node HTMLaddress w i
forall w i. Node HTMLaddress w i
ul []
var :: forall w i. Node I.HTMLvar w i
var :: forall w i. Node HTMLabbr w i
var = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"var")
var_ :: forall w i. Array (HTML w i) -> HTML w i
var_ :: forall w i. Array (HTML w i) -> HTML w i
var_ = Node HTMLabbr w i
forall w i. Node HTMLabbr w i
var []
video :: forall w i. Node I.HTMLvideo w i
video :: forall w i. Node HTMLvideo w i
video = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "autoplay" ':-> Bool, "class" ':-> Text,
"contentEditable" ':-> Bool, "controls" ':-> Bool,
"dir" ':-> DirValue, "draggable" ':-> Bool, "height" ':-> Int,
"hidden" ':-> Bool, "id" ':-> Text, "lang" ':-> Text,
"loop" ':-> Bool, "muted" ':-> Bool, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onError" ':-> Event,
"onFocus" ':-> FocusEvent, "onFocusIn" ':-> FocusEvent,
"onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"poster" ':-> Text, "preload" ':-> PreloadValue,
"spellcheck" ':-> Bool, "src" ':-> Text, "style" ':-> Text,
"tabIndex" ':-> Int, "title" ':-> Text, "type" ':-> MediaType,
"width" ':-> Int])
i)
-> [HTML w i]
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"video")
video_ :: forall w i. Array (HTML w i) -> HTML w i
video_ :: forall w i. Array (HTML w i) -> HTML w i
video_ = Node HTMLvideo w i
forall w i. Node HTMLvideo w i
video []
wbr :: forall w i. Leaf I.HTMLwbr w i
wbr :: forall w i. Leaf HTMLabbr w i
wbr [IProp HTMLabbr i]
props = ElemName
-> Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
-> Array (HTML w i)
-> HTML w i
forall (r :: Row (*)) w i.
ElemName -> Array (IProp r i) -> Array (HTML w i) -> HTML w i
element (Text -> ElemName
ElemName Text
"wbr") [IProp HTMLabbr i]
Array
(IProp
('R
'["accessKey" ':-> Text, "class" ':-> Text,
"contentEditable" ':-> Bool, "dir" ':-> DirValue,
"draggable" ':-> Bool, "hidden" ':-> Bool, "id" ':-> Text,
"lang" ':-> Text, "onAuxClick" ':-> MouseEvent,
"onBeforeInput" ':-> Event, "onBlur" ':-> FocusEvent,
"onClick" ':-> MouseEvent, "onContextMenu" ':-> Event,
"onCopy" ':-> ClipboardEvent, "onCut" ':-> ClipboardEvent,
"onDoubleClick" ':-> MouseEvent, "onDrag" ':-> DragEvent,
"onDragEnd" ':-> DragEvent, "onDragEnter" ':-> DragEvent,
"onDragExit" ':-> DragEvent, "onDragLeave" ':-> DragEvent,
"onDragOver" ':-> DragEvent, "onDragStart" ':-> DragEvent,
"onDrop" ':-> DragEvent, "onFocus" ':-> FocusEvent,
"onFocusIn" ':-> FocusEvent, "onFocusOut" ':-> FocusEvent,
"onGotPointerCapture" ':-> PointerEvent, "onInput" ':-> Event,
"onKeyDown" ':-> KeyboardEvent, "onKeyPress" ':-> KeyboardEvent,
"onKeyUp" ':-> KeyboardEvent,
"onLostPointerCapture" ':-> PointerEvent,
"onMouseDown" ':-> MouseEvent, "onMouseEnter" ':-> MouseEvent,
"onMouseLeave" ':-> MouseEvent, "onMouseMove" ':-> MouseEvent,
"onMouseOut" ':-> MouseEvent, "onMouseOver" ':-> MouseEvent,
"onMouseUp" ':-> MouseEvent, "onPaste" ':-> ClipboardEvent,
"onPointerCancel" ':-> PointerEvent,
"onPointerDown" ':-> PointerEvent,
"onPointerEnter" ':-> PointerEvent,
"onPointerLeave" ':-> PointerEvent,
"onPointerMove" ':-> PointerEvent,
"onPointerOut" ':-> PointerEvent,
"onPointerOver" ':-> PointerEvent, "onPointerUp" ':-> PointerEvent,
"onTouchCancel" ':-> TouchEvent, "onTouchEnd" ':-> TouchEvent,
"onTouchEnter" ':-> TouchEvent, "onTouchLeave" ':-> TouchEvent,
"onTouchMove" ':-> TouchEvent, "onTouchStart" ':-> TouchEvent,
"onTransitionEnd" ':-> Event, "onWheel" ':-> WheelEvent,
"spellcheck" ':-> Bool, "style" ':-> Text, "tabIndex" ':-> Int,
"title" ':-> Text])
i)
props []