logfmt-0.0.1: Formatting
Safe HaskellNone
LanguageHaskell2010

Data.Fmt.Attr

Description

Html5 formatting.

The API is similar to https://hackage.haskell.org/package/blaze-html.

Synopsis

Html

type Html a = Fmt LogStr a a #

Format HTML

For example:

 contact :: Html LogStr
 contact = p "You can reach me at" % ul . spr . li $ do
       c1 <- a ! href String "https://example.com" $ Website
       c2 <- a ! href String "mailto:cmk@example.com" $ Email
       pure $ c1 <> c2
 

generates the following output:

"<p>You can reach me at</p><ul><li><a href=\"https://foo.com\">Web</a></li><li><a href=\"mailto:cmk@foo.com\">Email</a></li></ul>"

data Attr #

Type for an attribute.

Instances

Instances details
Semigroup Attr # 
Instance details

Defined in Data.Fmt

Methods

(<>) :: Attr -> Attr -> Attr #

sconcat :: NonEmpty Attr -> Attr #

stimes :: Integral b => b -> Attr -> Attr #

Monoid Attr # 
Instance details

Defined in Data.Fmt

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

toHtml :: ToLogStr s => s -> Html a #

comment :: ToLogStr s => s -> Html a #

class Element html where #

Apply an attribute to an HTML tag.

The interface is similar to https://hackage.haskell.org/package/blaze-builder.

You should not define your own instances of this class.

Methods

(!) :: html -> Attr -> html #

Apply an attribute to an element.

>>> printf $ img ! src "foo.png"
<img src="foo.png" />

This can be used on nested elements as well:

>>> printf $ p ! style "float: right" $ "Hello!"
<p style="float: right">Hello!</p>

Instances

Instances details
Element (Html a) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: Html a -> Attr -> Html a #

Element (Html a -> Html b) # 
Instance details

Defined in Data.Fmt

Methods

(!) :: (Html a -> Html b) -> Attr -> Html a -> Html b #

(!?) :: Element html => html -> (Bool, Attr) -> html #

Shorthand for setting an attribute depending on a conditional.

Example:

p !? (isBig, A.class "big") $ "Hello"

Gives the same result as:

(if isBig then p ! A.class "big" else p) "Hello"

Attributes

accept #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the accept attribute.

Example:

div ! accept "bar" $ "Hello."

Result:

<div accept="bar">Hello.</div>

acceptCharset #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the accept-charset attribute.

Example:

div ! acceptCharset "bar" $ "Hello."

Result:

<div accept-charset="bar">Hello.</div>

accesskey #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the accesskey attribute.

Example:

div ! accesskey "bar" $ "Hello."

Result:

<div accesskey="bar">Hello.</div>

action #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the action attribute.

Example:

div ! action "bar" $ "Hello."

Result:

<div action="bar">Hello.</div>

alt #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the alt attribute.

Example:

div ! alt "bar" $ "Hello."

Result:

<div alt="bar">Hello.</div>

async #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the async attribute.

Example:

div ! async "bar" $ "Hello."

Result:

<div async="bar">Hello.</div>

autocomplete #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the autocomplete attribute.

Example:

div ! autocomplete "bar" $ "Hello."

Result:

<div autocomplete="bar">Hello.</div>

autofocus #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the autofocus attribute.

Example:

div ! autofocus "bar" $ "Hello."

Result:

<div autofocus="bar">Hello.</div>

autoplay #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the autoplay attribute.

Example:

div ! autoplay "bar" $ "Hello."

Result:

<div autoplay="bar">Hello.</div>

challenge #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the challenge attribute.

Example:

div ! challenge "bar" $ "Hello."

Result:

<div challenge="bar">Hello.</div>

charset #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the charset attribute.

Example:

div ! charset "bar" $ "Hello."

Result:

<div charset="bar">Hello.</div>

checked #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the checked attribute.

Example:

div ! checked "bar" $ "Hello."

Result:

<div checked="bar">Hello.</div>

cite #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the cite attribute.

Example:

div ! cite "bar" $ "Hello."

Result:

<div cite="bar">Hello.</div>

class_ #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the class attribute.

Example:

div ! class_ "bar" $ "Hello."

Result:

<div class="bar">Hello.</div>

cols #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the cols attribute.

Example:

div ! cols "bar" $ "Hello."

Result:

<div cols="bar">Hello.</div>

colspan #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the colspan attribute.

Example:

div ! colspan "bar" $ "Hello."

Result:

<div colspan="bar">Hello.</div>

