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

Safe HaskellNone
LanguageHaskell2010

Html

Contents

Synopsis

Documentation

renderString :: Document a => a -> String Source #

Render a html document to a String.

renderText :: Document a => a -> Text Source #

Render a html document to a lazy Text.

renderByteString :: Document a => a -> ByteString Source #

Render a html document to a lazy ByteString.

renderBuilder :: forall a. Document a => a -> Builder Source #

Render a html document to a Builder.

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) c where infixr 8 Source #

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

>>> WithAttributes (A.class_ "bar") "a" :: 'Div :> String
<div class="bar">a</div>

Constructors

WithAttributes :: (a ??> b, a ?> c) => b -> c -> (a :@: b) c 

data a # b infixr 5 Source #

Combine two elements or attributes sequentially.

>>> i_ () # div_ ()
<i></i><div></div>
>>> i_A (A.id_ "a" # A.class_ "b") "c"
<i id="a" class="b">c</i>

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.

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) d)) = a ?> (b > d) 
a ?> (f (b # c)) = a ?> (b # c) 
a ?> () = () 
a ?> (b -> c) = TypeError (Text "Html elements can't contain functions") 
a ?> b = CheckString a 

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

Equations

a ??> (b # c) = (a ??> b, a ??> c) 
a ??> (b := _) = If (Elem a (GetAttributeInfo b) || Null (GetAttributeInfo b)) (() :: Constraint) (TypeError ((ShowType b :<>: Text " is not a valid attribute of ") :<>: ShowType a)) 
a ??> b = TypeError (ShowType b :<>: Text " is not an attribute.") 

newtype (a :: Attribute) := b Source #

Constructors

AT b 

Instances

Convert b => Convert ((:=) a b) Source # 

Methods

convert :: (a := b) -> Converted Source #

newtype Raw a Source #

Wrapper for types which won't be escaped.

Constructors

Raw a 

class Convert a where Source #

Convert a type efficienctly to different string like types. Add instances if you want use custom types in your document.

{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Html

import Data.Text (Text)
import Data.Monoid

data Person
  = Person
  { name :: Text
  , age :: Int
  , vegetarian :: Bool
  }

-- | This is already very efficient.
-- Wrap the Strings in Raw if you don't want to escape them.
instance Convert Person where
  convert (Person{..})
    =  convert name
    <> " is "
    <> convert age
    <> " years old and likes "
    <> if vegetarian then "oranges." else "meat."

john :: Person
john = Person {name = John, age = 52, vegetarian = True}

main :: IO ()
main = print (div_ john)

Minimal complete definition

convert

Methods

convert :: a -> Converted 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, A ?> b) => a -> b -> (A :@: a) b Source #

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

abbr_A :: (Abbr ??> a, Abbr ?> b) => a -> b -> (Abbr :@: a) b Source #

acronym_A :: (Acronym ??> a, Acronym ?> b) => a -> b -> (Acronym :@: a) b Source #

address_A :: (Address ??> a, Address ?> b) => a -> b -> (Address :@: a) b Source #

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

applet_A :: (Applet ??> a, Applet ?> b) => a -> b -> (Applet :@: a) b Source #

area_A :: Area ??> a => a -> (Area :@: a) () Source #

article_A :: (Article ??> a, Article ?> b) => a -> b -> (Article :@: a) b Source #

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

aside_A :: (Aside ??> a, Aside ?> b) => a -> b -> (Aside :@: a) b Source #

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

audio_A :: (Audio ??> a, Audio ?> b) => a -> b -> (Audio :@: a) b Source #

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

b_A :: (B ??> a, B ?> b) => a -> b -> (B :@: a) b Source #

base_A :: Base ??> a => a -> (Base :@: a) () Source #

basefont_A :: (Basefont ??> a, Basefont ?> b) => a -> b -> (Basefont :@: a) b Source #

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

bdi_A :: (Bdi ??> a, Bdi ?> b) => a -> b -> (Bdi :@: a) b Source #

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

bdo_A :: (Bdo ??> a, Bdo ?> b) => a -> b -> (Bdo :@: a) b Source #

bgsound_A :: (Bgsound ??> a, Bgsound ?> b) => a -> b -> (Bgsound :@: a) b Source #

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

big_A :: (Big ??> a, Big ?> b) => a -> b -> (Big :@: a) b Source #

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

blink_A :: (Blink ??> a, Blink ?> b) => a -> b -> (Blink :@: a) b Source #

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

body_A :: (Body ??> a, Body ?> b) => a -> b -> (Body :@: a) b Source #

br_ :: Br > () Source #

br_A :: Br ??> a => a -> (Br :@: a) () Source #

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

button_A :: (Button ??> a, Button ?> b) => a -> b -> (Button :@: a) b Source #

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

canvas_A :: (Canvas ??> a, Canvas ?> b) => a -> b -> (Canvas :@: a) b Source #

caption_A :: (Caption ??> a, Caption ?> b) => a -> b -> (Caption :@: a) b Source #

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

center_A :: (Center ??> a, Center ?> b) => a -> b -> (Center :@: a) b Source #

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

cite_A :: (Cite ??> a, Cite ?> b) => a -> b -> (Cite :@: a) b Source #

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

code_A :: (Code ??> a, Code ?> b) => a -> b -> (Code :@: a) b Source #

col_ :: Col > () Source #

col_A :: Col ??> a => a -> (Col :@: a) () Source #

colgroup_A :: (Colgroup ??> a, Colgroup ?> b) => a -> b -> (Colgroup :@: a) b Source #

command_A :: (Command ??> a, Command ?> b) => a -> b -> (Command :@: a) b Source #

content_A :: (Content ??> a, Content ?> b) => a -> b -> (Content :@: a) b Source #

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

data_A :: (Data ??> a, Data ?> b) => a -> b -> (Data :@: a) b Source #

datalist_A :: (Datalist ??> a, Datalist ?> b) => a -> b -> (Datalist :@: a) b Source #

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

dd_A :: (Dd ??> a, Dd ?> b) => a -> b -> (Dd :@: a) b Source #

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

del_A :: (Del ??> a, Del ?> b) => a -> b -> (Del :@: a) b Source #

details_A :: (Details ??> a, Details ?> b) => a -> b -> (Details :@: a) b Source #

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

dfn_A :: (Dfn ??> a, Dfn ?> b) => a -> b -> (Dfn :@: a) b Source #

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

dialog_A :: (Dialog ??> a, Dialog ?> b) => a -> b -> (Dialog :@: a) b Source #

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

dir_A :: (Dir ??> a, Dir ?> b) => a -> b -> (Dir :@: a) b Source #

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

div_A :: (Div ??> a, Div ?> b) => a -> b -> (Div :@: a) b Source #

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

dl_A :: (Dl ??> a, Dl ?> b) => a -> b -> (Dl :@: a) b Source #

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

dt_A :: (Dt ??> a, Dt ?> b) => a -> b -> (Dt :@: a) b Source #

element_A :: (Element ??> a, Element ?> b) => a -> b -> (Element :@: a) b Source #

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

em_A :: (Em ??> a, Em ?> b) => a -> b -> (Em :@: a) b Source #

embed_A :: Embed ??> a => a -> (Embed :@: a) () Source #

fieldset_A :: (Fieldset ??> a, Fieldset ?> b) => a -> b -> (Fieldset :@: a) b Source #

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

figure_A :: (Figure ??> a, Figure ?> b) => a -> b -> (Figure :@: a) b Source #

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

font_A :: (Font ??> a, Font ?> b) => a -> b -> (Font :@: a) b Source #

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

footer_A :: (Footer ??> a, Footer ?> b) => a -> b -> (Footer :@: a) b Source #

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

form_A :: (Form ??> a, Form ?> b) => a -> b -> (Form :@: a) b Source #

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

frame_A :: (Frame ??> a, Frame ?> b) => a -> b -> (Frame :@: a) b Source #

frameset_A :: (Frameset ??> a, Frameset ?> b) => a -> b -> (Frameset :@: a) b Source #

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

h1_A :: (H1 ??> a, H1 ?> b) => a -> b -> (H1 :@: a) b Source #

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

h2_A :: (H2 ??> a, H2 ?> b) => a -> b -> (H2 :@: a) b Source #

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

h3_A :: (H3 ??> a, H3 ?> b) => a -> b -> (H3 :@: a) b Source #

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

h4_A :: (H4 ??> a, H4 ?> b) => a -> b -> (H4 :@: a) b Source #

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

h5_A :: (H5 ??> a, H5 ?> b) => a -> b -> (H5 :@: a) b Source #

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

h6_A :: (H6 ??> a, H6 ?> b) => a -> b -> (H6 :@: a) b Source #

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

head_A :: (Head ??> a, Head ?> b) => a -> b -> (Head :@: a) b Source #

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

header_A :: (Header ??> a, Header ?> b) => a -> b -> (Header :@: a) b Source #

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

hgroup_A :: (Hgroup ??> a, Hgroup ?> b) => a -> b -> (Hgroup :@: a) b Source #

hr_ :: Hr > () Source #

hr_A :: Hr ??> a => a -> (Hr :@: a) () Source #

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

html_A :: (Html ??> a, Html ?> b) => a -> b -> (Html :@: a) b Source #

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

i_A :: (I ??> a, I ?> b) => a -> b -> (I :@: a) b Source #

iframe_A :: Iframe ??> a => a -> (Iframe :@: a) () Source #

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

image_A :: (Image ??> a, Image ?> b) => a -> b -> (Image :@: a) b Source #

img_ :: Img > () Source #

img_A :: Img ??> a => a -> (Img :@: a) () Source #

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

input_A :: (Input ??> a, Input ?> b) => a -> b -> (Input :@: a) b Source #

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

ins_A :: (Ins ??> a, Ins ?> b) => a -> b -> (Ins :@: a) b Source #

isindex_A :: (Isindex ??> a, Isindex ?> b) => a -> b -> (Isindex :@: a) b Source #

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

kbd_A :: (Kbd ??> a, Kbd ?> b) => a -> b -> (Kbd :@: a) b Source #

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

keygen_A :: (Keygen ??> a, Keygen ?> b) => a -> b -> (Keygen :@: a) b Source #

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

label_A :: (Label ??> a, Label ?> b) => a -> b -> (Label :@: a) b Source #

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

legend_A :: (Legend ??> a, Legend ?> b) => a -> b -> (Legend :@: a) b Source #

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

li_A :: (Li ??> a, Li ?> b) => a -> b -> (Li :@: a) b Source #

link_A :: Link ??> a => a -> (Link :@: a) () Source #

listing_A :: (Listing ??> a, Listing ?> b) => a -> b -> (Listing :@: a) b Source #

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

main_A :: (Main ??> a, Main ?> b) => a -> b -> (Main :@: a) b Source #

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

map_A :: (Map ??> a, Map ?> b) => a -> b -> (Map :@: a) b Source #

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

mark_A :: (Mark ??> a, Mark ?> b) => a -> b -> (Mark :@: a) b Source #

marquee_A :: (Marquee ??> a, Marquee ?> b) => a -> b -> (Marquee :@: a) b Source #

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

math_A :: (Math ??> a, Math ?> b) => a -> b -> (Math :@: a) b Source #

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

menu_A :: (Menu ??> a, Menu ?> b) => a -> b -> (Menu :@: a) b Source #

menuitem_A :: Menuitem ??> a => a -> (Menuitem :@: a) () Source #

meta_A :: Meta ??> a => a -> (Meta :@: a) () Source #

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

meter_A :: (Meter ??> a, Meter ?> b) => a -> b -> (Meter :@: a) b Source #

multicol_A :: (Multicol ??> a, Multicol ?> b) => a -> b -> (Multicol :@: a) b Source #

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

nav_A :: (Nav ??> a, Nav ?> b) => a -> b -> (Nav :@: a) b Source #

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

nextid_A :: (Nextid ??> a, Nextid ?> b) => a -> b -> (Nextid :@: a) b Source #

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

nobr_A :: (Nobr ??> a, Nobr ?> b) => a -> b -> (Nobr :@: a) b Source #

noembed_A :: (Noembed ??> a, Noembed ?> b) => a -> b -> (Noembed :@: a) b Source #

noframes_A :: (Noframes ??> a, Noframes ?> b) => a -> b -> (Noframes :@: a) b Source #

noscript_A :: (Noscript ??> a, Noscript ?> b) => a -> b -> (Noscript :@: a) b Source #

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

object_A :: (Object ??> a, Object ?> b) => a -> b -> (Object :@: a) b Source #

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

ol_A :: (Ol ??> a, Ol ?> b) => a -> b -> (Ol :@: a) b Source #

optgroup_A :: (Optgroup ??> a, Optgroup ?> b) => a -> b -> (Optgroup :@: a) b Source #

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

option_A :: (Option ??> a, Option ?> b) => a -> b -> (Option :@: a) b Source #

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

output_A :: (Output ??> a, Output ?> b) => a -> b -> (Output :@: a) b Source #

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

p_A :: (P ??> a, P ?> b) => a -> b -> (P :@: a) b Source #

param_A :: Param ??> a => a -> (Param :@: a) () Source #

picture_A :: (Picture ??> a, Picture ?> b) => a -> b -> (Picture :@: a) b Source #

plaintext_A :: (Plaintext ??> a, Plaintext ?> b) => a -> b -> (Plaintext :@: a) b Source #

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

pre_A :: (Pre ??> a, Pre ?> b) => a -> b -> (Pre :@: a) b Source #

progress_A :: (Progress ??> a, Progress ?> b) => a -> b -> (Progress :@: a) b Source #

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

q_A :: (Q ??> a, Q ?> b) => a -> b -> (Q :@: a) b Source #

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

rp_A :: (Rp ??> a, Rp ?> b) => a -> b -> (Rp :@: a) b Source #

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

rt_A :: (Rt ??> a, Rt ?> b) => a -> b -> (Rt :@: a) b Source #

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

rtc_A :: (Rtc ??> a, Rtc ?> b) => a -> b -> (Rtc :@: a) b Source #

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

ruby_A :: (Ruby ??> a, Ruby ?> b) => a -> b -> (Ruby :@: a) b Source #

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

s_A :: (S ??> a, S ?> b) => a -> b -> (S :@: a) b Source #

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

samp_A :: (Samp ??> a, Samp ?> b) => a -> b -> (Samp :@: a) b Source #

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

script_A :: (Script ??> a, Script ?> b) => a -> b -> (Script :@: a) b Source #

section_A :: (Section ??> a, Section ?> b) => a -> b -> (Section :@: a) b Source #

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

select_A :: (Select ??> a, Select ?> b) => a -> b -> (Select :@: a) b Source #

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

shadow_A :: (Shadow ??> a, Shadow ?> b) => a -> b -> (Shadow :@: a) b Source #

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

slot_A :: (Slot ??> a, Slot ?> b) => a -> b -> (Slot :@: a) b Source #

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

small_A :: (Small ??> a, Small ?> b) => a -> b -> (Small :@: a) b Source #

source_A :: Source ??> a => a -> (Source :@: a) () Source #

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

spacer_A :: (Spacer ??> a, Spacer ?> b) => a -> b -> (Spacer :@: a) b Source #

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

span_A :: (Span ??> a, Span ?> b) => a -> b -> (Span :@: a) b Source #

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

strike_A :: (Strike ??> a, Strike ?> b) => a -> b -> (Strike :@: a) b Source #

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

strong_A :: (Strong ??> a, Strong ?> b) => a -> b -> (Strong :@: a) b Source #

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

style_A :: (Style ??> a, Style ?> b) => a -> b -> (Style :@: a) b Source #

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

sub_A :: (Sub ??> a, Sub ?> b) => a -> b -> (Sub :@: a) b Source #

summary_A :: (Summary ??> a, Summary ?> b) => a -> b -> (Summary :@: a) b Source #

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

sup_A :: (Sup ??> a, Sup ?> b) => a -> b -> (Sup :@: a) b Source #

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

svg_A :: (Svg ??> a, Svg ?> b) => a -> b -> (Svg :@: a) b Source #

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

table_A :: (Table ??> a, Table ?> b) => a -> b -> (Table :@: a) b Source #

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

tbody_A :: (Tbody ??> a, Tbody ?> b) => a -> b -> (Tbody :@: a) b Source #

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

td_A :: (Td ??> a, Td ?> b) => a -> b -> (Td :@: a) b Source #

template_A :: (Template ??> a, Template ?> b) => a -> b -> (Template :@: a) b Source #

textarea_A :: (Textarea ??> a, Textarea ?> b) => a -> b -> (Textarea :@: a) b Source #

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

tfoot_A :: (Tfoot ??> a, Tfoot ?> b) => a -> b -> (Tfoot :@: a) b Source #

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

th_A :: (Th ??> a, Th ?> b) => a -> b -> (Th :@: a) b Source #

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

thead_A :: (Thead ??> a, Thead ?> b) => a -> b -> (Thead :@: a) b Source #

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

time_A :: (Time ??> a, Time ?> b) => a -> b -> (Time :@: a) b Source #

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

title_A :: (Title ??> a, Title ?> b) => a -> b -> (Title :@: a) b Source #

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

tr_A :: (Tr ??> a, Tr ?> b) => a -> b -> (Tr :@: a) b Source #

track_A :: Track ??> a => a -> (Track :@: a) () Source #

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

tt_A :: (Tt ??> a, Tt ?> b) => a -> b -> (Tt :@: a) b Source #

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

u_A :: (U ??> a, U ?> b) => a -> b -> (U :@: a) b Source #

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

ul_A :: (Ul ??> a, Ul ?> b) => a -> b -> (Ul :@: a) b Source #

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

var_A :: (Var ??> a, Var ?> b) => a -> b -> (Var :@: a) b Source #

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

video_A :: (Video ??> a, Video ?> b) => a -> b -> (Video :@: a) b Source #

wbr_ :: Wbr > () Source #

wbr_A :: Wbr ??> a => a -> (Wbr :@: a) () Source #

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

xmp_A :: (Xmp ??> a, Xmp ?> b) => a -> b -> (Xmp :@: a) b Source #

Orphan instances

Document ((:@:) a b c) => Show [(:@:) a b c] Source # 

Methods

showsPrec :: Int -> [(a :@: b) c] -> ShowS #

show :: [(a :@: b) c] -> String #

showList :: [[(a :@: b) c]] -> ShowS #

Document ((>) a b) => Show [(>) a b] Source # 

Methods

showsPrec :: Int -> [a > b] -> ShowS #

show :: [a > b] -> String #

showList :: [[a > b]] -> ShowS #

Document ((#) a b) => Show [(#) a b] Source # 

Methods

showsPrec :: Int -> [a # b] -> ShowS #

show :: [a # b] -> String #

showList :: [[a # b]] -> ShowS #

Document ((>) a b) => Show ((>) a b) Source #

Orphan show instances to faciliate ghci development.

Methods

showsPrec :: Int -> (a > b) -> ShowS #

show :: (a > b) -> String #

showList :: [a > b] -> ShowS #

Document ((#) a b) => Show ((#) a b) Source # 

Methods

showsPrec :: Int -> (a # b) -> ShowS #

show :: (a # b) -> String #

showList :: [a # b] -> ShowS #

Document ((:@:) a b c) => Show ((:@:) a b c) Source # 

Methods

showsPrec :: Int -> (a :@: b) c -> ShowS #

show :: (a :@: b) c -> String #

showList :: [(a :@: b) c] -> ShowS #