Safe Haskell | None |
---|---|
Language | Haskell2010 |
- renderString :: Document a => a -> String
- renderText :: Document a => a -> Text
- renderByteString :: Document a => a -> ByteString
- renderBuilder :: Document a => a -> Builder
- data (a :: Element) > b where
- data ((a :: Element) :@: b) c where
- WithAttributes :: (a ??> b, a ?> c) => b -> c -> (a :@: b) c
- data a # b = (:#:) a b
- (#) :: a -> b -> a # b
- type family (a :: Element) ?> b :: Constraint where ...
- type family (a :: Element) ??> b :: Constraint where ...
- newtype (a :: Attribute) := b = AT b
- newtype Raw a = Raw a
- class Convert a where
- data Converted
- data Attribute
- = AcceptA
- | AcceptCharsetA
- | AccesskeyA
- | ActionA
- | AlignA
- | AltA
- | AsyncA
- | AutocompleteA
- | AutofocusA
- | AutoplayA
- | AutosaveA
- | BgcolorA
- | BorderA
- | BufferedA
- | ChallengeA
- | CharsetA
- | CheckedA
- | CiteA
- | ClassA
- | CodeA
- | CodebaseA
- | ColorA
- | ColsA
- | ColspanA
- | ContentA
- | ContenteditableA
- | ContextmenuA
- | ControlsA
- | CoordsA
- | CrossoriginA
- | DataA
- | DatetimeA
- | DefaultA
- | DeferA
- | DirA
- | DirnameA
- | DisabledA
- | DownloadA
- | DraggableA
- | DropzoneA
- | EnctypeA
- | ForA
- | FormA
- | FormactionA
- | HeadersA
- | HeightA
- | HiddenA
- | HighA
- | HrefA
- | HreflangA
- | HttpEquivA
- | IconA
- | IdA
- | IntegrityA
- | IsmapA
- | ItempropA
- | KeytypeA
- | KindA
- | LabelA
- | LangA
- | LanguageA
- | ListA
- | LoopA
- | LowA
- | ManifestA
- | MaxA
- | MaxlengthA
- | MinlengthA
- | MediaA
- | MethodA
- | MinA
- | MultipleA
- | MutedA
- | NameA
- | NovalidateA
- | OpenA
- | OptimumA
- | PatternA
- | PingA
- | PlaceholderA
- | PosterA
- | PreloadA
- | RadiogroupA
- | ReadonlyA
- | RelA
- | RequiredA
- | ReversedA
- | RowsA
- | RowspanA
- | SandboxA
- | ScopeA
- | ScopedA
- | SeamlessA
- | SelectedA
- | ShapeA
- | SizeA
- | SizesA
- | SlotA
- | SpanA
- | SpellcheckA
- | SrcA
- | SrcdocA
- | SrclangA
- | SrcsetA
- | StartA
- | StepA
- | StyleA
- | SummaryA
- | TabindexA
- | TargetA
- | TitleA
- | TypeA
- | UsemapA
- | ValueA
- | WidthA
- | WrapA
- data Element
- = DOCTYPE
- | A
- | Abbr
- | Acronym
- | Address
- | Applet
- | Area
- | Article
- | Aside
- | Audio
- | B
- | Base
- | Basefont
- | Bdi
- | Bdo
- | Bgsound
- | Big
- | Blink
- | Blockquote
- | Body
- | Br
- | Button
- | Canvas
- | Caption
- | Center
- | Cite
- | Code
- | Col
- | Colgroup
- | Command
- | Content
- | Data
- | Datalist
- | Dd
- | Del
- | Details
- | Dfn
- | Dialog
- | Dir
- | Div
- | Dl
- | Dt
- | Element
- | Em
- | Embed
- | Fieldset
- | Figcaption
- | Figure
- | Font
- | Footer
- | Form
- | Frame
- | Frameset
- | H1
- | H2
- | H3
- | H4
- | H5
- | H6
- | Head
- | Header
- | Hgroup
- | Hr
- | Html
- | I
- | Iframe
- | Image
- | Img
- | Input
- | Ins
- | Isindex
- | Kbd
- | Keygen
- | Label
- | Legend
- | Li
- | Link
- | Listing
- | Main
- | Map
- | Mark
- | Marquee
- | Math
- | Menu
- | Menuitem
- | Meta
- | Meter
- | Multicol
- | Nav
- | Nextid
- | Nobr
- | Noembed
- | Noframes
- | Noscript
- | Object
- | Ol
- | Optgroup
- | Option
- | Output
- | P
- | Param
- | Picture
- | Plaintext
- | Pre
- | Progress
- | Q
- | Rp
- | Rt
- | Rtc
- | Ruby
- | S
- | Samp
- | Script
- | Section
- | Select
- | Shadow
- | Slot
- | Small
- | Source
- | Spacer
- | Span
- | Strike
- | Strong
- | Style
- | Sub
- | Summary
- | Sup
- | Svg
- | Table
- | Tbody
- | Td
- | Template
- | Textarea
- | Tfoot
- | Th
- | Thead
- | Time
- | Title
- | Tr
- | Track
- | Tt
- | U
- | Ul
- | Var
- | Video
- | Wbr
- | Xmp
- doctype_ :: DOCTYPE > ()
- a_ :: A ?> a => a -> A > a
- a_A :: (A ??> a, A ?> b) => a -> b -> (A :@: a) b
- abbr_ :: Abbr ?> a => a -> Abbr > a
- abbr_A :: (Abbr ??> a, Abbr ?> b) => a -> b -> (Abbr :@: a) b
- acronym_ :: Acronym ?> a => a -> Acronym > a
- acronym_A :: (Acronym ??> a, Acronym ?> b) => a -> b -> (Acronym :@: a) b
- address_ :: Address ?> a => a -> Address > a
- address_A :: (Address ??> a, Address ?> b) => a -> b -> (Address :@: a) b
- applet_ :: Applet ?> a => a -> Applet > a
- applet_A :: (Applet ??> a, Applet ?> b) => a -> b -> (Applet :@: a) b
- area_ :: Area > ()
- area_A :: Area ??> a => a -> (Area :@: a) ()
- article_ :: Article ?> a => a -> Article > a
- article_A :: (Article ??> a, Article ?> b) => a -> b -> (Article :@: a) b
- aside_ :: Aside ?> a => a -> Aside > a
- aside_A :: (Aside ??> a, Aside ?> b) => a -> b -> (Aside :@: a) b
- audio_ :: Audio ?> a => a -> Audio > a
- audio_A :: (Audio ??> a, Audio ?> b) => a -> b -> (Audio :@: a) b
- b_ :: B ?> a => a -> B > a
- b_A :: (B ??> a, B ?> b) => a -> b -> (B :@: a) b
- base_ :: Base > ()
- base_A :: Base ??> a => a -> (Base :@: a) ()
- basefont_ :: Basefont ?> a => a -> Basefont > a
- basefont_A :: (Basefont ??> a, Basefont ?> b) => a -> b -> (Basefont :@: a) b
- bdi_ :: Bdi ?> a => a -> Bdi > a
- bdi_A :: (Bdi ??> a, Bdi ?> b) => a -> b -> (Bdi :@: a) b
- bdo_ :: Bdo ?> a => a -> Bdo > a
- bdo_A :: (Bdo ??> a, Bdo ?> b) => a -> b -> (Bdo :@: a) b
- bgsound_ :: Bgsound ?> a => a -> Bgsound > a
- bgsound_A :: (Bgsound ??> a, Bgsound ?> b) => a -> b -> (Bgsound :@: a) b
- big_ :: Big ?> a => a -> Big > a
- big_A :: (Big ??> a, Big ?> b) => a -> b -> (Big :@: a) b
- blink_ :: Blink ?> a => a -> Blink > a
- blink_A :: (Blink ??> a, Blink ?> b) => a -> b -> (Blink :@: a) b
- blockquote_ :: Blockquote ?> a => a -> Blockquote > a
- blockquote_A :: (Blockquote ??> a, Blockquote ?> b) => a -> b -> (Blockquote :@: a) b
- body_ :: Body ?> a => a -> Body > a
- body_A :: (Body ??> a, Body ?> b) => a -> b -> (Body :@: a) b
- br_ :: Br > ()
- br_A :: Br ??> a => a -> (Br :@: a) ()
- button_ :: Button ?> a => a -> Button > a
- button_A :: (Button ??> a, Button ?> b) => a -> b -> (Button :@: a) b
- canvas_ :: Canvas ?> a => a -> Canvas > a
- canvas_A :: (Canvas ??> a, Canvas ?> b) => a -> b -> (Canvas :@: a) b
- caption_ :: Caption ?> a => a -> Caption > a
- caption_A :: (Caption ??> a, Caption ?> b) => a -> b -> (Caption :@: a) b
- center_ :: Center ?> a => a -> Center > a
- center_A :: (Center ??> a, Center ?> b) => a -> b -> (Center :@: a) b
- cite_ :: Cite ?> a => a -> Cite > a
- cite_A :: (Cite ??> a, Cite ?> b) => a -> b -> (Cite :@: a) b
- code_ :: Code ?> a => a -> Code > a
- code_A :: (Code ??> a, Code ?> b) => a -> b -> (Code :@: a) b
- col_ :: Col > ()
- col_A :: Col ??> a => a -> (Col :@: a) ()
- colgroup_ :: Colgroup ?> a => a -> Colgroup > a
- colgroup_A :: (Colgroup ??> a, Colgroup ?> b) => a -> b -> (Colgroup :@: a) b
- command_ :: Command ?> a => a -> Command > a
- command_A :: (Command ??> a, Command ?> b) => a -> b -> (Command :@: a) b
- content_ :: Content ?> a => a -> Content > a
- content_A :: (Content ??> a, Content ?> b) => a -> b -> (Content :@: a) b
- data_ :: Data ?> a => a -> Data > a
- data_A :: (Data ??> a, Data ?> b) => a -> b -> (Data :@: a) b
- datalist_ :: Datalist ?> a => a -> Datalist > a
- datalist_A :: (Datalist ??> a, Datalist ?> b) => a -> b -> (Datalist :@: a) b
- dd_ :: Dd ?> a => a -> Dd > a
- dd_A :: (Dd ??> a, Dd ?> b) => a -> b -> (Dd :@: a) b
- del_ :: Del ?> a => a -> Del > a
- del_A :: (Del ??> a, Del ?> b) => a -> b -> (Del :@: a) b
- details_ :: Details ?> a => a -> Details > a
- details_A :: (Details ??> a, Details ?> b) => a -> b -> (Details :@: a) b
- dfn_ :: Dfn ?> a => a -> Dfn > a
- dfn_A :: (Dfn ??> a, Dfn ?> b) => a -> b -> (Dfn :@: a) b
- dialog_ :: Dialog ?> a => a -> Dialog > a
- dialog_A :: (Dialog ??> a, Dialog ?> b) => a -> b -> (Dialog :@: a) b
- dir_ :: Dir ?> a => a -> Dir > a
- dir_A :: (Dir ??> a, Dir ?> b) => a -> b -> (Dir :@: a) b
- div_ :: Div ?> a => a -> Div > a
- div_A :: (Div ??> a, Div ?> b) => a -> b -> (Div :@: a) b
- dl_ :: Dl ?> a => a -> Dl > a
- dl_A :: (Dl ??> a, Dl ?> b) => a -> b -> (Dl :@: a) b
- dt_ :: Dt ?> a => a -> Dt > a
- dt_A :: (Dt ??> a, Dt ?> b) => a -> b -> (Dt :@: a) b
- element_ :: Element ?> a => a -> Element > a
- element_A :: (Element ??> a, Element ?> b) => a -> b -> (Element :@: a) b
- em_ :: Em ?> a => a -> Em > a
- em_A :: (Em ??> a, Em ?> b) => a -> b -> (Em :@: a) b
- embed_ :: Embed > ()
- embed_A :: Embed ??> a => a -> (Embed :@: a) ()
- fieldset_ :: Fieldset ?> a => a -> Fieldset > a
- fieldset_A :: (Fieldset ??> a, Fieldset ?> b) => a -> b -> (Fieldset :@: a) b
- figcaption_ :: Figcaption ?> a => a -> Figcaption > a
- figcaption_A :: (Figcaption ??> a, Figcaption ?> b) => a -> b -> (Figcaption :@: a) b
- figure_ :: Figure ?> a => a -> Figure > a
- figure_A :: (Figure ??> a, Figure ?> b) => a -> b -> (Figure :@: a) b
- font_ :: Font ?> a => a -> Font > a
- font_A :: (Font ??> a, Font ?> b) => a -> b -> (Font :@: a) b
- footer_ :: Footer ?> a => a -> Footer > a
- footer_A :: (Footer ??> a, Footer ?> b) => a -> b -> (Footer :@: a) b
- form_ :: Form ?> a => a -> Form > a
- form_A :: (Form ??> a, Form ?> b) => a -> b -> (Form :@: a) b
- frame_ :: Frame ?> a => a -> Frame > a
- frame_A :: (Frame ??> a, Frame ?> b) => a -> b -> (Frame :@: a) b
- frameset_ :: Frameset ?> a => a -> Frameset > a
- frameset_A :: (Frameset ??> a, Frameset ?> b) => a -> b -> (Frameset :@: a) b
- h1_ :: H1 ?> a => a -> H1 > a
- h1_A :: (H1 ??> a, H1 ?> b) => a -> b -> (H1 :@: a) b
- h2_ :: H2 ?> a => a -> H2 > a
- h2_A :: (H2 ??> a, H2 ?> b) => a -> b -> (H2 :@: a) b
- h3_ :: H3 ?> a => a -> H3 > a
- h3_A :: (H3 ??> a, H3 ?> b) => a -> b -> (H3 :@: a) b
- h4_ :: H4 ?> a => a -> H4 > a
- h4_A :: (H4 ??> a, H4 ?> b) => a -> b -> (H4 :@: a) b
- h5_ :: H5 ?> a => a -> H5 > a
- h5_A :: (H5 ??> a, H5 ?> b) => a -> b -> (H5 :@: a) b
- h6_ :: H6 ?> a => a -> H6 > a
- h6_A :: (H6 ??> a, H6 ?> b) => a -> b -> (H6 :@: a) b
- head_ :: Head ?> a => a -> Head > a
- head_A :: (Head ??> a, Head ?> b) => a -> b -> (Head :@: a) b
- header_ :: Header ?> a => a -> Header > a
- header_A :: (Header ??> a, Header ?> b) => a -> b -> (Header :@: a) b
- hgroup_ :: Hgroup ?> a => a -> Hgroup > a
- hgroup_A :: (Hgroup ??> a, Hgroup ?> b) => a -> b -> (Hgroup :@: a) b
- hr_ :: Hr > ()
- hr_A :: Hr ??> a => a -> (Hr :@: a) ()
- html_ :: Html ?> a => a -> Html > a
- html_A :: (Html ??> a, Html ?> b) => a -> b -> (Html :@: a) b
- i_ :: I ?> a => a -> I > a
- i_A :: (I ??> a, I ?> b) => a -> b -> (I :@: a) b
- iframe_ :: Iframe > ()
- iframe_A :: Iframe ??> a => a -> (Iframe :@: a) ()
- image_ :: Image ?> a => a -> Image > a
- image_A :: (Image ??> a, Image ?> b) => a -> b -> (Image :@: a) b
- img_ :: Img > ()
- img_A :: Img ??> a => a -> (Img :@: a) ()
- input_ :: Input ?> a => a -> Input > a
- input_A :: (Input ??> a, Input ?> b) => a -> b -> (Input :@: a) b
- ins_ :: Ins ?> a => a -> Ins > a
- ins_A :: (Ins ??> a, Ins ?> b) => a -> b -> (Ins :@: a) b
- isindex_ :: Isindex ?> a => a -> Isindex > a
- isindex_A :: (Isindex ??> a, Isindex ?> b) => a -> b -> (Isindex :@: a) b
- kbd_ :: Kbd ?> a => a -> Kbd > a
- kbd_A :: (Kbd ??> a, Kbd ?> b) => a -> b -> (Kbd :@: a) b
- keygen_ :: Keygen ?> a => a -> Keygen > a
- keygen_A :: (Keygen ??> a, Keygen ?> b) => a -> b -> (Keygen :@: a) b
- label_ :: Label ?> a => a -> Label > a
- label_A :: (Label ??> a, Label ?> b) => a -> b -> (Label :@: a) b
- legend_ :: Legend ?> a => a -> Legend > a
- legend_A :: (Legend ??> a, Legend ?> b) => a -> b -> (Legend :@: a) b
- li_ :: Li ?> a => a -> Li > a
- li_A :: (Li ??> a, Li ?> b) => a -> b -> (Li :@: a) b
- link_ :: Link > ()
- link_A :: Link ??> a => a -> (Link :@: a) ()
- listing_ :: Listing ?> a => a -> Listing > a
- listing_A :: (Listing ??> a, Listing ?> b) => a -> b -> (Listing :@: a) b
- main_ :: Main ?> a => a -> Main > a
- main_A :: (Main ??> a, Main ?> b) => a -> b -> (Main :@: a) b
- map_ :: Map ?> a => a -> Map > a
- map_A :: (Map ??> a, Map ?> b) => a -> b -> (Map :@: a) b
- mark_ :: Mark ?> a => a -> Mark > a
- mark_A :: (Mark ??> a, Mark ?> b) => a -> b -> (Mark :@: a) b
- marquee_ :: Marquee ?> a => a -> Marquee > a
- marquee_A :: (Marquee ??> a, Marquee ?> b) => a -> b -> (Marquee :@: a) b
- math_ :: Math ?> a => a -> Math > a
- math_A :: (Math ??> a, Math ?> b) => a -> b -> (Math :@: a) b
- menu_ :: Menu ?> a => a -> Menu > a
- menu_A :: (Menu ??> a, Menu ?> b) => a -> b -> (Menu :@: a) b
- menuitem_ :: Menuitem > ()
- menuitem_A :: Menuitem ??> a => a -> (Menuitem :@: a) ()
- meta_ :: Meta > ()
- meta_A :: Meta ??> a => a -> (Meta :@: a) ()
- meter_ :: Meter ?> a => a -> Meter > a
- meter_A :: (Meter ??> a, Meter ?> b) => a -> b -> (Meter :@: a) b
- multicol_ :: Multicol ?> a => a -> Multicol > a
- multicol_A :: (Multicol ??> a, Multicol ?> b) => a -> b -> (Multicol :@: a) b
- nav_ :: Nav ?> a => a -> Nav > a
- nav_A :: (Nav ??> a, Nav ?> b) => a -> b -> (Nav :@: a) b
- nextid_ :: Nextid ?> a => a -> Nextid > a
- nextid_A :: (Nextid ??> a, Nextid ?> b) => a -> b -> (Nextid :@: a) b
- nobr_ :: Nobr ?> a => a -> Nobr > a
- nobr_A :: (Nobr ??> a, Nobr ?> b) => a -> b -> (Nobr :@: a) b
- noembed_ :: Noembed ?> a => a -> Noembed > a
- noembed_A :: (Noembed ??> a, Noembed ?> b) => a -> b -> (Noembed :@: a) b
- noframes_ :: Noframes ?> a => a -> Noframes > a
- noframes_A :: (Noframes ??> a, Noframes ?> b) => a -> b -> (Noframes :@: a) b
- noscript_ :: Noscript ?> a => a -> Noscript > a
- noscript_A :: (Noscript ??> a, Noscript ?> b) => a -> b -> (Noscript :@: a) b
- object_ :: Object ?> a => a -> Object > a
- object_A :: (Object ??> a, Object ?> b) => a -> b -> (Object :@: a) b
- ol_ :: Ol ?> a => a -> Ol > a
- ol_A :: (Ol ??> a, Ol ?> b) => a -> b -> (Ol :@: a) b
- optgroup_ :: Optgroup ?> a => a -> Optgroup > a
- optgroup_A :: (Optgroup ??> a, Optgroup ?> b) => a -> b -> (Optgroup :@: a) b
- option_ :: Option ?> a => a -> Option > a
- option_A :: (Option ??> a, Option ?> b) => a -> b -> (Option :@: a) b
- output_ :: Output ?> a => a -> Output > a
- output_A :: (Output ??> a, Output ?> b) => a -> b -> (Output :@: a) b
- p_ :: P ?> a => a -> P > a
- p_A :: (P ??> a, P ?> b) => a -> b -> (P :@: a) b
- param_ :: Param > ()
- param_A :: Param ??> a => a -> (Param :@: a) ()
- picture_ :: Picture ?> a => a -> Picture > a
- picture_A :: (Picture ??> a, Picture ?> b) => a -> b -> (Picture :@: a) b
- plaintext_ :: Plaintext ?> a => a -> Plaintext > a
- plaintext_A :: (Plaintext ??> a, Plaintext ?> b) => a -> b -> (Plaintext :@: a) b
- pre_ :: Pre ?> a => a -> Pre > a
- pre_A :: (Pre ??> a, Pre ?> b) => a -> b -> (Pre :@: a) b
- progress_ :: Progress ?> a => a -> Progress > a
- progress_A :: (Progress ??> a, Progress ?> b) => a -> b -> (Progress :@: a) b
- q_ :: Q ?> a => a -> Q > a
- q_A :: (Q ??> a, Q ?> b) => a -> b -> (Q :@: a) b
- rp_ :: Rp ?> a => a -> Rp > a
- rp_A :: (Rp ??> a, Rp ?> b) => a -> b -> (Rp :@: a) b
- rt_ :: Rt ?> a => a -> Rt > a
- rt_A :: (Rt ??> a, Rt ?> b) => a -> b -> (Rt :@: a) b
- rtc_ :: Rtc ?> a => a -> Rtc > a
- rtc_A :: (Rtc ??> a, Rtc ?> b) => a -> b -> (Rtc :@: a) b
- ruby_ :: Ruby ?> a => a -> Ruby > a
- ruby_A :: (Ruby ??> a, Ruby ?> b) => a -> b -> (Ruby :@: a) b
- s_ :: S ?> a => a -> S > a
- s_A :: (S ??> a, S ?> b) => a -> b -> (S :@: a) b
- samp_ :: Samp ?> a => a -> Samp > a
- samp_A :: (Samp ??> a, Samp ?> b) => a -> b -> (Samp :@: a) b
- script_ :: Script ?> a => a -> Script > a
- script_A :: (Script ??> a, Script ?> b) => a -> b -> (Script :@: a) b
- section_ :: Section ?> a => a -> Section > a
- section_A :: (Section ??> a, Section ?> b) => a -> b -> (Section :@: a) b
- select_ :: Select ?> a => a -> Select > a
- select_A :: (Select ??> a, Select ?> b) => a -> b -> (Select :@: a) b
- shadow_ :: Shadow ?> a => a -> Shadow > a
- shadow_A :: (Shadow ??> a, Shadow ?> b) => a -> b -> (Shadow :@: a) b
- slot_ :: Slot ?> a => a -> Slot > a
- slot_A :: (Slot ??> a, Slot ?> b) => a -> b -> (Slot :@: a) b
- small_ :: Small ?> a => a -> Small > a
- small_A :: (Small ??> a, Small ?> b) => a -> b -> (Small :@: a) b
- source_ :: Source > ()
- source_A :: Source ??> a => a -> (Source :@: a) ()
- spacer_ :: Spacer ?> a => a -> Spacer > a
- spacer_A :: (Spacer ??> a, Spacer ?> b) => a -> b -> (Spacer :@: a) b
- span_ :: Span ?> a => a -> Span > a
- span_A :: (Span ??> a, Span ?> b) => a -> b -> (Span :@: a) b
- strike_ :: Strike ?> a => a -> Strike > a
- strike_A :: (Strike ??> a, Strike ?> b) => a -> b -> (Strike :@: a) b
- strong_ :: Strong ?> a => a -> Strong > a
- strong_A :: (Strong ??> a, Strong ?> b) => a -> b -> (Strong :@: a) b
- style_ :: Style ?> a => a -> Style > a
- style_A :: (Style ??> a, Style ?> b) => a -> b -> (Style :@: a) b
- sub_ :: Sub ?> a => a -> Sub > a
- sub_A :: (Sub ??> a, Sub ?> b) => a -> b -> (Sub :@: a) b
- summary_ :: Summary ?> a => a -> Summary > a
- summary_A :: (Summary ??> a, Summary ?> b) => a -> b -> (Summary :@: a) b
- sup_ :: Sup ?> a => a -> Sup > a
- sup_A :: (Sup ??> a, Sup ?> b) => a -> b -> (Sup :@: a) b
- svg_ :: Svg ?> a => a -> Svg > a
- svg_A :: (Svg ??> a, Svg ?> b) => a -> b -> (Svg :@: a) b
- table_ :: Table ?> a => a -> Table > a
- table_A :: (Table ??> a, Table ?> b) => a -> b -> (Table :@: a) b
- tbody_ :: Tbody ?> a => a -> Tbody > a
- tbody_A :: (Tbody ??> a, Tbody ?> b) => a -> b -> (Tbody :@: a) b
- td_ :: Td ?> a => a -> Td > a
- td_A :: (Td ??> a, Td ?> b) => a -> b -> (Td :@: a) b
- template_ :: Template ?> a => a -> Template > a
- template_A :: (Template ??> a, Template ?> b) => a -> b -> (Template :@: a) b
- textarea_ :: Textarea ?> a => a -> Textarea > a
- textarea_A :: (Textarea ??> a, Textarea ?> b) => a -> b -> (Textarea :@: a) b
- tfoot_ :: Tfoot ?> a => a -> Tfoot > a
- tfoot_A :: (Tfoot ??> a, Tfoot ?> b) => a -> b -> (Tfoot :@: a) b
- th_ :: Th ?> a => a -> Th > a
- th_A :: (Th ??> a, Th ?> b) => a -> b -> (Th :@: a) b
- thead_ :: Thead ?> a => a -> Thead > a
- thead_A :: (Thead ??> a, Thead ?> b) => a -> b -> (Thead :@: a) b
- time_ :: Time ?> a => a -> Time > a
- time_A :: (Time ??> a, Time ?> b) => a -> b -> (Time :@: a) b
- title_ :: Title ?> a => a -> Title > a
- title_A :: (Title ??> a, Title ?> b) => a -> b -> (Title :@: a) b
- tr_ :: Tr ?> a => a -> Tr > a
- tr_A :: (Tr ??> a, Tr ?> b) => a -> b -> (Tr :@: a) b
- track_ :: Track > ()
- track_A :: Track ??> a => a -> (Track :@: a) ()
- tt_ :: Tt ?> a => a -> Tt > a
- tt_A :: (Tt ??> a, Tt ?> b) => a -> b -> (Tt :@: a) b
- u_ :: U ?> a => a -> U > a
- u_A :: (U ??> a, U ?> b) => a -> b -> (U :@: a) b
- ul_ :: Ul ?> a => a -> Ul > a
- ul_A :: (Ul ??> a, Ul ?> b) => a -> b -> (Ul :@: a) b
- var_ :: Var ?> a => a -> Var > a
- var_A :: (Var ??> a, Var ?> b) => a -> b -> (Var :@: a) b
- video_ :: Video ?> a => a -> Video > a
- video_A :: (Video ??> a, Video ?> b) => a -> b -> (Video :@: a) b
- wbr_ :: Wbr > ()
- wbr_A :: Wbr ??> a => a -> (Wbr :@: a) ()
- xmp_ :: Xmp ?> a => a -> Xmp > a
- xmp_A :: (Xmp ??> a, Xmp ?> b) => a -> b -> (Xmp :@: a) b
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 :: 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>
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>
WithAttributes :: (a ??> b, a ?> c) => b -> c -> (a :@: b) c |
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>
(:#:) a b |
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.
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 b |
type family (a :: Element) ??> b :: Constraint where ... Source #
Wrapper for types which won't be escaped.
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)
Convert Char Source # | |
Convert Double Source # | |
Convert Float Source # | |
Convert Int Source # | |
Convert Integer Source # | |
Convert Word Source # | |
Convert String Source # | |
Convert Text Source # | |
Convert Text Source # | |
Convert (Raw Char) Source # | |
Convert (Raw String) Source # | |
Convert (Raw Builder) Source # | |
Convert (Raw Text) Source # | |
Convert (Raw Text) Source # | |
KnownSymbol a => Convert (Proxy Symbol a) Source # | |
Convert b => Convert ((:=) a b) Source # | |
The data type of all html elements and the kind of elements.
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. |
blockquote_ :: Blockquote ?> a => a -> Blockquote > a Source #
blockquote_A :: (Blockquote ??> a, Blockquote ?> b) => a -> b -> (Blockquote :@: a) b Source #
figcaption_ :: Figcaption ?> a => a -> Figcaption > a Source #
figcaption_A :: (Figcaption ??> a, Figcaption ?> b) => a -> b -> (Figcaption :@: a) b Source #
Orphan instances
Document ((:@:) a b c) => Show [(:@:) a b c] Source # | |
Document ((>) a b) => Show [(>) a b] Source # | |
Document ((#) a b) => Show [(#) a b] Source # | |
Document ((>) a b) => Show ((>) a b) Source # | Orphan show instances to faciliate ghci development. |
Document ((#) a b) => Show ((#) a b) Source # | |
Document ((:@:) a b c) => Show ((:@:) a b c) Source # | |