type-of-html-0.2.1.1: High performance type driven html generation.

Safe HaskellNone
LanguageHaskell2010

Html

Description

With type-of-html are three main goals:

  • Type safety
  • Modularity
  • Performance

Let's check out the type safety in ghci:

Html> td_ (tr_ "a")

<interactive>:1:1: error:
    • 'Tr is not a valid child of 'Td
    • In the expression: td_ (tr_ "a")
      In an equation for ‘it’: it = td_ (tr_ "a")

<interactive>:1:6: error:
    • 'Tr can't contain a string
    • In the first argument of ‘td_’, namely ‘(tr_ "a")’
      In the expression: td_ (tr_ "a")
      In an equation for ‘it’: it = td_ (tr_ "a")

For every child, it is checked if it could possibly be lawful.

The checking is a bit lenient at the moment:

  • some elements can't contain itself as any descendant: at the moment we look only at direct children. This allows some (quite exotic) invalid html documents.
  • some elements change their permitted content based on attributes: we don't know at compile time the attributes, therefore we always allow content as if all relevant attributes are set.
  • some elements can't be brethren: we look only at parent child relations, therefore if you don't specify the parent, it'll compile

Never the less: these cases are seldom. In the vast majority of the time you're only allowed to construct valid html.

Let's talk about modularity:

Rosetrees of html are just ordinary haskell values which can be composed or abstracted over:

Html> let table = table_ . map (tr_ . map td_)
Html> :t table
table :: ('Td ?> a) => [[a]] -> 'Table > ['Tr > ['Td > a]]
Html> table [["A","B"],["C"]]
<table><tr><td>A<td>B<tr><td>C</table>
Html> import Data.Char
Html Data.Char> html_ . body_ . table $ map (\c -> [[c], show $ ord c]) ['a'..'d']
<html><body><table><tr><td>a<td>97<tr><td>b<td>98<tr><td>c<td>99<tr><td>d<td>100</table></body></html>

And here's an example module

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds     #-}

module Main where

import Html

import Data.Text.Lazy.IO      as T
import Data.Text.Lazy.Builder as T

main :: IO ()
main
  = T.putStrLn
  . T.toLazyText
  . render
  . page
  $ map td_ [1..(10::Int)]

page
  :: 'Tr ?> a
  => a
  -> 'Div
     > ( 'Div > [Char]
       # 'Div > [Char]
       # 'Table > 'Tr > a
       )
page tds =
  div_
    ( div_ "foo"
    # div_ "bar"
    # table_ (tr_ tds)
    )

Please note that the type of page is inferable, so ask ghc-mod or whatever you use to write it for you. If you choose not to write the types, you don't need the language extensions.

Last and fast: performance!

Don't look any further, there is no option for faster html generation. type-of-html up to 10 times faster than blaze-html, which is until now the fastest generation library and the foundation block of lucid and shakespeare.

Wait! 10 times faster? How is this possible? We supercompile lots of parts of the generation process. This is possible thanks to the new features of GHC 8.2: AppendSymbol. We represent tags as kinds and remove according to the html specification omittable closing tags with type families. Afterwards we map these tags to (a :: [Symbol]) and then fold all neighbouring Proxies with AppendSymbol. Afterwards we retrieve the Proxies with symbolVal which will be embedded in the executable as CString. All this happens at compile time. At runtime we do only generate the content and mconcat.

For example, if you write:

render $ div_ "a"

The compiler does actually optimize it to the following:

mconcat [ fromString $ symbolVal (Proxy :: Proxy "<div>")
        , fromString "a"
        , fromString $ symbolVal (Proxy :: Proxy "</div>")
        ]

If you write

render $ div_ (div_ ())

The compiler does actually optimize it to the following:

mconcat [ fromString $ symbolVal (Proxy :: Proxy "<div><div></div></div>") ]

If you write

render $ tr_ (td_ "test")

The compiler does actually optimize it to the following:

mconcat [ fromString $ symbolVal (Proxy :: Proxy "<tr><td>")
        , fromString "test"
        , fromString $ symbolVal (Proxy :: Proxy "</tr>")
        ]

Let's look at core:

We take an extremely simple library