content #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the content attribute.

Example:

div ! content "bar" $ "Hello."

Result:

<div content="bar">Hello.</div>

contenteditable #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the contenteditable attribute.

Example:

div ! contenteditable "bar" $ "Hello."

Result:

<div contenteditable="bar">Hello.</div>

contextmenu #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the contextmenu attribute.

Example:

div ! contextmenu "bar" $ "Hello."

Result:

<div contextmenu="bar">Hello.</div>

controls #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the controls attribute.

Example:

div ! controls "bar" $ "Hello."

Result:

<div controls="bar">Hello.</div>

coords #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the coords attribute.

Example:

div ! coords "bar" $ "Hello."

Result:

<div coords="bar">Hello.</div>

data_ #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the data attribute.

Example:

div ! data_ "bar" $ "Hello."

Result:

<div data="bar">Hello.</div>

datetime #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the datetime attribute.

Example:

div ! datetime "bar" $ "Hello."

Result:

<div datetime="bar">Hello.</div>

defer #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the defer attribute.

Example:

div ! defer "bar" $ "Hello."

Result:

<div defer="bar">Hello.</div>

dir #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the dir attribute.

Example:

div ! dir "bar" $ "Hello."

Result:

<div dir="bar">Hello.</div>

disabled #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the disabled attribute.

Example:

div ! disabled "bar" $ "Hello."

Result:

<div disabled="bar">Hello.</div>

draggable #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the draggable attribute.

Example:

div ! draggable "bar" $ "Hello."

Result:

<div draggable="bar">Hello.</div>

enctype #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the enctype attribute.

Example:

div ! enctype "bar" $ "Hello."

Result:

<div enctype="bar">Hello.</div>

for #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the for attribute.

Example:

div ! for "bar" $ "Hello."

Result:

<div for="bar">Hello.</div>

form #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the form attribute.

Example:

div ! form "bar" $ "Hello."

Result:

<div form="bar">Hello.</div>

formaction #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the formaction attribute.

Example:

div ! formaction "bar" $ "Hello."

Result:

<div formaction="bar">Hello.</div>

formenctype #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the formenctype attribute.

Example:

div ! formenctype "bar" $ "Hello."

Result:

<div formenctype="bar">Hello.</div>

formmethod #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the formmethod attribute.

Example:

div ! formmethod "bar" $ "Hello."

Result:

<div formmethod="bar">Hello.</div>

formnovalidate #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the formnovalidate attribute.

Example:

div ! formnovalidate "bar" $ "Hello."

Result:

<div formnovalidate="bar">Hello.</div>

formtarget #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the formtarget attribute.

Example:

div ! formtarget "bar" $ "Hello."

Result:

<div formtarget="bar">Hello.</div>

headers #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the headers attribute.

Example:

div ! headers "bar" $ "Hello."

Result:

<div headers="bar">Hello.</div>

height #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the height attribute.

Example:

div ! height "bar" $ "Hello."

Result:

<div height="bar">Hello.</div>

hidden #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the hidden attribute.

Example:

div ! hidden "bar" $ "Hello."

Result:

<div hidden="bar">Hello.</div>

high #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the high attribute.

Example:

div ! high "bar" $ "Hello."

Result:

<div high="bar">Hello.</div>

href #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the href attribute.

Example:

div ! href "bar" $ "Hello."

Result:

<div href="bar">Hello.</div>

hreflang #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the hreflang attribute.

Example:

div ! hreflang "bar" $ "Hello."

Result:

<div hreflang="bar">Hello.</div>

httpEquiv #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the http-equiv attribute.

Example:

div ! httpEquiv "bar" $ "Hello."

Result:

<div http-equiv="bar">Hello.</div>

icon #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the icon attribute.

Example:

div ! icon "bar" $ "Hello."

Result:

<div icon="bar">Hello.</div>

id #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the id attribute.

Example:

div ! id "bar" $ "Hello."

Result:

<div id="bar">Hello.</div>

ismap #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ismap attribute.

Example:

div ! ismap "bar" $ "Hello."

Result:

<div ismap="bar">Hello.</div>

item #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the item attribute.

Example:

div ! item "bar" $ "Hello."

Result:

<div item="bar">Hello.</div>

itemprop #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the itemprop attribute.

Example:

div ! itemprop "bar" $ "Hello."

Result:

<div itemprop="bar">Hello.</div>

itemscope #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the itemscope attribute.

Example:

div ! itemscope "bar" $ "Hello."

Result:

