{-# OPTIONS_GHC -Wno-missing-signatures #-}
-- | Predefined DOM elements, for convenience.
module Graphics.UI.Threepenny.Elements (
    -- * Combinations and utilities
    addStyleSheet,
    -- text,
    new,

    -- * Primitive HTML elements
    address, a, anchor, applet, area, audio,
    basefont, big, blockquote, body, bold, br, button,
    canvas, caption, center, cite, code,
    ddef, define, div, dlist,
    dterm, emphasize, fieldset, font, form, frame, frameset,
    h1, h2, h3, h4, h5, h6, header, hr,
    img, image, input, italics,
    keyboard, label, legend, li, link, map, meta, noframes, olist, option,
    p, paragraph, param, pre,
    sample, select, small, source, span, strong, sub, sup,
    table, td, textarea, th, thebase,
    thehtml, title_, tr, tt, ul,
    underline, variable, video,
    ) where

import           Control.Monad
import           Graphics.UI.Threepenny.Core
import           Prelude                     hiding (div, map, span)

{-----------------------------------------------------------------------------
    Combinations
------------------------------------------------------------------------------}
-- | Add a stylesheet to the head.
--
-- The second argument refers to the filename of the stylesheet,
-- but not its complete filepath.
-- Threepenny will prefix the 'css' subdirectory of the 'tpStatic' configuration field
-- to construct the complete filepath.
addStyleSheet
    :: Window
    -> FilePath
    -> UI ()
addStyleSheet :: Window -> FilePath -> UI ()
addStyleSheet Window
w FilePath
filename = UI Element -> UI ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (UI Element -> UI ()) -> UI Element -> UI ()
forall a b. (a -> b) -> a -> b
$ do
    Element
el <- FilePath -> UI Element
mkElement FilePath
"link"
            # set (attr "rel" ) "stylesheet"
            # set (attr "type") "text/css"
            # set (attr "href") ("/static/css/" ++ filename)
    Window -> UI Element
getHead Window
w UI Element -> [UI Element] -> UI Element
#+ [Element -> UI Element
forall (m :: * -> *) w. (MonadIO m, Widget w) => w -> m Element
element Element
el]

-- | Make a new @div@ element, synonym for 'div'.
new :: UI Element
new :: UI Element
new = UI Element
div

{-----------------------------------------------------------------------------
    Primitives

    Taken from the HTML library (BSD3 license)
    http://hackage.haskell.org/package/html
------------------------------------------------------------------------------}
tag :: FilePath -> UI Element
tag    = FilePath -> UI Element
mkElement
itag :: FilePath -> UI Element
itag   = FilePath -> UI Element
mkElement