module Minimal where

import Html

minimal :: String
minimal = render
  ( div_ "a"
  # div_ "b"
  # table_ (tr_ (td_ "c"))
  )

compile it with

ghc -O2 Minimal.hs -ddump-to-file -ddump-simpl -dsuppress-idinfo -dsuppress-module-prefixes -dsuppress-type-applications -dsuppress-uniques

and clean up a bit:

minimal1 :: Addr#
minimal1 = "<div>a</div><div>b</div><table><tr><td>c</table>"#

minimal :: String
minimal = unpackCString# minimal1

Well, that's a perfect optimization! Not only was *all* overhead removed, optional ending tags were chopped off (tr, td). This sort of compiletime optimization isn't for free. Running ghc with -v says that desugaring resulted in 675 types and 5507 coercions: Compile times will increase, some medium size html documents will take 10 secs to compile.

Synopsis

Documentation

render :: forall a b. (Document a, Escape b, Monoid b, IsString b) => a -> b Source #

Render a html document. The resulting type can be a String, strict Text, lazy Text, or Builder. For performance it is recommended to use a lazy Text or a Builder.

>>> render "a" :: String
"a"
>>> render (div_ "a") :: Text
"<div>a</div>"

For prototyping, there's as well a Show instance:

>>> i_ "a"
<i>a</i>

Please note the extra quotes for String when using show:

>>> show "a" == render "a"
False
>>> show img_ == render img_
True

data (a :: Element) > b where infixr 8 Source #

Descend to a valid child of an element. It is recommended to use the predefined elements.

>>> Child "a" :: 'Div > String
<div>a</div>
>>> div_ "a"
<div>a</div>

Constructors

Child :: a ?> b => b -> a > b 

data (a :: Element) :> b where infixr 8 Source #

Decorate an element with attributes and descend to a valid child.

>>> WithAttributes [("foo","bar")] "a" :: 'Div :> String
<div foo=bar>a</div>

Constructors

WithAttributes :: a ?> b => Attributes -> b -> a :> b 

addAttributes :: a ?> b => [(String, String)] -> (a > b) -> a :> b Source #

data a # b infixr 5 Source #

Combine two elements sequentially.

>>> render (i_ () # div_ ()) :: String
"<i></i><div></div>"

Constructors

(:#:) a b 

(#) :: a -> b -> a # b infixr 5 Source #

type family (a :: Element) ?> b :: Constraint where ... Source #

Check whether b is a valid child of a. You'll propably never need to call this directly. Through a GADT, it is enforced that every child is lawful.

The only way to circumvent this would be to use undefined or error in combination with only type level values.

>>> undefined :: 'Div > ('Html > ())
<div><html></html></div>
>>> undefined :: 'Div > ('Html > Proxy "a")
<div><html>a</html></div>
>>> undefined :: 'Div > ('Html > String)
<div><html>*** Exception: Prelude.undefined

Equations

