-----------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.Html.Element
-- Copyright   :  (C) 2016-2025 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <code@dmj.io>
-- Stability   :  experimental
-- Portability :  non-portable
----------------------------------------------------------------------------
module Miso.Html.Element
  ( -- ** Smart constructors
      nodeHtml
    , nodeHtmlKeyed
    -- ** Document metadata
    , html_
    , doctype_
    , base_
    , head_
    , link_
    , meta_
    , style_
    , title_
    -- ** Sectioning root
    , body_
    -- ** Content sectioning
    , address_
    , article_
    , aside_
    , footer_
    , header_
    , h1_
    , h2_
    , h3_
    , h4_
    , h5_
    , h6_
    , hgroup_
    , main_
    , nav_
    , section_
    , search_
    -- ** Text content
    , blockquote_
    , dd_
    , div_
    , dl_
    , dt_
    , figcaption_
    , figure_
    , hr_
    , li_
    , liKeyed_
    , menu_
    , ol_
    , p_
    , pre_
    , ul_
    -- ** Inline text semantics
    , a_
    , abbr_
    , b_
    , bdi_
    , bdo_
    , br_
    , cite_
    , code_
    , data_
    , dfn_
    , em_
    , i_
    , kbd_
    , mark_
    , q_
    , rp_
    , rt_
    , ruby_
    , s_
    , samp_
    , small_
    , span_
    , strong_
    , sub_
    , sup_
    , time_
    , u_
    , var_
    , wbr_
    -- ** Image and multimedia
    , area_
    , audio_
    , img_
    , map_
    , track_
    , video_
    -- ** Embedded content
    , embed_
    , fencedframe_
    , iframe_
    , object_
    , picture_
    , source_
    -- ** Scripting
    , canvas_
    , noscript_
    , script_
    -- ** Demarcating edits
    , del_
    , ins_
    -- ** Table content
    , caption_
    , col_
    , colgroup_
    , table_
    , tbody_
    , td_
    , tfoot_
    , th_
    , thead_
    , tr_
    , trKeyed_
    -- ** Forms
    , button_
    , datalist_
    , fieldset_
    , form
    , input_
    , label_
    , legend_
    , meter_
    , optgroup_
    , option_
    , output_
    , progress_
    , select_
    , textarea_
    -- ** Interactive elements
    , details_
    , dialog_
    , summary_
    -- ** Web components
    , slot_
    , template_
    ) where