<div itemscope="bar">Hello.</div>

itemtype #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the itemtype attribute.

Example:

div ! itemtype "bar" $ "Hello."

Result:

<div itemtype="bar">Hello.</div>

keytype #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the keytype attribute.

Example:

div ! keytype "bar" $ "Hello."

Result:

<div keytype="bar">Hello.</div>

label #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the label attribute.

Example:

div ! label "bar" $ "Hello."

Result:

<div label="bar">Hello.</div>

lang #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the lang attribute.

Example:

div ! lang "bar" $ "Hello."

Result:

<div lang="bar">Hello.</div>

list #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the list attribute.

Example:

div ! list "bar" $ "Hello."

Result:

<div list="bar">Hello.</div>

loop #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the loop attribute.

Example:

div ! loop "bar" $ "Hello."

Result:

<div loop="bar">Hello.</div>

low #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the low attribute.

Example:

div ! low "bar" $ "Hello."

Result:

<div low="bar">Hello.</div>

manifest #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the manifest attribute.

Example:

div ! manifest "bar" $ "Hello."

Result:

<div manifest="bar">Hello.</div>

max #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the max attribute.

Example:

div ! max "bar" $ "Hello."

Result:

<div max="bar">Hello.</div>

maxlength #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the maxlength attribute.

Example:

div ! maxlength "bar" $ "Hello."

Result:

<div maxlength="bar">Hello.</div>

media #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the media attribute.

Example:

div ! media "bar" $ "Hello."

Result:

<div media="bar">Hello.</div>

method #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the method attribute.

Example:

div ! method "bar" $ "Hello."

Result:

<div method="bar">Hello.</div>

min #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the min attribute.

Example:

div ! min "bar" $ "Hello."

Result:

<div min="bar">Hello.</div>

multiple #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the multiple attribute.

Example:

div ! multiple "bar" $ "Hello."

Result:

<div multiple="bar">Hello.</div>

name #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the name attribute.

Example:

div ! name "bar" $ "Hello."

Result:

<div name="bar">Hello.</div>

novalidate #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the novalidate attribute.

Example:

div ! novalidate "bar" $ "Hello."

Result:

<div novalidate="bar">Hello.</div>

onbeforeonload #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onbeforeonload attribute.

Example:

div ! onbeforeonload "bar" $ "Hello."

Result:

<div onbeforeonload="bar">Hello.</div>

onbeforeprint #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onbeforeprint attribute.

Example:

div ! onbeforeprint "bar" $ "Hello."

Result:

<div onbeforeprint="bar">Hello.</div>

onblur #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onblur attribute.

Example:

div ! onblur "bar" $ "Hello."

Result:

<div onblur="bar">Hello.</div>

oncanplay #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the oncanplay attribute.

Example:

div ! oncanplay "bar" $ "Hello."

Result:

<div oncanplay="bar">Hello.</div>

oncanplaythrough #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the oncanplaythrough attribute.

Example:

div ! oncanplaythrough "bar" $ "Hello."

Result:

<div oncanplaythrough="bar">Hello.</div>

onchange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onchange attribute.

Example:

div ! onchange "bar" $ "Hello."

Result:

<div onchange="bar">Hello.</div>

onclick #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onclick attribute.

Example:

div ! onclick "bar" $ "Hello."

Result:

<div onclick="bar">Hello.</div>

oncontextmenu #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the oncontextmenu attribute.

Example:

div ! oncontextmenu "bar" $ "Hello."

Result:

<div oncontextmenu="bar">Hello.</div>

ondblclick #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondblclick attribute.

Example:

div ! ondblclick "bar" $ "Hello."

Result:

<div ondblclick="bar">Hello.</div>

ondrag #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondrag attribute.

Example:

div ! ondrag "bar" $ "Hello."

Result:

<div ondrag="bar">Hello.</div>

ondragend #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondragend attribute.

Example:

div ! ondragend "bar" $ "Hello."

Result:

<div ondragend="bar">Hello.</div>

ondragenter #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondragenter attribute.

Example:

div ! ondragenter "bar" $ "Hello."

Result:

<div ondragenter="bar">Hello.</div>

ondragleave #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondragleave attribute.

Example:

div ! ondragleave "bar" $ "Hello."

Result:

<div ondragleave="bar">Hello.</div>

ondragover #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondragover attribute.

Example:

div ! ondragover "bar" $ "Hello."

Result:

<div ondragover="bar">Hello.</div>

ondragstart #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondragstart attribute.