a ?> (b # c) = (a ?> b, a ?> c) 
a ?> (b > _) = MaybeTypeError a b (TestPaternity (SingleElement b) (GetInfo a) (GetInfo b)) 
a ?> (b :> _) = MaybeTypeError a b (TestPaternity (SingleElement b) (GetInfo a) (GetInfo b)) 
a ?> (Maybe b) = a ?> b 
a ?> (Either b c) = (a ?> b, a ?> c) 
a ?> (f (b > c)) = a ?> (b > c) 
a ?> (f (b :> c)) = a ?> (b > c) 
a ?> (f (b # c)) = a ?> (b # c) 
a ?> () = () 
a ?> (b -> c) = TypeError (Text "Html elements can't contain functions") 
a ?> b = CheckString a 

class Convert a where Source #

Convert something to a target stringlike thing.

Minimal complete definition

convert

Methods

convert :: (Escape b, IsString b, Monoid b) => a -> b Source #

Instances

Convert Double Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Double -> b Source #

Convert Float Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Float -> b Source #

Convert Int Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Int -> b Source #

Convert Integer Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Integer -> b Source #

Convert Word Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Word -> b Source #

Convert String Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => String -> b Source #

Convert Builder Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Builder -> b Source #

Convert Text Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Text -> b Source #

Convert Text Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Text -> b Source #

Convert a => Convert (Maybe a) Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Maybe a -> b Source #

KnownSymbol a => Convert (Proxy Symbol a) Source # 

Methods

convert :: (Escape b, IsString b, Monoid b) => Proxy Symbol a -> b Source #

class (IsString a, Monoid a) => Escape a where Source #

Minimal complete definition

escape

Methods

escape :: a -> a Source #

data Element Source #

The data type of all html elements and the kind of elements.

Constructors

DOCTYPE 
A 
Abbr 
Acronym

Deprecated: This is an obsolete html element and should not be used.

Address 
Applet

Deprecated: This is an obsolete html element and should not be used.

Area 
Article 
Aside 
Audio 
B 
Base 
Basefont

Deprecated: This is an obsolete html element and should not be used.

Bdi 
Bdo 
Bgsound 
Big

Deprecated: This is an obsolete html element and should not be used.

Blink

Deprecated: This is an obsolete html element and should not be used.

Blockquote 
Body 
Br 
Button 
Canvas 
Caption 
Center

Deprecated: This is an obsolete html element and should not be used.

Cite 
Code 
Col 
Colgroup 
Command

Deprecated: This is an obsolete html element and should not be used.

Content

Deprecated: This is an obsolete html element and should not be used.

Data 
Datalist 
Dd 
Del 
Details 
Dfn 
Dialog 
Dir

Deprecated: This is an obsolete html element and should not be used.

Div 
Dl 
Dt 
Element 
Em 
Embed 
Fieldset 
Figcaption 
Figure 
Font

Deprecated: This is an obsolete html element and should not be used.

Footer 
Form 
Frame

Deprecated: This is an obsolete html element and should not be used.

Frameset

Deprecated: This is an obsolete html element and should not be used.

H1 
H2 
H3 
H4 
H5 
H6 
Head 
Header 
Hgroup 
Hr 
Html 
I 
Iframe 
Image 
Img 
Input 
Ins 
Isindex

Deprecated: This is an obsolete html element and should not be used.

Kbd 
Keygen

Deprecated: This is an obsolete html element and should not be used.

Label 
Legend 
Li 
Link 
Listing

Deprecated: This is an obsolete html element and should not be used.

Main 
Map 
Mark 
Marquee

Deprecated: This is an obsolete html element and should not be used.

Math 
Menu 
Menuitem 
Meta 
Meter 
Multicol

Deprecated: This is an obsolete html element and should not be used.

Nav 
Nextid

Deprecated: This is an obsolete html element and should not be used.

Nobr 
Noembed

Deprecated: This is an obsolete html element and should not be used.

Noframes 
Noscript 
Object 
Ol 
Optgroup 
Option 
Output 
P 
Param 
Picture 
Plaintext

Deprecated: This is an obsolete html element and should not be used.

Pre 
Progress 
Q 
Rp 
Rt 
Rtc 
Ruby 
S 
Samp 
Script 
Section 
Select 
Shadow

Deprecated: This is an obsolete html element and should not be used.

Slot 
Small 
Source 
Spacer

Deprecated: This is an obsolete html element and should not be used.

Span 
Strike

Deprecated: This is an obsolete html element and should not be used.

Strong 
Style 
Sub 
Summary 
Sup 
Svg 
Table 
Tbody 
Td 
Template 
Textarea 
Tfoot 
Th 
Thead 
Time 
Title 
Tr 
Track 
Tt

Deprecated: This is an obsolete html element and should not be used.

U 
Ul 
Var 
Video 
Wbr 
Xmp

Deprecated: This is an obsolete html element and should not be used.

a_ :: A ?> a => a -> A > a Source #

a_A :: A ?> a => [(String, String)] -> a -> A :> a Source #

abbr_ :: Abbr ?> a => a -> Abbr > a Source #

abbr_A :: Abbr ?> a => [(String, String)] -> a -> Abbr :> a Source #

acronym_A :: Acronym ?> a => [(String, String)] -> a -> Acronym :> a Source #

address_A :: Address ?> a => [(String, String)] -> a -> Address :> a Source #

applet_ :: Applet ?> a => a -> Applet > a Source #

applet_A :: Applet ?> a => [(String, String)] -> a -> Applet :> a Source #

article_A :: Article ?> a => [(String, String)] -> a -> Article :> a Source #

aside_ :: Aside ?> a => a -> Aside > a Source #

aside_A :: Aside ?> a => [(String, String)] -> a -> Aside :> a Source #

audio_ :: Audio ?> a => a -> Audio > a Source #

audio_A :: Audio ?> a => [(String, String)] -> a -> Audio :> a Source #

b_ :: B ?> a => a -> B > a Source #

b_A :: B ?> a => [(String, String)] -> a -> B :> a Source #

bdi_ :: Bdi ?> a => a -> Bdi > a Source #

bdi_A :: Bdi ?> a => [(String, String)] -> a -> Bdi :> a Source #

bdo_ :: Bdo ?> a => a -> Bdo > a Source #

bdo_A :: Bdo ?> a => [(String, String)] -> a -> Bdo :> a Source #

bgsound_A :: Bgsound ?> a => [(String, String)] -> a -> Bgsound :> a Source #

big_ :: Big ?> a => a -> Big > a Source #

big_A :: Big ?> a => [(String, String)] -> a -> Big :> a Source #

blink_ :: Blink ?> a => a -> Blink > a Source #

blink_A :: Blink ?> a => [(String, String)] -> a -> Blink :> a Source #

body_ :: Body ?> a => a -> Body > a Source #

body_A :: Body ?> a => [(String, String)] -> a -> Body :> a Source #

br_ :: Br > () Source #

br_A :: [(String, String)] -> Br :> () Source #

button_ :: Button ?> a => a -> Button > a Source #

button_A :: Button ?> a => [(String, String)] -> a -> Button :> a Source #

canvas_ :: Canvas ?> a => a -> Canvas > a Source #

canvas_A :: Canvas ?> a => [(String, String)] -> a -> Canvas :> a Source #

caption_A :: Caption ?> a => [(String, String)] -> a -> Caption :> a Source #

center_ :: Center ?> a => a -> Center > a Source #

center_A :: Center ?> a => [(String, String)] -> a -> Center :> a Source #

cite_ :: Cite ?> a => a -> Cite > a Source #

cite_A :: Cite ?> a => [(String, String)] -> a -> Cite :> a Source #

code_ :: Code ?> a => a -> Code > a Source #

code_A :: Code ?> a => [(String, String)] -> a -> Code :> a Source #

col_ :: Col > () Source #

col_A :: [(String, String)] -> Col :> () Source #

command_A :: Command ?> a => [(String, String)] -> a -> Command :> a Source #

content_A :: Content ?> a => [(String, String)] -> a -> Content :> a Source #

data_ :: Data ?> a => a -> Data > a Source #

data_A :: Data ?> a => [(String, String)] -> a -> Data :> a Source #

dd_ :: Dd ?> a => a -> Dd > a Source #

dd_A :: Dd ?> a => [(String, String)] -> a -> Dd :> a Source #

del_ :: Del ?> a => a -> Del > a Source #

del_A :: Del ?> a => [(String, String)] -> a -> Del :> a Source #

details_A :: Details ?> a => [(String, String)] -> a -> Details :> a Source #

dfn_ :: Dfn ?> a => a -> Dfn > a Source #

dfn_A :: Dfn ?> a => [(String, String)] -> a -> Dfn :> a Source #

dialog_ :: Dialog ?> a => a -> Dialog > a Source #

dialog_A :: Dialog ?> a => [(String, String)] -> a -> Dialog :> a Source #

dir_ :: Dir ?> a => a -> Dir > a Source #

dir_A :: Dir ?> a => [(String, String)] -> a -> Dir :> a Source #

div_ :: Div ?> a => a -> Div > a Source #

div_A :: Div ?> a => [(String, String)] -> a -> Div :> a Source #

dl_ :: Dl ?> a => a -> Dl > a Source #

dl_A :: Dl ?> a => [(String, String)] -> a -> Dl :> a Source #

dt_ :: Dt ?> a => a -> Dt > a Source #

dt_A :: Dt ?> a => [(String, String)] -> a -> Dt :> a Source #

element_A :: Element ?> a => [(String, String)] -> a -> Element :> a Source #

em_ :: Em ?> a => a -> Em > a Source #

em_A :: Em ?> a => [(String, String)] -> a -> Em :> a Source #

figure_ :: Figure ?> a => a -> Figure > a Source #

figure_A :: Figure ?> a => [(String, String)] -> a -> Figure :> a Source #

font_ :: Font ?> a => a -> Font > a Source #

font_A :: Font ?> a => [(String, String)] -> a -> Font :> a Source #

footer_ :: Footer ?> a => a -> Footer > a Source #

footer_A :: Footer ?> a => [(String, String)] -> a -> Footer :> a Source #

form_ :: Form ?> a => a -> Form > a Source #

form_A :: Form ?> a => [(String, String)] -> a -> Form :> a Source #

frame_ :: Frame ?> a => a -> Frame > a Source #

frame_A :: Frame ?> a => [(String, String)] -> a -> Frame :> a Source #

h1_ :: H1 ?> a => a -> H1 > a Source #

h1_A :: H1 ?> a => [(String, String)] -> a -> H1 :> a Source #

h2_ :: H2 ?> a => a -> H2 > a Source #

h2_A :: H2 ?> a => [(String, String)] -> a -> H2 :> a Source #

h3_ :: H3 ?> a => a -> H3 > a Source #

h3_A :: H3 ?> a => [(String, String)] -> a -> H3 :> a Source #

h4_ :: H4 ?> a => a -> H4 > a Source #

h4_A :: H4 ?> a => [(String, String)] -> a -> H4 :> a Source #

h5_ :: H5 ?> a => a -> H5 > a Source #

h5_A :: H5 ?> a => [(String, String)] -> a -> H5 :> a Source #

h6_ :: H6 ?> a => a -> H6 > a Source #

h6_A :: H6 ?> a => [(String, String)] -> a -> H6 :> a Source #

head_ :: Head ?> a => a -> Head > a Source #

head_A :: Head ?> a => [(String, String)] -> a -> Head :> a Source #

header_ :: Header ?> a => a -> Header > a Source #

header_A :: Header ?> a => [(String, String)] -> a -> Header :> a Source #

hgroup_ :: Hgroup ?> a => a -> Hgroup > a Source #

hgroup_A :: Hgroup ?> a => [(String, String)] -> a -> Hgroup :> a Source #

hr_ :: Hr > () Source #

hr_A :: [(String, String)] -> Hr :> () Source #

html_ :: Html ?> a => a -> Html > a Source #

html_A :: Html ?> a => [(String, String)] -> a -> Html :> a Source #

i_ :: I ?> a => a -> I > a Source #

i_A :: I ?> a => [(String, String)] -> a -> I :> a Source #

image_ :: Image ?> a => a -> Image > a Source #

image_A :: Image ?> a => [(String, String)] -> a -> Image :> a Source #

img_ :: Img > () Source #

img_A :: [(String, String)] -> Img :> () Source #

input_ :: Input ?> a => a -> Input > a Source #

input_A :: Input ?> a => [(String, String)] -> a -> Input :> a Source #

ins_ :: Ins ?> a => a -> Ins > a Source #

ins_A :: Ins ?> a => [(String, String)] -> a -> Ins :> a Source #

isindex_A :: Isindex ?> a => [(String, String)] -> a -> Isindex :> a Source #

kbd_ :: Kbd ?> a => a -> Kbd > a Source #

kbd_A :: Kbd ?> a => [(String, String)] -> a -> Kbd :> a Source #

keygen_ :: Keygen ?> a => a -> Keygen > a Source #

keygen_A :: Keygen ?> a => [(String, String)] -> a -> Keygen :> a Source #

label_ :: Label ?> a => a -> Label > a Source #

label_A :: Label ?> a => [(String, String)] -> a -> Label :> a Source #

legend_ :: Legend ?> a => a -> Legend > a Source #

legend_A :: Legend ?> a => [(String, String)] -> a -> Legend :> a Source #

li_ :: Li ?> a => a -> Li > a Source #

li_A :: Li ?> a => [(String, String)] -> a -> Li :> a Source #

listing_A :: Listing ?> a => [(String, String)] -> a -> Listing :> a Source #

main_ :: Main ?> a => a -> Main > a Source #

main_A :: Main ?> a => [(String, String)] -> a -> Main :> a Source #

map_ :: Map ?> a => a -> Map > a Source #

map_A :: Map ?> a => [(String, String)] -> a -> Map :> a Source #

mark_ :: Mark ?> a => a -> Mark > a Source #

mark_A :: Mark ?> a => [(String, String)] -> a -> Mark :> a Source #

marquee_A :: Marquee ?> a => [(String, String)] -> a -> Marquee :> a Source #

math_ :: Math ?> a => a -> Math > a Source #

math_A :: Math ?> a => [(String, String)] -> a -> Math :> a Source #

menu_ :: Menu ?> a => a -> Menu > a Source #

menu_A :: Menu ?> a => [(String, String)] -> a -> Menu :> a Source #

meter_ :: Meter ?> a => a -> Meter > a Source #

meter_A :: Meter ?> a => [(String, String)] -> a -> Meter :> a Source #

nav_ :: Nav ?> a => a -> Nav > a Source #

nav_A :: Nav ?> a => [(String, String)] -> a -> Nav :> a Source #

nextid_ :: Nextid ?> a => a -> Nextid > a Source #

nextid_A :: Nextid ?> a => [(String, String)] -> a -> Nextid :> a Source #

nobr_ :: Nobr ?> a => a -> Nobr > a Source #

nobr_A :: Nobr ?> a => [(String, String)] -> a -> Nobr :> a Source #

noembed_A :: Noembed ?> a => [(String, String)] -> a -> Noembed :> a Source #

object_ :: Object ?> a => a -> Object > a Source #

object_A :: Object ?> a => [(String, String)] -> a -> Object :> a Source #

ol_ :: Ol ?> a => a -> Ol > a Source #

ol_A :: Ol ?> a => [(String, String)] -> a -> Ol :> a Source #

option_ :: Option ?> a => a -> Option > a Source #

option_A :: Option ?> a => [(String, String)] -> a -> Option :> a Source #

output_ :: Output ?> a => a -> Output > a Source #

output_A :: Output ?> a => [(String, String)] -> a -> Output :> a Source #

p_ :: P ?> a => a -> P > a Source #

p_A :: P ?> a => [(String, String)] -> a -> P :> a Source #

picture_A :: Picture ?> a => [(String, String)] -> a -> Picture :> a Source #

pre_ :: Pre ?> a => a -> Pre > a Source #

pre_A :: Pre ?> a => [(String, String)] -> a -> Pre :> a Source #

q_ :: Q ?> a => a -> Q > a Source #

q_A :: Q ?> a => [(String, String)] -> a -> Q :> a Source #

rp_ :: Rp ?> a => a -> Rp > a Source #

rp_A :: Rp ?> a => [(String, String)] -> a -> Rp :> a Source #

rt_ :: Rt ?> a => a -> Rt > a Source #

rt_A :: Rt ?> a => [(String, String)] -> a -> Rt :> a Source #

rtc_ :: Rtc ?> a => a -> Rtc > a Source #

rtc_A :: Rtc ?> a => [(String, String)] -> a -> Rtc :> a Source #

ruby_ :: Ruby ?> a => a -> Ruby > a Source #

ruby_A :: Ruby ?> a => [(String, String)] -> a -> Ruby :> a Source #

s_ :: S ?> a => a -> S > a Source #

s_A :: S ?> a => [(String, String)] -> a -> S :> a Source #

samp_ :: Samp ?> a => a -> Samp > a Source #

samp_A :: Samp ?> a => [(String, String)] -> a -> Samp :> a Source #

script_ :: Script ?> a => a -> Script > a Source #

script_A :: Script ?> a => [(String, String)] -> a -> Script :> a Source #

section_A :: Section ?> a => [(String, String)] -> a -> Section :> a Source #

select_ :: Select ?> a => a -> Select > a Source #

select_A :: Select ?> a => [(String, String)] -> a -> Select :> a Source #

shadow_ :: Shadow ?> a => a -> Shadow > a Source #

shadow_A :: Shadow ?> a => [(String, String)] -> a -> Shadow :> a Source #

slot_ :: Slot ?> a => a -> Slot > a Source #

slot_A :: Slot ?> a => [(String, String)] -> a -> Slot :> a Source #

small_ :: Small ?> a => a -> Small > a Source #

small_A :: Small ?> a => [(String, String)] -> a -> Small :> a Source #

spacer_ :: Spacer ?> a => a -> Spacer > a Source #

spacer_A :: Spacer ?> a => [(String, String)] -> a -> Spacer :> a Source #

span_ :: Span ?> a => a -> Span > a Source #

span_A :: Span ?> a => [(String, String)] -> a -> Span :> a Source #

strike_ :: Strike ?> a => a -> Strike > a Source #

strike_A :: Strike ?> a => [(String, String)] -> a -> Strike :> a Source #

strong_ :: Strong ?> a => a -> Strong > a Source #

strong_A :: Strong ?> a => [(String, String)] -> a -> Strong :> a Source #

style_ :: Style ?> a => a -> Style > a Source #

style_A :: Style ?> a => [(String, String)] -> a -> Style :> a Source #

sub_ :: Sub ?> a => a -> Sub > a Source #

sub_A :: Sub ?> a => [(String, String)] -> a -> Sub :> a Source #

summary_A :: Summary ?> a => [(String, String)] -> a -> Summary :> a Source #

sup_ :: Sup ?> a => a -> Sup > a Source #

sup_A :: Sup ?> a => [(String, String)] -> a -> Sup :> a Source #

svg_ :: Svg ?> a => a -> Svg > a Source #

svg_A :: Svg ?> a => [(String, String)] -> a -> Svg :> a Source #

table_ :: Table ?> a => a -> Table > a Source #

table_A :: Table ?> a => [(String, String)] -> a -> Table :> a Source #

tbody_ :: Tbody ?> a => a -> Tbody > a Source #

tbody_A :: Tbody ?> a => [(String, String)] -> a -> Tbody :> a Source #

td_ :: Td ?> a => a -> Td > a Source #

td_A :: Td ?> a => [(String, String)] -> a -> Td :> a Source #

tfoot_ :: Tfoot ?> a => a -> Tfoot > a Source #

tfoot_A :: Tfoot ?> a => [(String, String)] -> a -> Tfoot :> a Source #

th_ :: Th ?> a => a -> Th > a Source #

th_A :: Th ?> a => [(String, String)] -> a -> Th :> a Source #

thead_ :: Thead ?> a => a -> Thead > a Source #

thead_A :: Thead ?> a => [(String, String)] -> a -> Thead :> a Source #

time_ :: Time ?> a => a -> Time > a Source #

time_A :: Time ?> a => [(String, String)] -> a -> Time :> a Source #

title_ :: Title ?> a => a -> Title > a Source #

title_A :: Title ?> a => [(String, String)] -> a -> Title :> a Source #

tr_ :: Tr ?> a => a -> Tr > a Source #

tr_A :: Tr ?> a => [(String, String)] -> a -> Tr :> a Source #

tt_ :: Tt ?> a => a -> Tt > a Source #

tt_A :: Tt ?> a => [(String, String)] -> a -> Tt :> a Source #

u_ :: U ?> a => a -> U > a Source #

u_A :: U ?> a => [(String, String)] -> a -> U :> a Source #

ul_ :: Ul ?> a => a -> Ul > a Source #

ul_A :: Ul ?> a => [(String, String)] -> a -> Ul :> a Source #

var_ :: Var ?> a => a -> Var > a Source #

var_A :: Var ?> a => [(String, String)] -> a -> Var :> a Source #

video_ :: Video ?> a => a -> Video > a Source #

video_A :: Video ?> a => [(String, String)] -> a -> Video :> a Source #

wbr_ :: Wbr > () Source #

wbr_A :: [(String, String)] -> Wbr :> () Source #

xmp_ :: Xmp ?> a => a -> Xmp > a Source #

xmp_A :: Xmp ?> a => [(String, String)] -> a -> Xmp :> a Source #