-----------------------------------------------------------------------------
import           Miso.Html.Types
import           Miso.String (MisoString)
-----------------------------------------------------------------------------
-- | Used to construct @Node@ in @View@
nodeHtml :: MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml :: forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
nodeName = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
nodeName Maybe Key
forall a. Maybe a
Nothing
-----------------------------------------------------------------------------
-- | Construct a node with a @Key@
nodeHtmlKeyed :: MisoString -> Key -> [Attribute action] -> [View action] -> View action
nodeHtmlKeyed :: forall action.
MisoString
-> Key -> [Attribute action] -> [View action] -> View action
nodeHtmlKeyed MisoString
name = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
name (Maybe Key -> [Attribute action] -> [View action] -> View action)
-> (Key -> Maybe Key)
-> Key
-> [Attribute action]
-> [View action]
-> View action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Maybe Key
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/div
div_ :: [Attribute action] -> [View action] -> View action
div_ :: forall action. [Attribute action] -> [View action] -> View action
div_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"div"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/table
table_ :: [Attribute action] -> [View action] -> View action
table_ :: forall action. [Attribute action] -> [View action] -> View action
table_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"table"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/thead
thead_ :: [Attribute action] -> [View action] -> View action
thead_ :: forall action. [Attribute action] -> [View action] -> View action
thead_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"thead"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/tbody
tbody_ :: [Attribute action] -> [View action] -> View action
tbody_ :: forall action. [Attribute action] -> [View action] -> View action
tbody_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"tbody"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/tr
tr_ :: [Attribute action] -> [View action] -> View action
tr_ :: forall action. [Attribute action] -> [View action] -> View action
tr_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"tr"
-----------------------------------------------------------------------------
-- | Contains `Key`, inteded to be used for child replacement patch
--
-- <https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/tr>
-----------------------------------------------------------------------------
trKeyed_ :: Key -> [Attribute action] -> [View action] -> View action
trKeyed_ :: forall action.
Key -> [Attribute action] -> [View action] -> View action
trKeyed_ = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
"tr" (Maybe Key -> [Attribute action] -> [View action] -> View action)
-> (Key -> Maybe Key)
-> Key
-> [Attribute action]
-> [View action]
-> View action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Maybe Key
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/th
th_ :: [Attribute action] -> [View action] -> View action
th_ :: forall action. [Attribute action] -> [View action] -> View action
th_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"th"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/td
td_ :: [Attribute action] -> [View action] -> View action
td_ :: forall action. [Attribute action] -> [View action] -> View action
td_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"td"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/tfoot
tfoot_ :: [Attribute action] -> [View action] -> View action
tfoot_ :: forall action. [Attribute action] -> [View action] -> View action
tfoot_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"tfoot"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/section
section_ :: [Attribute action] -> [View action] -> View action
section_ :: forall action. [Attribute action] -> [View action] -> View action
section_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"section"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/header
header_ :: [Attribute action] -> [View action] -> View action
header_ :: forall action. [Attribute action] -> [View action] -> View action
header_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"header"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/footer
footer_ :: [Attribute action] -> [View action] -> View action
footer_ :: forall action. [Attribute action] -> [View action] -> View action
footer_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"footer"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/button
button_ :: [Attribute action] -> [View action] -> View action
button_ :: forall action. [Attribute action] -> [View action] -> View action
button_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"button"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/form
--
-- For usage in a real-world application with the `onSubmit` event.
--
-- >
-- > view :: Model -> View action
-- > view model = form [ onSubmit NoOp ] [ input [ type_ "submit" ] ]
-- >
--
-- Note: @onSubmit@ will use @preventDefault = True@. This will keep
-- the form from submitting to the server.
--
form :: [Attribute action] -> [View action] -> View action
form :: forall action. [Attribute action] -> [View action] -> View action
form = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"form"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/p
p_ :: [Attribute action] -> [View action] -> View action
p_ :: forall action. [Attribute action] -> [View action] -> View action
p_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"p"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/s
s_ :: [Attribute action] -> [View action] -> View action
s_ :: forall action. [Attribute action] -> [View action] -> View action
s_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"s"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/ul
ul_ :: [Attribute action] -> [View action] -> View action
ul_ :: forall action. [Attribute action] -> [View action] -> View action
ul_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"ul"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/span
span_ :: [Attribute action] -> [View action] -> View action
span_ :: forall action. [Attribute action] -> [View action] -> View action
span_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"span"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/strong
strong_ :: [Attribute action] -> [View action] -> View action
strong_ :: forall action. [Attribute action] -> [View action] -> View action
strong_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"strong"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/li
li_ :: [Attribute action] -> [View action] -> View action
li_ :: forall action. [Attribute action] -> [View action] -> View action
li_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"li"
-----------------------------------------------------------------------------
-- | Contains `Key`, inteded to be used for child replacement patch
--
-- <https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/li>
--
liKeyed_ :: Key -> [Attribute action] -> [View action] -> View action
liKeyed_ :: forall action.
Key -> [Attribute action] -> [View action] -> View action
liKeyed_ = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
"li" (Maybe Key -> [Attribute action] -> [View action] -> View action)
-> (Key -> Maybe Key)
-> Key
-> [Attribute action]
-> [View action]
-> View action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Maybe Key
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h1_ :: [Attribute action] -> [View action] -> View action
h1_ :: forall action. [Attribute action] -> [View action] -> View action
h1_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h1"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h2_ :: [Attribute action] -> [View action] -> View action
h2_ :: forall action. [Attribute action] -> [View action] -> View action
h2_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h2"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h3_ :: [Attribute action] -> [View action] -> View action
h3_ :: forall action. [Attribute action] -> [View action] -> View action
h3_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h3"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h4_ :: [Attribute action] -> [View action] -> View action
h4_ :: forall action. [Attribute action] -> [View action] -> View action
h4_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h4"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h5_ :: [Attribute action] -> [View action] -> View action
h5_ :: forall action. [Attribute action] -> [View action] -> View action
h5_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h5"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/Heading_Elements
h6_ :: [Attribute action] -> [View action] -> View action
h6_ :: forall action. [Attribute action] -> [View action] -> View action
h6_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"h6"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/hr
hr_ :: [Attribute action] -> View action
hr_ :: forall action. [Attribute action] -> View action
hr_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"hr") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/pre
pre_ :: [Attribute action] -> [View action] -> View action
pre_ :: forall action. [Attribute action] -> [View action] -> View action
pre_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"pre"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/input
input_ :: [Attribute action] -> View action
input_ :: forall action. [Attribute action] -> View action
input_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"input") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/label
label_ :: [Attribute action] -> [View action] -> View action
label_ :: forall action. [Attribute action] -> [View action] -> View action
label_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"label"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/a
a_ :: [Attribute action] -> [View action] -> View action
a_ :: forall action. [Attribute action] -> [View action] -> View action
a_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"a"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/mark
mark_ :: [Attribute action] -> [View action] -> View action
mark_ :: forall action. [Attribute action] -> [View action] -> View action
mark_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"mark"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/ruby
ruby_ :: [Attribute action] -> [View action] -> View action
ruby_ :: forall action. [Attribute action] -> [View action] -> View action
ruby_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"ruby"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/rt
rt_ :: [Attribute action] -> [View action] -> View action
rt_ :: forall action. [Attribute action] -> [View action] -> View action
rt_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"rt"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/rp
rp_ :: [Attribute action] -> [View action] -> View action
rp_ :: forall action. [Attribute action] -> [View action] -> View action
rp_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"rp"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/bdi
bdi_ :: [Attribute action] -> [View action] -> View action
bdi_ :: forall action. [Attribute action] -> [View action] -> View action
bdi_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"bdi"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/bdo
bdo_ :: [Attribute action] -> [View action] -> View action
bdo_ :: forall action. [Attribute action] -> [View action] -> View action
bdo_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"bdo"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/wbr
wbr_ :: [Attribute action] -> View action
wbr_ :: forall action. [Attribute action] -> View action
wbr_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"wbr") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/details
details_ :: [Attribute action] -> [View action] -> View action
details_ :: forall action. [Attribute action] -> [View action] -> View action
details_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"details"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/summary
summary_ :: [Attribute action] -> [View action] -> View action
summary_ :: forall action. [Attribute action] -> [View action] -> View action
summary_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"summary"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/menu
menu_ :: [Attribute action] -> [View action] -> View action
menu_ :: forall action. [Attribute action] -> [View action] -> View action
menu_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"menu"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/fieldset
fieldset_ :: [Attribute action] -> [View action] -> View action
fieldset_ :: forall action. [Attribute action] -> [View action] -> View action
fieldset_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"fieldset"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/legend
legend_ :: [Attribute action] -> [View action] -> View action
legend_ :: forall action. [Attribute action] -> [View action] -> View action
legend_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"legend"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/datalist
datalist_ :: [Attribute action] -> [View action] -> View action
datalist_ :: forall action. [Attribute action] -> [View action] -> View action
datalist_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"datalist"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/optgroup
optgroup_ :: [Attribute action] -> [View action] -> View action
optgroup_ :: forall action. [Attribute action] -> [View action] -> View action
optgroup_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"optgroup"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/output
output_ :: [Attribute action] -> [View action] -> View action
output_ :: forall action. [Attribute action] -> [View action] -> View action
output_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"output"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/progress
progress_ :: [Attribute action] -> [View action] -> View action
progress_ :: forall action. [Attribute action] -> [View action] -> View action
progress_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"progress"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/meter
meter_ :: [Attribute action] -> [View action] -> View action
meter_ :: forall action. [Attribute action] -> [View action] -> View action
meter_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"meter"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/audio
audio_ :: [Attribute action] -> [View action] -> View action
audio_ :: forall action. [Attribute action] -> [View action] -> View action
audio_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"audio"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/video
video_ :: [Attribute action] -> [View action] -> View action
video_ :: forall action. [Attribute action] -> [View action] -> View action
video_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"video"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/source
source_ :: [Attribute action] -> View action
source_ :: forall action. [Attribute action] -> View action
source_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"source") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/track
track_ :: [Attribute action] -> View action
track_ :: forall action. [Attribute action] -> View action
track_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"track") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/embed
embed_ :: [Attribute action] -> View action
embed_ :: forall action. [Attribute action] -> View action
embed_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"embed") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/object
object_ :: [Attribute action] -> [View action] -> View action
object_ :: forall action. [Attribute action] -> [View action] -> View action
object_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"object"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/ins
ins_ :: [Attribute action] -> [View action] -> View action
ins_ :: forall action. [Attribute action] -> [View action] -> View action
ins_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"ins"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/del
del_ :: [Attribute action] -> [View action] -> View action
del_ :: forall action. [Attribute action] -> [View action] -> View action
del_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"del"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/small
small_ :: [Attribute action] -> [View action] -> View action
small_ :: forall action. [Attribute action] -> [View action] -> View action
small_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"small"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/cite
cite_ :: [Attribute action] -> [View action] -> View action
cite_ :: forall action. [Attribute action] -> [View action] -> View action
cite_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"cite"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/dfn
dfn_ :: [Attribute action] -> [View action] -> View action
dfn_ :: forall action. [Attribute action] -> [View action] -> View action
dfn_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"dfn"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/abbr
abbr_ :: [Attribute action] -> [View action] -> View action
abbr_ :: forall action. [Attribute action] -> [View action] -> View action
abbr_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"abbr"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/time
time_ :: [Attribute action] -> [View action] -> View action
time_ :: forall action. [Attribute action] -> [View action] -> View action
time_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"time"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/var
var_ :: [Attribute action] -> [View action] -> View action
var_ :: forall action. [Attribute action] -> [View action] -> View action
var_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"var"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/samp
samp_ :: [Attribute action] -> [View action] -> View action
samp_ :: forall action. [Attribute action] -> [View action] -> View action
samp_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"samp"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/kbd
kbd_ :: [Attribute action] -> [View action] -> View action
kbd_ :: forall action. [Attribute action] -> [View action] -> View action
kbd_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"kbd"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/caption
caption_ :: [Attribute action] -> [View action] -> View action
caption_ :: forall action. [Attribute action] -> [View action] -> View action
caption_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"caption"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/colgroup
colgroup_ :: [Attribute action] -> [View action] -> View action
colgroup_ :: forall action. [Attribute action] -> [View action] -> View action
colgroup_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"colgroup"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/col
col_ :: [Attribute action] -> View action
col_ :: forall action. [Attribute action] -> View action
col_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"col") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/nav
nav_ :: [Attribute action] -> [View action] -> View action
nav_ :: forall action. [Attribute action] -> [View action] -> View action
nav_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"nav"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/article
article_ :: [Attribute action] -> [View action] -> View action
article_ :: forall action. [Attribute action] -> [View action] -> View action
article_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"article"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/aside
aside_ :: [Attribute action] -> [View action] -> View action
aside_ :: forall action. [Attribute action] -> [View action] -> View action
aside_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"aside"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/address
address_ :: [Attribute action] -> [View action] -> View action
address_ :: forall action. [Attribute action] -> [View action] -> View action
address_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"address"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/main
main_ :: [Attribute action] -> [View action] -> View action
main_ :: forall action. [Attribute action] -> [View action] -> View action
main_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"main"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/body
body_ :: [Attribute action] -> [View action] -> View action
body_ :: forall action. [Attribute action] -> [View action] -> View action
body_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"body"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/figure
figure_ :: [Attribute action] -> [View action] -> View action
figure_ :: forall action. [Attribute action] -> [View action] -> View action
figure_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"figure"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/figcaption
figcaption_ :: [Attribute action] -> [View action] -> View action
figcaption_ :: forall action. [Attribute action] -> [View action] -> View action
figcaption_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"figcaption"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/dl
dl_ :: [Attribute action] -> [View action] -> View action
dl_ :: forall action. [Attribute action] -> [View action] -> View action
dl_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"dl"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/dt
dt_ :: [Attribute action] -> [View action] -> View action
dt_ :: forall action. [Attribute action] -> [View action] -> View action
dt_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"dt"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/dd
dd_ :: [Attribute action] -> [View action] -> View action
dd_ :: forall action. [Attribute action] -> [View action] -> View action
dd_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"dd"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/img
img_ :: [Attribute action] -> View action
img_ :: forall action. [Attribute action] -> View action
img_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"img") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/iframe
iframe_ :: [Attribute action] -> [View action] -> View action
iframe_ :: forall action. [Attribute action] -> [View action] -> View action
iframe_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"iframe"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/canvas
canvas_ :: [Attribute action] -> [View action] -> View action
canvas_ :: forall action. [Attribute action] -> [View action] -> View action
canvas_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"canvas"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/select
select_ :: [Attribute action] -> [View action] -> View action
select_ :: forall action. [Attribute action] -> [View action] -> View action
select_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"select"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/option
option_ :: [Attribute action] -> [View action] -> View action
option_ :: forall action. [Attribute action] -> [View action] -> View action
option_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"option"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/textarea
textarea_ :: [Attribute action] -> [View action] -> View action
textarea_ :: forall action. [Attribute action] -> [View action] -> View action
textarea_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"textarea"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/sub
sub_ :: [Attribute action] -> [View action] -> View action
sub_ :: forall action. [Attribute action] -> [View action] -> View action
sub_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"sub"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/sup
sup_ :: [Attribute action] -> [View action] -> View action
sup_ :: forall action. [Attribute action] -> [View action] -> View action
sup_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"sup"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/br
br_ :: [Attribute action] -> View action
br_ :: forall action. [Attribute action] -> View action
br_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"br") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/ol
ol_ :: [Attribute action] -> [View action] -> View action
ol_ :: forall action. [Attribute action] -> [View action] -> View action
ol_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"ol"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/blockquote
blockquote_ :: [Attribute action] -> [View action] -> View action
blockquote_ :: forall action. [Attribute action] -> [View action] -> View action
blockquote_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"blockquote"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/code
code_ :: [Attribute action] -> [View action] -> View action
code_ :: forall action. [Attribute action] -> [View action] -> View action
code_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"code"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/em
em_ :: [Attribute action] -> [View action] -> View action
em_ :: forall action. [Attribute action] -> [View action] -> View action
em_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"em"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/i
i_ :: [Attribute action] -> [View action] -> View action
i_ :: forall action. [Attribute action] -> [View action] -> View action
i_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"i"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/b
b_ :: [Attribute action] -> [View action] -> View action
b_ :: forall action. [Attribute action] -> [View action] -> View action
b_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"b"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/u
u_ :: [Attribute action] -> [View action] -> View action
u_ :: forall action. [Attribute action] -> [View action] -> View action
u_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"u"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/q
q_ :: [Attribute action] -> [View action] -> View action
q_ :: forall action. [Attribute action] -> [View action] -> View action
q_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"q"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/link
link_ :: [Attribute action] -> View action
link_ :: forall action. [Attribute action] -> View action
link_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"link") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/style
--
-- This takes the raw text to be put in the style tag.
--
-- That means that if any part of the text is not trusted there's
-- a potential CSS injection. Read more at
-- https://owasp.org/www-project-web-security-testing-guide/latest/4-Web_Application_Security_Testing/11-Client_Side_Testing/05-Testing_for_CSS_Injection
--
-- You can also easily shoot yourself in the foot with something like:
--
-- @'style_' [] "\</style\>"@
style_ :: [Attribute action] -> MisoString -> View action
style_ :: forall action. [Attribute action] -> MisoString -> View action
style_ [Attribute action]
attrs MisoString
rawText = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
"style" Maybe Key
forall a. Maybe a
Nothing [Attribute action]
attrs [MisoString -> View action
forall action. MisoString -> View action
textRaw MisoString
rawText]
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/script
--
-- This takes the raw text to be put in the script tag.
--
-- That means that if any part of the text is not trusted there's
-- a potential JavaScript injection. Read more at
-- https://owasp.org/www-community/attacks/xss/
--
-- You can also easily shoot yourself in the foot with something like:
--
-- @'script_' [] "\</script\>"@
script_ :: [Attribute action] -> MisoString -> View action
script_ :: forall action. [Attribute action] -> MisoString -> View action
script_ [Attribute action]
attrs MisoString
rawText = NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
forall action.
NS
-> MisoString
-> Maybe Key
-> [Attribute action]
-> [View action]
-> View action
node NS
HTML MisoString
"script" Maybe Key
forall a. Maybe a
Nothing [Attribute action]
attrs [MisoString -> View action
forall action. MisoString -> View action
textRaw MisoString
rawText]
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Glossary/Doctype
doctype_ :: View action
doctype_ :: forall action. View action
doctype_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"doctype" [] []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/html
html_ :: [Attribute action] -> [View action] -> View action
html_ :: forall action. [Attribute action] -> [View action] -> View action
html_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"html"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/head
head_ :: [Attribute action] -> [View action] -> View action
head_ :: forall action. [Attribute action] -> [View action] -> View action
head_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"head"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/meta
meta_ :: [Attribute action] -> View action
meta_ :: forall action. [Attribute action] -> View action
meta_ = ([Attribute action] -> [View action] -> View action)
-> [View action] -> [Attribute action] -> View action
forall a b c. (a -> b -> c) -> b -> a -> c
flip (MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"meta") []
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/area
area_ :: [Attribute action] -> [View action] -> View action
area_ :: forall action. [Attribute action] -> [View action] -> View action
area_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"area"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/base
base_ :: [Attribute action] -> [View action] -> View action
base_ :: forall action. [Attribute action] -> [View action] -> View action
base_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"base"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/data
data_ :: [Attribute action] -> [View action] -> View action
data_ :: forall action. [Attribute action] -> [View action] -> View action
data_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"data"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/dialog
dialog_ :: [Attribute action] -> [View action] -> View action
dialog_ :: forall action. [Attribute action] -> [View action] -> View action
dialog_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"dialog"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/fencedframe
fencedframe_ :: [Attribute action] -> [View action] -> View action
fencedframe_ :: forall action. [Attribute action] -> [View action] -> View action
fencedframe_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"fencedframe"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/hgroup
hgroup_ :: [Attribute action] -> [View action] -> View action
hgroup_ :: forall action. [Attribute action] -> [View action] -> View action
hgroup_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"hgroup"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/map
map_ :: [Attribute action] -> [View action] -> View action
map_ :: forall action. [Attribute action] -> [View action] -> View action
map_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"map"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/noscript
noscript_ :: [Attribute action] -> [View action] -> View action
noscript_ :: forall action. [Attribute action] -> [View action] -> View action
noscript_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"noscript"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/picture
picture_ :: [Attribute action] -> [View action] -> View action
picture_ :: forall action. [Attribute action] -> [View action] -> View action
picture_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"picture"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/search
search_ :: [Attribute action] -> [View action] -> View action
search_ :: forall action. [Attribute action] -> [View action] -> View action
search_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"search"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/slot
slot_ :: [Attribute action] -> [View action] -> View action
slot_ :: forall action. [Attribute action] -> [View action] -> View action
slot_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"slot"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/template
template_ :: [Attribute action] -> [View action] -> View action
template_ :: forall action. [Attribute action] -> [View action] -> View action
template_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"template"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/HTML/Reference/Elements/title
title_ :: [Attribute action] -> [View action] -> View action
title_ :: forall action. [Attribute action] -> [View action] -> View action
title_ = MisoString -> [Attribute action] -> [View action] -> View action
forall action.
MisoString -> [Attribute action] -> [View action] -> View action
nodeHtml MisoString
"title"
-----------------------------------------------------------------------------