Example:

div ! ondragstart "bar" $ "Hello."

Result:

<div ondragstart="bar">Hello.</div>

ondrop #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondrop attribute.

Example:

div ! ondrop "bar" $ "Hello."

Result:

<div ondrop="bar">Hello.</div>

ondurationchange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ondurationchange attribute.

Example:

div ! ondurationchange "bar" $ "Hello."

Result:

<div ondurationchange="bar">Hello.</div>

onemptied #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onemptied attribute.

Example:

div ! onemptied "bar" $ "Hello."

Result:

<div onemptied="bar">Hello.</div>

onended #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onended attribute.

Example:

div ! onended "bar" $ "Hello."

Result:

<div onended="bar">Hello.</div>

onerror #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onerror attribute.

Example:

div ! onerror "bar" $ "Hello."

Result:

<div onerror="bar">Hello.</div>

onfocus #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onfocus attribute.

Example:

div ! onfocus "bar" $ "Hello."

Result:

<div onfocus="bar">Hello.</div>

onformchange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onformchange attribute.

Example:

div ! onformchange "bar" $ "Hello."

Result:

<div onformchange="bar">Hello.</div>

onforminput #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onforminput attribute.

Example:

div ! onforminput "bar" $ "Hello."

Result:

<div onforminput="bar">Hello.</div>

onhaschange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onhaschange attribute.

Example:

div ! onhaschange "bar" $ "Hello."

Result:

<div onhaschange="bar">Hello.</div>

oninput #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the oninput attribute.

Example:

div ! oninput "bar" $ "Hello."

Result:

<div oninput="bar">Hello.</div>

oninvalid #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the oninvalid attribute.

Example:

div ! oninvalid "bar" $ "Hello."

Result:

<div oninvalid="bar">Hello.</div>

onkeydown #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onkeydown attribute.

Example:

div ! onkeydown "bar" $ "Hello."

Result:

<div onkeydown="bar">Hello.</div>

onkeyup #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onkeyup attribute.

Example:

div ! onkeyup "bar" $ "Hello."

Result:

<div onkeyup="bar">Hello.</div>

onload #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onload attribute.

Example:

div ! onload "bar" $ "Hello."

Result:

<div onload="bar">Hello.</div>

onloadeddata #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onloadeddata attribute.

Example:

div ! onloadeddata "bar" $ "Hello."

Result:

<div onloadeddata="bar">Hello.</div>

onloadedmetadata #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onloadedmetadata attribute.

Example:

div ! onloadedmetadata "bar" $ "Hello."

Result:

<div onloadedmetadata="bar">Hello.</div>

onloadstart #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onloadstart attribute.

Example:

div ! onloadstart "bar" $ "Hello."

Result:

<div onloadstart="bar">Hello.</div>

onmessage #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmessage attribute.

Example:

div ! onmessage "bar" $ "Hello."

Result:

<div onmessage="bar">Hello.</div>

onmousedown #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmousedown attribute.

Example:

div ! onmousedown "bar" $ "Hello."

Result:

<div onmousedown="bar">Hello.</div>

onmousemove #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmousemove attribute.

Example:

div ! onmousemove "bar" $ "Hello."

Result:

<div onmousemove="bar">Hello.</div>

onmouseout #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmouseout attribute.

Example:

div ! onmouseout "bar" $ "Hello."

Result:

<div onmouseout="bar">Hello.</div>

onmouseover #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmouseover attribute.

Example:

div ! onmouseover "bar" $ "Hello."

Result:

<div onmouseover="bar">Hello.</div>

onmouseup #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmouseup attribute.

Example:

div ! onmouseup "bar" $ "Hello."

Result:

<div onmouseup="bar">Hello.</div>

onmousewheel #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onmousewheel attribute.

Example:

div ! onmousewheel "bar" $ "Hello."

Result:

<div onmousewheel="bar">Hello.</div>

ononline #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ononline attribute.

Example:

div ! ononline "bar" $ "Hello."

Result:

<div ononline="bar">Hello.</div>

onpagehide #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onpagehide attribute.

Example:

div ! onpagehide "bar" $ "Hello."

Result:

<div onpagehide="bar">Hello.</div>

onpageshow #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onpageshow attribute.

Example:

div ! onpageshow "bar" $ "Hello."

Result:

<div onpageshow="bar">Hello.</div>

onpause #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onpause attribute.

Example:

div ! onpause "bar" $ "Hello."

Result:

<div onpause="bar">Hello.</div>