address :: UI Element
address             =  FilePath -> UI Element
tag FilePath
"address"
a :: UI Element
a                   =  UI Element
anchor
anchor :: UI Element
anchor              =  FilePath -> UI Element
tag FilePath
"a"
applet :: UI Element
applet              =  FilePath -> UI Element
tag FilePath
"applet"
area :: UI Element
area                = FilePath -> UI Element
itag FilePath
"area"
audio :: UI Element
audio               =  FilePath -> UI Element
tag FilePath
"audio"
basefont :: UI Element
basefont            = FilePath -> UI Element
itag FilePath
"basefont"
big :: UI Element
big                 =  FilePath -> UI Element
tag FilePath
"big"
blockquote :: UI Element
blockquote          =  FilePath -> UI Element
tag FilePath
"blockquote"
body :: UI Element
body                =  FilePath -> UI Element
tag FilePath
"body"
bold :: UI Element
bold                =  FilePath -> UI Element
tag FilePath
"b"
br :: UI Element
br                  = FilePath -> UI Element
itag FilePath
"br"
button :: UI Element
button              =  FilePath -> UI Element
tag FilePath
"button"
canvas :: UI Element
canvas              =  FilePath -> UI Element
tag FilePath
"canvas"
caption :: UI Element
caption             =  FilePath -> UI Element
tag FilePath
"caption"
center :: UI Element
center              =  FilePath -> UI Element
tag FilePath
"center"
cite :: UI Element
cite                =  FilePath -> UI Element
tag FilePath
"cite"
code :: UI Element
code                =  FilePath -> UI Element
tag FilePath
"code"
ddef :: UI Element
ddef                =  FilePath -> UI Element
tag FilePath
"dd"
define :: UI Element
define              =  FilePath -> UI Element
tag FilePath
"dfn"
div :: UI Element
div                 =  FilePath -> UI Element
tag FilePath
"div"
dlist :: UI Element
dlist               =  FilePath -> UI Element
tag FilePath
"dl"
dterm :: UI Element
dterm               =  FilePath -> UI Element
tag FilePath
"dt"
emphasize :: UI Element
emphasize           =  FilePath -> UI Element
tag FilePath
"em"
fieldset :: UI Element
fieldset            =  FilePath -> UI Element
tag FilePath
"fieldset"
font :: UI Element
font                =  FilePath -> UI Element
tag FilePath
"font"
form :: UI Element
form                =  FilePath -> UI Element
tag FilePath
"form"
frame :: UI Element
frame               =  FilePath -> UI Element
tag FilePath
"frame"
frameset :: UI Element
frameset            =  FilePath -> UI Element
tag FilePath
"frameset"
h1 :: UI Element
h1                  =  FilePath -> UI Element
tag FilePath
"h1"
h2 :: UI Element
h2                  =  FilePath -> UI Element
tag FilePath
"h2"
h3 :: UI Element
h3                  =  FilePath -> UI Element
tag FilePath
"h3"
h4 :: UI Element
h4                  =  FilePath -> UI Element
tag FilePath
"h4"
h5 :: UI Element
h5                  =  FilePath -> UI Element
tag FilePath
"h5"
h6 :: UI Element
h6                  =  FilePath -> UI Element
tag FilePath
"h6"
header :: UI Element
header              =  FilePath -> UI Element
tag FilePath
"head"
hr :: UI Element
hr                  = FilePath -> UI Element
itag FilePath
"hr"
img :: UI Element
img                 = UI Element
image
image :: UI Element
image               = FilePath -> UI Element
itag FilePath
"img"
input :: UI Element
input               = FilePath -> UI Element
itag FilePath
"input"
italics :: UI Element
italics             =  FilePath -> UI Element
tag FilePath
"i"
keyboard :: UI Element
keyboard            =  FilePath -> UI Element
tag FilePath
"kbd"
label :: UI Element
label               =  FilePath -> UI Element
tag FilePath
"label"
legend :: UI Element
legend              =  FilePath -> UI Element
tag FilePath
"legend"
li :: UI Element
li                  =  FilePath -> UI Element
tag FilePath
"li"
link :: UI Element
link                =  FilePath -> UI Element
tag FilePath
"link"
map :: UI Element
map                 =  FilePath -> UI Element
tag FilePath
"map"
meta :: UI Element
meta                = FilePath -> UI Element
itag FilePath
"meta"
noframes :: UI Element
noframes            =  FilePath -> UI Element
tag FilePath
"noframes"
olist :: UI Element
olist               =  FilePath -> UI Element
tag FilePath
"ol"
option :: UI Element
option              =  FilePath -> UI Element
tag FilePath
"option"
p :: UI Element
p                   =  FilePath -> UI Element
tag FilePath
"p"
paragraph :: UI Element
paragraph           =  FilePath -> UI Element
tag FilePath
"p"
param :: UI Element
param               = FilePath -> UI Element
itag FilePath
"param"
pre :: UI Element
pre                 =  FilePath -> UI Element
tag FilePath
"pre"
sample :: UI Element
sample              =  FilePath -> UI Element
tag FilePath
"samp"
select :: UI Element
select              =  FilePath -> UI Element
tag FilePath
"select"
small :: UI Element
small               =  FilePath -> UI Element
tag FilePath
"small"
source :: UI Element
source              =  FilePath -> UI Element
tag FilePath
"source"
strong :: UI Element
strong              =  FilePath -> UI Element
tag FilePath
"strong"
sub :: UI Element
sub                 =  FilePath -> UI Element
tag FilePath
"sub"
sup :: UI Element
sup                 =  FilePath -> UI Element
tag FilePath
"sup"
table :: UI Element
table               =  FilePath -> UI Element
tag FilePath
"table"
td :: UI Element
td                  =  FilePath -> UI Element
tag FilePath
"td"
textarea :: UI Element
textarea            =  FilePath -> UI Element
tag FilePath
"textarea"
th :: UI Element
th                  =  FilePath -> UI Element
tag FilePath
"th"
thebase :: UI Element
thebase             = FilePath -> UI Element
itag FilePath
"base"
thehtml :: UI Element
thehtml             =  FilePath -> UI Element
tag FilePath
"html"
span :: UI Element
span                =  FilePath -> UI Element
tag FilePath
"span"
title_ :: UI Element
title_              =  FilePath -> UI Element
tag FilePath
"title"
tr :: UI Element
tr                  =  FilePath -> UI Element
tag FilePath
"tr"
tt :: UI Element
tt                  =  FilePath -> UI Element
tag FilePath
"tt"
ul :: UI Element
ul                  =  FilePath -> UI Element
tag FilePath
"ul"
underline :: UI Element
underline           =  FilePath -> UI Element
tag FilePath
"u"
variable :: UI Element
variable            =  FilePath -> UI Element
tag FilePath
"var"
video :: UI Element
video               =  FilePath -> UI Element
tag FilePath
"video"