516 lines
20 KiB
Text
516 lines
20 KiB
Text
-- | The `Bulma` module is a wrapper around the BULMA css framework.
|
|
module Bulma where
|
|
import Prelude (class Show, map, show, ($), (<>), (==))
|
|
|
|
import Data.Maybe (Maybe, fromMaybe)
|
|
import Data.Tuple (Tuple, fst, snd)
|
|
import Halogen.HTML as HH
|
|
import DOM.HTML.Indexed as DHI
|
|
import Halogen.HTML.Properties as HP
|
|
import Halogen.HTML.Events as HE
|
|
|
|
import DOM.HTML.Indexed.AutocompleteType (AutocompleteType(..))
|
|
import CSSClasses as C
|
|
|
|
import Halogen.HTML.Core (AttrName(..))
|
|
-- import Web.Event.Event (type_, Event, EventType(..))
|
|
-- import Web.UIEvent.MouseEvent (MouseEvent) -- package web-uievents
|
|
|
|
checkbox :: forall w i. Array (HH.HTML w i) -> i -> HH.HTML w i
|
|
checkbox content_ action
|
|
= HH.label
|
|
[ HP.classes [C.label] ] $ [ HH.input [ HE.onValueInput \ _ -> action, HP.type_ HP.InputCheckbox ] ] <> content_
|
|
-- <label class="checkbox">
|
|
-- <input type="checkbox" />
|
|
-- I agree to the <a href="#">terms and conditions</a>
|
|
-- </label>
|
|
|
|
outside_link :: forall w i. Array HH.ClassName -> String -> String -> HH.HTML w i
|
|
outside_link classes url title = HH.a [ HP.classes classes, HP.target "_blank", HP.href url ] [ HH.text title ]
|
|
|
|
columns :: forall (w :: Type) (i :: Type).
|
|
Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
columns classes = HH.div [ HP.classes ([C.columns] <> classes) ]
|
|
|
|
columns_ :: forall (w :: Type) (i :: Type). Array (HH.HTML w i) -> HH.HTML w i
|
|
columns_ = columns []
|
|
|
|
column :: forall (w :: Type) (i :: Type).
|
|
Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
column classes = HH.div [ HP.classes ([C.column] <> classes) ]
|
|
|
|
column_ :: forall (w :: Type) (i :: Type). Array (HH.HTML w i) -> HH.HTML w i
|
|
column_ = column []
|
|
|
|
h1 :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
|
|
h1 title = HH.h1 [ HP.classes [C.title] ] [ HH.text title ]
|
|
|
|
h3 :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
|
|
h3 title = HH.h3 [ HP.classes [C.title] ] [ HH.text title ]
|
|
|
|
h4 :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
|
|
h4 title = HH.h4 [ HP.classes [C.title] ] [ HH.text title ]
|
|
|
|
zone_rr_title :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
|
|
zone_rr_title title
|
|
= HH.h3 [ HP.classes [C.title, C.has_text_light, C.has_background_dark] ]
|
|
[ HH.text title ]
|
|
|
|
subtitle :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
|
|
subtitle title = HH.h2 [ HP.classes [C.subtitle, C.is4] ] [ HH.text title ]
|
|
|
|
hdiv :: forall (w :: Type) (a :: Type). Array (HH.HTML w a) -> HH.HTML w a
|
|
hdiv = HH.div [ HP.classes [HH.ClassName "mt-5"] ]
|
|
|
|
--offcolumn :: forall (w :: Type) (a :: Type).
|
|
-- Int -> Int -> Array (HH.HTML w a) -> HH.HTML w a
|
|
--offcolumn 0 size = HH.div [ HP.classes [HH.ClassName ("mt-"<>show size)] ]
|
|
--offcolumn offset size
|
|
-- = column [ HH.ClassName ("is-offset-" <> (show offset) <> " is-" <> (show size)) ]
|
|
|
|
input_classes :: Array HH.ClassName
|
|
input_classes = [C.input, C.is_small, C.is_info]
|
|
|
|
table :: forall w i. HH.Node DHI.HTMLtable w i
|
|
table prop xs = HH.table ([ HP.classes [C.table] ] <> prop) xs
|
|
|
|
table_ :: forall w i. Array HH.ClassName -> HH.Node DHI.HTMLtable w i
|
|
table_ classes prop xs = HH.table ([ HP.classes $ [C.table] <> classes] <> prop) xs
|
|
|
|
textarea_ :: forall w i. Array HH.ClassName -> String -> String -> (String -> i) -> HH.HTML w i
|
|
textarea_ classes placeholder value action
|
|
= HH.textarea
|
|
[ HE.onValueInput action
|
|
, HP.value value
|
|
, HP.placeholder placeholder
|
|
, HP.classes $ [C.textarea] <> classes
|
|
]
|
|
|
|
textarea :: forall w i. String -> String -> (String -> i) -> HH.HTML w i
|
|
textarea placeholder value action = textarea_ [] placeholder value action
|
|
|
|
-- | Create a `level`, different components that should appear on the same horizontal line.
|
|
-- | First argument, elements that should appear on the left, second on the right.
|
|
level :: forall w i. Array (HH.HTML w i) -> Array (HH.HTML w i) -> HH.HTML w i
|
|
level left right = HH.nav [ HP.classes [C.level] ]
|
|
[ HH.div [ HP.classes [C.level_left] ] $ itemize left
|
|
, HH.div [ HP.classes [C.level_right] ] $ itemize right
|
|
]
|
|
where itemize = map (\v -> HH.div [ HP.classes [C.level_item] ] [v])
|
|
|
|
-- | Bulma's `field`, which contains an array of `Halogen.HTML` entries.
|
|
-- | Two entries are expected: a field label (`div_field_label`) and a field content (`div_field_content`).
|
|
div_field :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
div_field classes = HH.div [HP.classes ([C.field, C.is_horizontal] <> classes)]
|
|
|
|
-- | Field label (id and title) for a Bulma `field`.
|
|
div_field_label :: forall w i. String -> String -> HH.HTML w i
|
|
div_field_label id title = HH.div [HP.classes [C.field_label, C.normal]]
|
|
[HH.label [ HP.classes [C.label], HP.for id ] [ HH.text title ]]
|
|
|
|
-- | Any `Halogen.HTML` data in Bulma `field-body > field > control` divs.
|
|
div_field_content :: forall w i. HH.HTML w i -> HH.HTML w i
|
|
div_field_content content
|
|
= HH.div [ HP.classes [C.field_body] ]
|
|
[ HH.div [HP.classes [C.field] ] [ HH.div [HP.classes [C.control] ] [ content ] ] ]
|
|
|
|
-- | Basic field entry with a title and a field content.
|
|
-- |
|
|
-- |```
|
|
-- |div [field is-horizontal]
|
|
-- | div [field-label is-normal]
|
|
-- | label [for-id]
|
|
-- | text
|
|
-- | div [field-body]
|
|
-- | div [field]
|
|
-- | div [control]
|
|
-- |```
|
|
field_entry :: forall w i. String -> String -> HH.HTML w i -> HH.HTML w i
|
|
field_entry id title entry
|
|
= div_field []
|
|
[ div_field_label id title
|
|
, div_field_content entry
|
|
]
|
|
|
|
-- | Error field entry with a title and a field content.
|
|
error_field_entry :: forall w i. String -> String -> HH.HTML w i -> HH.HTML w i
|
|
error_field_entry id title entry
|
|
= div_field [C.has_background_danger_light]
|
|
[ div_field_label id title
|
|
, div_field_content entry
|
|
]
|
|
|
|
error_box :: forall w i. String -> String -> String -> HH.HTML w i
|
|
error_box id title value = error_field_entry id title $ notification_danger' value
|
|
|
|
field_inner :: forall w i.
|
|
Boolean -> (HP.IProp DHI.HTMLinput i) -> String -> String -> String -> (String -> i) -> String -> HH.HTML w i
|
|
field_inner ispassword cond id title placeholder action value
|
|
= field_entry id title $ render_input ispassword id placeholder action value cond
|
|
|
|
div_field_ :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
div_field_ classes = HH.div [ HP.classes ([C.field] <> classes) ]
|
|
|
|
btn_labeled :: forall w i. String -> String -> String -> i -> HH.HTML w i
|
|
btn_labeled id title button_text action
|
|
= field_entry id title $ HH.button
|
|
[ HE.onClick \_ -> action
|
|
, HP.classes [C.button, C.is_small, C.is_info]
|
|
, HP.id id
|
|
] [ HH.text button_text ]
|
|
|
|
box_input_ :: forall w i.
|
|
(HP.IProp DHI.HTMLinput i) -> String -> String -> String -> (String -> i) -> String -> HH.HTML w i
|
|
box_input_ = field_inner false
|
|
|
|
box_password_ :: forall w i.
|
|
(HP.IProp DHI.HTMLinput i) -> String -> String -> String -> (String -> i) -> String -> HH.HTML w i
|
|
box_password_ = field_inner true
|
|
|
|
box_input :: forall w i. String -> String -> String -> (String -> i) -> String -> HH.HTML w i
|
|
box_input = box_input_ (HP.enabled true)
|
|
|
|
box_password :: forall w i. String -> String -> String -> (String -> i) -> String -> HH.HTML w i
|
|
box_password = box_password_ (HP.enabled true)
|
|
|
|
section_small :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
section_small = HH.section [ HP.classes [C.section, C.is_small] ]
|
|
|
|
section_medium :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
section_medium = HH.section [ HP.classes [C.section, C.medium] ]
|
|
|
|
new_domain_field :: forall w i.
|
|
(String -> i) -> String -> Array (HP.IProp DHI.HTMLselect i) -> Array String -> HH.HTML w i
|
|
new_domain_field inputaction text_ selectaction accepted_domains
|
|
= div_field_ [C.has_addons]
|
|
[ HH.p
|
|
[ HP.classes [C.control] ]
|
|
[ HH.input $
|
|
[ HE.onValueInput inputaction
|
|
, HP.placeholder "www"
|
|
, HP.value text_
|
|
, HP.type_ HP.InputText
|
|
, HP.classes [C.is_primary, C.input]
|
|
]
|
|
]
|
|
, HH.p
|
|
[ HP.classes [C.control] ]
|
|
[ select selectaction $ map option accepted_domains ]
|
|
]
|
|
|
|
box :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
box = HH.div [HP.classes [C.box]]
|
|
|
|
box_ :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
box_ classes = HH.div [HP.classes $ [C.box] <> classes]
|
|
|
|
select :: forall w i. HH.Node DHI.HTMLselect w i
|
|
select action options
|
|
= HH.div [ HP.classes [C.select, C.is_primary] ]
|
|
[ HH.select action options]
|
|
|
|
hero :: forall w i. String -> String -> HH.HTML w i
|
|
hero _title _subtitle
|
|
= HH.section [ HP.classes [C.hero, C.is_info, C.is_small] ]
|
|
[ HH.div [ HP.classes [C.hero_body] ]
|
|
[ HH.p [ HP.classes [C.title] ] [ HH.text _title ]
|
|
, HH.p [ HP.classes [C.subtitle] ] [ HH.text _subtitle ]
|
|
]
|
|
]
|
|
|
|
small_hero :: forall w i. String -> String -> HH.HTML w i
|
|
small_hero _title _subtitle =
|
|
HH.section [ HP.classes [C.hero, C.is_info, C.is_small] ]
|
|
[ HH.div [ HP.classes [C.hero_body] ]
|
|
[ HH.div [ HP.classes [C.container, C.has_text_centered] ]
|
|
[ HH.p [ HP.classes [C.title] ] [ HH.text _title ]
|
|
, HH.p [ HP.classes [C.subtitle] ] [ HH.text _subtitle ]
|
|
]
|
|
]
|
|
]
|
|
|
|
hero_danger_txt :: forall w i. String -> String -> HH.HTML w i
|
|
hero_danger_txt _title _subtitle
|
|
= hero_danger [ HH.text _title ] [ HH.text _subtitle ]
|
|
|
|
hero_danger :: forall w i. Array (HH.HTML w i) -> Array (HH.HTML w i) -> HH.HTML w i
|
|
hero_danger _title _subtitle
|
|
= HH.section [ HP.classes [C.hero, C.is_danger, C.is_small] ]
|
|
[ HH.div [ HP.classes [C.hero_body] ]
|
|
[ HH.p [ HP.classes [C.title] ] _title
|
|
, HH.p [ HP.classes [C.subtitle] ] _subtitle
|
|
]
|
|
]
|
|
|
|
header :: forall w i. String -> String -> HH.HTML w i
|
|
header = hero
|
|
|
|
container :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
container = HH.div [HP.classes [C.container, C.is_info]]
|
|
|
|
data_target :: forall r i. String -> HP.IProp r i
|
|
data_target = HP.attr (AttrName "data-target")
|
|
|
|
modal_ :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
modal_ = HH.div [HP.classes [C.modal, C.is_active]]
|
|
modal_background :: forall w i. HH.HTML w i
|
|
modal_background = HH.div [HP.classes [C.modal_background]] []
|
|
modal_card_large :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
modal_card_large = HH.div [HP.classes [C.modal_card, C.is_large]]
|
|
modal_header :: forall w i. String -> HH.HTML w i
|
|
modal_header title = HH.header [HP.classes [C.modal_card_head]]
|
|
[ HH.p [HP.classes [C.modal_card_title]] [HH.text title]
|
|
]
|
|
modal_body :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
modal_body = HH.section [HP.classes [C.modal_card_body]]
|
|
modal_foot :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
modal_foot = HH.div [HP.classes [C.modal_card_foot]]
|
|
|
|
cancel_button :: forall w i. i -> HH.HTML w i
|
|
cancel_button action
|
|
= HH.button [ HP.classes [C.button]
|
|
, HE.onClick \_ -> action
|
|
] [HH.text "Cancel"]
|
|
|
|
tile :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
tile classes = HH.div [HP.classes ([C.tile] <> classes)]
|
|
|
|
tile_ :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
tile_ = tile []
|
|
|
|
tile_danger :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
tile_danger classes = tile $ [C.is_danger, C.notification] <> classes
|
|
|
|
tile_warning :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
tile_warning classes = tile $ [C.is_warning, C.notification] <> classes
|
|
|
|
article_ :: forall w i. Array HH.ClassName -> HH.HTML w i -> HH.HTML w i -> HH.HTML w i
|
|
article_ classes head body = HH.article [HP.classes $ [C.message] <> classes]
|
|
[ HH.div [HP.classes [C.message_header]] [head]
|
|
, HH.div [HP.classes [C.message_body] ] [body]
|
|
]
|
|
|
|
article :: forall w i. HH.HTML w i -> HH.HTML w i -> HH.HTML w i
|
|
article head body = article_ [] head body
|
|
|
|
error_message :: forall w i. HH.HTML w i -> HH.HTML w i -> HH.HTML w i
|
|
error_message head body = article_ [C.is_danger] head body
|
|
|
|
|
|
-- | Basic input field with a read-only side text.
|
|
-- |
|
|
-- |```
|
|
-- |div [field is-horizontal]
|
|
-- | div [field-label normal]
|
|
-- | label [label for-id]
|
|
-- | text
|
|
-- | div [field-body]
|
|
-- | div [has-addons field]
|
|
-- | p [control]
|
|
-- | input
|
|
-- | p [control]
|
|
-- | a [button is-small is-static]
|
|
-- | text
|
|
-- |```
|
|
input_with_side_text :: forall w i.
|
|
String -> String -> String -> (String -> i) -> String -> String -> HH.HTML w i
|
|
input_with_side_text id title placeholder action value sidetext
|
|
= HH.div [HP.classes [C.field, C.is_horizontal]]
|
|
[ HH.div [ HP.classes [C.field_label, C.normal] ]
|
|
[HH.label [ HP.classes [C.label], HP.for id ] [ HH.text title ]]
|
|
, HH.div [ HP.classes [C.field_body] ]
|
|
[ HH.div [ HP.classes [C.has_addons, C.field] ]
|
|
[ HH.p [HP.classes [C.control]]
|
|
[ HH.input $
|
|
[ HE.onValueInput action
|
|
, HP.value value
|
|
, HP.placeholder placeholder
|
|
, HP.classes $ input_classes
|
|
, HP.id id
|
|
]
|
|
]
|
|
, HH.p [HP.classes [C.control]]
|
|
[ HH.a [HP.classes [C.button, C.is_small, C.is_static]]
|
|
[HH.text sidetext] ]
|
|
]
|
|
]
|
|
]
|
|
|
|
side_text_above_input :: forall w i.
|
|
String -> String -> HH.HTML w i -> HH.HTML w i
|
|
side_text_above_input id title sidetext
|
|
= HH.div [HP.classes [C.field, C.is_horizontal]]
|
|
[ HH.div [ HP.classes [C.field_label, C.normal] ]
|
|
[HH.label [ HP.classes [C.label], HP.for id ] [ HH.text title ]]
|
|
, HH.div [ HP.classes [C.field_body] ]
|
|
[ HH.div [ HP.classes [C.has_addons, C.field] ]
|
|
[ HH.p [HP.classes [C.control]] [ sidetext ] ]
|
|
]
|
|
]
|
|
|
|
-- | `modal`: create a modal by providing a few things:
|
|
-- | - a title (a simple String)
|
|
-- | - a body (`HTML` content)
|
|
-- | - a footer (`HTML` content)
|
|
modal :: forall w i. String -> Array (HH.HTML w i) -> Array (HH.HTML w i) -> HH.HTML w i
|
|
modal title body foot =
|
|
modal_
|
|
[ modal_background
|
|
, modal_card_large [modal_header title, modal_body body]
|
|
, modal_foot foot
|
|
]
|
|
|
|
-- selection: create a "select" input.
|
|
-- Get the changes with "onSelectedIndexChange" which provides an index.
|
|
selection :: forall w i. (Int -> i) -> Array String -> String -> HH.HTML w i
|
|
selection action values selected = HH.div [HP.classes [C.select, C.is_normal]]
|
|
[ HH.select [ HE.onSelectedIndexChange action ]
|
|
$ map (\n -> HH.option [HP.value n, HP.selected (n == selected)] [HH.text n]) values
|
|
]
|
|
|
|
selection_field :: forall w i. String -> String -> (Int -> i) -> Array String -> String -> HH.HTML w i
|
|
selection_field id title action values selected
|
|
= field_entry id title $ selection action values selected
|
|
|
|
selection_field' :: forall w i.
|
|
String -> String -> (Int -> i) -> Array (Tuple String String) -> String -> HH.HTML w i
|
|
selection_field' id title action values selected
|
|
= field_entry id title $ selection' action values selected
|
|
|
|
selection_field'' :: forall w i t. Show t =>
|
|
String -> String -> (Int -> i) -> Array (Tuple String String) -> t -> Maybe t -> HH.HTML w i
|
|
selection_field'' id title action values default_value selected
|
|
= field_entry id title $ selection' action values selected_value
|
|
where
|
|
selected_value = (show $ fromMaybe default_value selected)
|
|
|
|
-- | selection': as `selection` but takes an array of tuple as values.
|
|
-- | First value in the tuple is what to display, the second one is what to match on.
|
|
selection' :: forall w i. (Int -> i) -> Array (Tuple String String) -> String -> HH.HTML w i
|
|
selection' action values selected = HH.div [HP.classes [C.select, C.is_normal]]
|
|
[ HH.select [ HE.onSelectedIndexChange action ]
|
|
$ map (\n -> HH.option [HP.value (snd n), HP.selected ((snd n) == selected)] [HH.text (fst n)]) values
|
|
]
|
|
|
|
tag_light_info :: forall w i. String -> HH.HTML w i
|
|
tag_light_info str = HH.span [HP.classes [C.tag, C.is_info, C.is_light]] [HH.text str]
|
|
|
|
div_large_content :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
div_large_content content = HH.div [HP.classes [C.is_large, C.content]] content
|
|
|
|
div_content :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
div_content classes content = HH.div [HP.classes ([C.content] <> classes)] content
|
|
|
|
explanation :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
explanation content = HH.blockquote [HP.classes [HH.ClassName "justified"]] content
|
|
|
|
quote :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
quote content = div_content [] [ explanation content ]
|
|
|
|
simple_quote :: forall w i. String -> HH.HTML w i
|
|
simple_quote content = quote [ p content ]
|
|
|
|
tabs :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
tabs classes tab_list = HH.div [HP.classes $ [C.tabs] <> classes] [HH.ul_ tab_list]
|
|
|
|
fancy_tabs :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
fancy_tabs arr = tabs [C.is_medium, C.is_boxed, C.is_centered] arr
|
|
|
|
tab_entry :: forall w i. Boolean -> String -> i -> HH.HTML w i
|
|
tab_entry active name action =
|
|
HH.li (if active then [HP.classes [C.is_active]] else [])
|
|
[ HH.a [HE.onClick \_ -> action] [HH.text name] ]
|
|
|
|
delete_btn :: forall w i. i -> HH.HTML w i
|
|
delete_btn action = HH.button [HE.onClick \_ -> action, HP.classes [C.delete]] []
|
|
|
|
notification :: forall w i. Array HH.ClassName -> String -> i -> HH.HTML w i
|
|
notification classes value deleteaction =
|
|
HH.div [HP.classes $ [C.notification] <> classes]
|
|
[ delete_btn deleteaction
|
|
, HH.text value
|
|
]
|
|
|
|
notification_primary :: forall w i. String -> i -> HH.HTML w i
|
|
notification_primary value action = notification [C.is_primary] value action
|
|
|
|
notification_success :: forall w i. String -> i -> HH.HTML w i
|
|
notification_success value action = notification [C.is_success] value action
|
|
|
|
notification_warning :: forall w i. String -> i -> HH.HTML w i
|
|
notification_warning value action = notification [C.is_warning] value action
|
|
|
|
notification_danger :: forall w i. String -> i -> HH.HTML w i
|
|
notification_danger value action = notification [C.is_danger] value action
|
|
|
|
notification_block' :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
|
|
notification_block' classes content =
|
|
HH.div [HP.classes ([C.notification] <> classes)] content
|
|
|
|
notification' :: forall w i. Array HH.ClassName -> String -> HH.HTML w i
|
|
notification' classes value =
|
|
HH.div [HP.classes ([C.notification] <> classes)]
|
|
[ HH.text value ]
|
|
|
|
notification_primary' :: forall w i. String -> HH.HTML w i
|
|
notification_primary' value = notification' [C.is_primary] value
|
|
|
|
notification_warning' :: forall w i. String -> HH.HTML w i
|
|
notification_warning' value = notification' [C.is_warning] value
|
|
|
|
notification_danger' :: forall w i. String -> HH.HTML w i
|
|
notification_danger' value = notification' [C.is_danger] value
|
|
|
|
notification_danger_block' :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
|
notification_danger_block' content = notification_block' [C.is_danger] content
|
|
|
|
-- | Box with tags.
|
|
-- |```
|
|
-- |box_with_tag [C.has_background_danger_light] some_tag [Bulma.p "Hello"]
|
|
-- |```
|
|
box_with_tag :: forall w action.
|
|
Array HH.ClassName -- css classes (like the color)
|
|
-> HH.HTML w action -- tag (title for the box)
|
|
-> Array (HH.HTML w action) -- box content
|
|
-> HH.HTML w action
|
|
box_with_tag colors tag xs
|
|
= box_
|
|
([C.no_padding_left, C.no_padding_top] <> colors)
|
|
[tag, HH.div [HP.classes [C.restore_padding_left, C.restore_padding_top]] xs]
|
|
|
|
-- GENERIC HTML API
|
|
|
|
render_input :: forall w i.
|
|
Boolean -> String -> String -> (String -> i) -> String -> (HP.IProp DHI.HTMLinput i) -> HH.HTML w i
|
|
render_input password id placeholder action value cond
|
|
= HH.input $
|
|
[ HE.onValueInput action
|
|
, HP.value value
|
|
, HP.placeholder placeholder
|
|
, HP.classes $ input_classes
|
|
, HP.id id
|
|
, cond
|
|
] <> case password of
|
|
false -> []
|
|
true -> [ HP.type_ HP.InputPassword ]
|
|
|
|
code :: forall w i. String -> HH.HTML w i
|
|
code str = HH.code_ [ HH.text str ]
|
|
|
|
text :: forall w i. String -> HH.HTML w i
|
|
text = HH.text
|
|
|
|
p :: forall w i. String -> HH.HTML w i
|
|
p str = HH.p_ [ HH.text str ]
|
|
|
|
p_ :: forall w i. Array HH.ClassName -> String -> HH.HTML w i
|
|
p_ classes str = HH.p [HP.classes classes] [ HH.text str ]
|
|
|
|
option :: forall w i. String -> HH.HTML w i
|
|
option value = HH.option_ [HH.text value]
|
|
|
|
strong :: forall w i. String -> HH.HTML w i
|
|
strong str = HH.strong_ [ HH.text str ]
|
|
|
|
hr :: forall w i. HH.HTML w i
|
|
hr = HH.hr_
|