onplay #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onplay attribute.

Example:

div ! onplay "bar" $ "Hello."

Result:

<div onplay="bar">Hello.</div>

onplaying #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onplaying attribute.

Example:

div ! onplaying "bar" $ "Hello."

Result:

<div onplaying="bar">Hello.</div>

onprogress #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onprogress attribute.

Example:

div ! onprogress "bar" $ "Hello."

Result:

<div onprogress="bar">Hello.</div>

onpropstate #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onpropstate attribute.

Example:

div ! onpropstate "bar" $ "Hello."

Result:

<div onpropstate="bar">Hello.</div>

onratechange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onratechange attribute.

Example:

div ! onratechange "bar" $ "Hello."

Result:

<div onratechange="bar">Hello.</div>

onreadystatechange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onreadystatechange attribute.

Example:

div ! onreadystatechange "bar" $ "Hello."

Result:

<div onreadystatechange="bar">Hello.</div>

onredo #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onredo attribute.

Example:

div ! onredo "bar" $ "Hello."

Result:

<div onredo="bar">Hello.</div>

onresize #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onresize attribute.

Example:

div ! onresize "bar" $ "Hello."

Result:

<div onresize="bar">Hello.</div>

onscroll #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onscroll attribute.

Example:

div ! onscroll "bar" $ "Hello."

Result:

<div onscroll="bar">Hello.</div>

onseeked #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onseeked attribute.

Example:

div ! onseeked "bar" $ "Hello."

Result:

<div onseeked="bar">Hello.</div>

onseeking #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onseeking attribute.

Example:

div ! onseeking "bar" $ "Hello."

Result:

<div onseeking="bar">Hello.</div>

onselect #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onselect attribute.

Example:

div ! onselect "bar" $ "Hello."

Result:

<div onselect="bar">Hello.</div>

onstalled #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onstalled attribute.

Example:

div ! onstalled "bar" $ "Hello."

Result:

<div onstalled="bar">Hello.</div>

onstorage #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onstorage attribute.

Example:

div ! onstorage "bar" $ "Hello."

Result:

<div onstorage="bar">Hello.</div>

onsubmit #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onsubmit attribute.

Example:

div ! onsubmit "bar" $ "Hello."

Result:

<div onsubmit="bar">Hello.</div>

onsuspend #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onsuspend attribute.

Example:

div ! onsuspend "bar" $ "Hello."

Result:

<div onsuspend="bar">Hello.</div>

ontimeupdate #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ontimeupdate attribute.

Example:

div ! ontimeupdate "bar" $ "Hello."

Result:

<div ontimeupdate="bar">Hello.</div>

onundo #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onundo attribute.

Example:

div ! onundo "bar" $ "Hello."

Result:

<div onundo="bar">Hello.</div>

onunload #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onunload attribute.

Example:

div ! onunload "bar" $ "Hello."

Result:

<div onunload="bar">Hello.</div>

onvolumechange #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onvolumechange attribute.

Example:

div ! onvolumechange "bar" $ "Hello."

Result:

<div onvolumechange="bar">Hello.</div>

onwaiting #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the onwaiting attribute.

Example:

div ! onwaiting "bar" $ "Hello."

Result:

<div onwaiting="bar">Hello.</div>

open #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the open attribute.

Example:

div ! open "bar" $ "Hello."

Result:

<div open="bar">Hello.</div>

optimum #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the optimum attribute.

Example:

div ! optimum "bar" $ "Hello."

Result:

<div optimum="bar">Hello.</div>

pattern #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the pattern attribute.

Example:

div ! pattern "bar" $ "Hello."

Result:

<div pattern="bar">Hello.</div>

ping #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the ping attribute.

Example:

div ! ping "bar" $ "Hello."

Result:

<div ping="bar">Hello.</div>

placeholder #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the placeholder attribute.

Example:

div ! placeholder "bar" $ "Hello."

Result:

<div placeholder="bar">Hello.</div>

preload #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the preload attribute.

Example:

div ! preload "bar" $ "Hello."

Result:

<div preload="bar">Hello.</div>

pubdate #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the pubdate attribute.

Example:

div ! pubdate "bar" $ "Hello."

Result:

<div pubdate="bar">Hello.</div>

radiogroup #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the radiogroup attribute.

Example:

div ! radiogroup "bar" $ "Hello."

Result:

<div radiogroup="bar">Hello.</div>

readonly #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the readonly attribute.

Example:

div ! readonly "bar" $ "Hello."

Result:

<div readonly="bar">Hello.</div>

rel #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the rel attribute.

Example:

div ! rel "bar" $ "Hello."

Result:

<div rel="bar">Hello.</div>

required #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the required attribute.

Example:

div ! required "bar" $ "Hello."

Result:

<div required="bar">Hello.</div>

reversed #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the reversed attribute.

Example:

div ! reversed "bar" $ "Hello."

Result:

<div reversed="bar">Hello.</div>

role #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the role attribute.

Example:

div ! role "bar" $ "Hello."

Result:

<div role="bar">Hello.</div>

rows #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the rows attribute.

Example:

div ! rows "bar" $ "Hello."

Result:

<div rows="bar">Hello.</div>

rowspan #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the rowspan attribute.

Example:

div ! rowspan "bar" $ "Hello."

Result:

<div rowspan="bar">Hello.</div>

sandbox #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the sandbox attribute.

Example:

div ! sandbox "bar" $ "Hello."

Result:

<div sandbox="bar">Hello.</div>

scope #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the scope attribute.

Example:

div ! scope "bar" $ "Hello."

Result:

<div scope="bar">Hello.</div>

scoped #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the scoped attribute.

Example:

div ! scoped "bar" $ "Hello."

Result:

<div scoped="bar">Hello.</div>

seamless #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the seamless attribute.

Example:

div ! seamless "bar" $ "Hello."

Result:

<div seamless="bar">Hello.</div>

selected #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the selected attribute.

Example:

div ! selected "bar" $ "Hello."

Result:

<div selected="bar">Hello.</div>

shape #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the shape attribute.

Example:

div ! shape "bar" $ "Hello."

Result:

<div shape="bar">Hello.</div>

size #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the size attribute.

Example:

div ! size "bar" $ "Hello."

Result:

<div size="bar">Hello.</div>

sizes #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the sizes attribute.

Example:

div ! sizes "bar" $ "Hello."

Result:

<div sizes="bar">Hello.</div>

span #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the span attribute.

Example:

div ! span "bar" $ "Hello."

Result:

<div span="bar">Hello.</div>

spellcheck #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the spellcheck attribute.

Example:

div ! spellcheck "bar" $ "Hello."

Result:

<div spellcheck="bar">Hello.</div>

src #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the src attribute.

Example:

div ! src "bar" $ "Hello."

Result:

<div src="bar">Hello.</div>

srcdoc #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the srcdoc attribute.

Example:

div ! srcdoc "bar" $ "Hello."

Result:

<div srcdoc="bar">Hello.</div>

start #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the start attribute.

Example:

div ! start "bar" $ "Hello."

Result:

<div start="bar">Hello.</div>

step #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the step attribute.

Example:

div ! step "bar" $ "Hello."

Result:

<div step="bar">Hello.</div>

style #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the style attribute.

Example:

div ! style "bar" $ "Hello."

Result:

<div style="bar">Hello.</div>

subject #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the subject attribute.

Example:

div ! subject "bar" $ "Hello."

Result:

<div subject="bar">Hello.</div>

summary #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the summary attribute.

Example:

div ! summary "bar" $ "Hello."

Result:

<div summary="bar">Hello.</div>

tabindex #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the tabindex attribute.

Example:

div ! tabindex "bar" $ "Hello."

Result:

<div tabindex="bar">Hello.</div>

target #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the target attribute.

Example:

div ! target "bar" $ "Hello."

Result:

<div target="bar">Hello.</div>

title #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the title attribute.

Example:

div ! title "bar" $ "Hello."

Result:

<div title="bar">Hello.</div>

type_ #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the type attribute.

Example:

div ! type_ "bar" $ "Hello."

Result:

<div type="bar">Hello.</div>

usemap #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the usemap attribute.

Example:

div ! usemap "bar" $ "Hello."

Result:

<div usemap="bar">Hello.</div>

value #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the value attribute.

Example:

div ! value "bar" $ "Hello."

Result:

<div value="bar">Hello.</div>

width #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the width attribute.

Example:

div ! width "bar" $ "Hello."

Result:

<div width="bar">Hello.</div>

wrap #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the wrap attribute.

Example:

div ! wrap "bar" $ "Hello."

Result:

<div wrap="bar">Hello.</div>

xmlns #

Arguments

:: ToLogStr s 
=> s

Attribute value.

-> Attr

Resulting attribute.

Combinator for the xmlns attribute.

Example:

div ! xmlns "bar" $ "Hello."

Result:

<div xmlns="bar">Hello.</div>