halogen-websocket-ipc-playzone/src/Bulma.purs

433 lines
15 KiB
Plaintext
Raw Normal View History

2023-06-08 21:51:12 +02:00
module Bulma where
{- This file is a wrapper around the BULMA css framework. -}
import Prelude
import Halogen.HTML as HH
2023-07-02 00:05:38 +02:00
import DOM.HTML.Indexed as DHI
2023-06-08 21:51:12 +02:00
import Halogen.HTML.Properties as HP
import Halogen.HTML.Events as HE
2023-07-08 01:50:11 +02:00
import CSSClasses as C
2023-07-08 00:22:23 +02:00
2023-06-08 21:51:12 +02:00
-- HTML PropName used with HP.prop
2023-07-08 00:22:23 +02:00
import Halogen.HTML.Core (AttrName(..))
2023-07-05 06:50:30 +02:00
--import Halogen.HTML.Core (PropName(..))
2023-06-08 21:51:12 +02:00
-- import Web.Event.Event (type_, Event, EventType(..))
2023-07-05 06:50:30 +02:00
--import Web.UIEvent.MouseEvent (MouseEvent)
2023-06-08 21:51:12 +02:00
columns :: forall (w :: Type) (i :: Type).
Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
2023-07-08 01:50:11 +02:00
columns classes = HH.div [ HP.classes (C.columns <> classes) ]
2023-06-08 21:51:12 +02:00
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
2023-07-08 01:50:11 +02:00
column classes = HH.div [ HP.classes (C.column <> classes) ]
2023-06-08 21:51:12 +02:00
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
2023-07-08 01:50:11 +02:00
h1 title = HH.h1 [ HP.classes (C.title) ] [ HH.text title ]
2023-06-08 21:51:12 +02:00
h3 :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
2023-07-09 14:26:47 +02:00
h3 title = HH.h3 [ HP.classes (C.title <> C.is5) ] [ 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.is5 <> C.has_text_light <> C.has_background_dark) ]
[ HH.text title ]
2023-06-08 21:51:12 +02:00
--subtitle :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
2023-07-08 01:50:11 +02:00
--subtitle title = HH.h2 [ HP.classes (C.subtitle <> C.is4) ] [ HH.text title ]
2023-06-08 21:51:12 +02:00
--
--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 :: forall (r :: Row Type) (i :: Type). Boolean -> HP.IProp ( class :: String | r ) i
input_classes true = HP.classes [ HH.ClassName "input is-small is-info" ]
input_classes false = HP.classes [ HH.ClassName "input is-small is-danger" ]
2023-06-08 22:00:53 +02:00
btn_classes :: forall (r :: Row Type) (i :: Type)
. Boolean -> HP.IProp ( class :: String | r ) i
btn_classes true = HP.classes [ HH.ClassName "button is-small is-info" ]
btn_classes false = HP.classes [ HH.ClassName "button is-small is-danger" ]
2023-06-08 21:51:12 +02:00
--simple_table_header :: forall w i. HH.HTML w i
--simple_table_header
-- = HH.thead_ [ HH.tr_ [ HH.th [ HP.style "width: 50px;" ] [ HH.text "Type" ]
-- , HH.th_ [ HH.text "Domain" ]
-- , HH.th_ [ HH.text "TTL" ]
-- , HH.th_ [ HH.text "Value" ]
-- ]
-- ]
--
--mx_table_header :: forall w i. HH.HTML w i
--mx_table_header
-- = HH.thead_ [ HH.tr_ [ HH.th_ [ HH.text "Domain" ]
-- , HH.th_ [ HH.text "TTL" ]
-- , HH.th_ [ HH.text "Priority" ]
-- , HH.th_ [ HH.text "Value" ]
-- ]
-- ]
--
--srv_table_header :: forall w i. HH.HTML w i
--srv_table_header
-- = HH.thead_ [ HH.tr_ [ HH.th_ [ HH.text "Domain" ]
-- , HH.th_ [ HH.text "TTL" ]
-- , HH.th_ [ HH.text "Priority" ]
-- , HH.th_ [ HH.text "Weight" ]
-- , HH.th_ [ HH.text "Port" ]
-- , HH.th_ [ HH.text "Value" ]
-- ]
-- ]
--
--txt_name :: forall w i. String -> HH.HTML w i
--txt_name t
-- = HH.td [ rr_name_style ] [ rr_name_text ]
-- where
-- rr_name_style = HP.style "width: 80px;"
-- rr_name_text = HH.text t
input_email :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
input_email action "" validity
= HH.input [ HE.onValueInput action, HP.placeholder "email", input_classes validity ]
input_email action email validity
= HH.input
[ HE.onValueInput action
, HP.value email
, HP.placeholder "email"
, input_classes validity
]
box_input_email :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_email action email validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
[ HH.label [HP.classes C.label ] [ HH.text "Email" ]
, HH.div [HP.classes C.control ] [ input_email action email validity ]
2023-06-08 21:51:12 +02:00
]
input_password :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
input_password action "" validity
= HH.input [ HE.onValueInput action, HP.placeholder "password", input_classes validity ]
input_password action password validity
= HH.input
[ HE.onValueInput action
, HP.value password
, HP.placeholder "password"
, input_classes validity
]
box_input_password :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_password action password validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
[ HH.label [HP.classes C.label ] [ HH.text "Password" ]
, HH.div [HP.classes C.control ] [ input_password action password validity ]
2023-06-08 21:51:12 +02:00
]
---- TODO: right types
---- input_domain :: forall a w i
---- . (String -> a)
---- -> String
---- -> Boolean
---- -> HH.HTML w i
--input_domain :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_domain action domain validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value domain
-- , HP.placeholder "domain"
-- , input_classes validity
-- ]
--
--box_input_domain :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_domain action domain validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "Domain" ]
-- , HH.div [HP.classes C.control ] [ input_domain action domain validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--input_ttl :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_ttl action ttl validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value ttl
-- , HP.prop (PropName "size") 6.0
-- , HP.placeholder "ttl"
-- , input_classes validity
-- ]
--
--box_input_ttl :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_ttl action value validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "TTL" ]
-- , HH.div [HP.classes C.control ] [ input_ttl action value validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--
--input_priority :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_priority action priority validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value priority
-- , HP.prop (PropName "size") 6.0
-- , HP.placeholder "priority"
-- , input_classes validity
-- ]
--
--box_input_priority :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_priority action value validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "Priority" ]
-- , HH.div [HP.classes C.control ] [ input_priority action value validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--
--input_value :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_value action value validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value value
-- , HP.placeholder "value"
-- , input_classes validity
-- ]
--
--box_input_value :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_value action value validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "Value" ]
-- , HH.div [HP.classes C.control ] [ input_value action value validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--
--input_weight :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_weight action weight validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value weight
-- , HP.prop (PropName "size") 6.0
-- , HP.placeholder "weight"
-- , input_classes validity
-- ]
--
--box_input_weight :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_weight action weight validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "Weight" ]
-- , HH.div [HP.classes C.control ] [ input_weight action weight validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--
--input_port :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--input_port action port validity
-- = HH.input
-- [ HE.onValueInput action
-- , HP.value port
-- , HP.prop (PropName "size") 6.0
-- , HP.placeholder "port"
-- , input_classes validity
-- ]
--
--box_input_port :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
--box_input_port action port validity = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text "Port" ]
-- , HH.div [HP.classes C.control ] [ input_port action port validity ]
2023-06-08 21:51:12 +02:00
-- ]
--
--
--btn_change :: forall w i. i -> i -> Boolean -> Boolean -> HH.HTML w i
--btn_change action1 action2 modified validity
-- = HH.button
-- [ HP.disabled (not modified)
-- , btn_change_action validity
-- , btn_classes validity
-- ] [ HH.text "fix" ]
-- where
--
-- btn_change_action = case _ of
-- true -> HE.onClick \_ -> action1
-- _ -> HE.onClick \_ -> action2
--
--
--btn_delete :: forall w i. (MouseEvent -> i) -> HH.HTML w i
--btn_delete action
-- = HH.button
-- [ HE.onClick action
-- , HP.classes [ HH.ClassName "button is-small is-danger" ]
-- ] [ HH.text "X" ]
--
--
--btn_add :: forall w i. i -> i -> Boolean -> HH.HTML w i
--btn_add action1 action2 validity
-- = HH.button
-- [ btn_add_action validity
-- , btn_classes validity
-- ] [ HH.text "Add" ]
-- where
--
-- btn_add_action = case _ of
-- true -> HE.onClick \_ -> action1
-- _ -> HE.onClick \_ -> action2
2023-06-08 22:00:53 +02:00
2023-06-13 20:17:27 +02:00
btn :: forall w action. String -> action -> action -> Boolean -> HH.HTML w action
2023-06-08 22:00:53 +02:00
btn title action1 action2 validity
= HH.button
[ btn_add_action validity
, btn_classes validity
] [ HH.text title ]
where
btn_add_action = case _ of
true -> HE.onClick \_ -> action1
_ -> HE.onClick \_ -> action2
2023-07-08 03:47:13 +02:00
render_input :: forall w i.
Boolean -> String -> (String -> i) -> String -> Boolean -> (HP.IProp DHI.HTMLinput i) -> HH.HTML w i
2023-06-09 00:28:03 +02:00
render_input password placeholder action value validity cond
= HH.input $
[ HE.onValueInput action
, HP.value value
, HP.placeholder placeholder
, input_classes validity
, cond
] <> case password of
false -> []
true -> [ HP.type_ HP.InputPassword ]
2023-07-08 03:47:13 +02:00
field_inner :: forall w i.
Boolean -> String -> String -> (String -> i) -> String -> Boolean -> (HP.IProp DHI.HTMLinput i) -> HH.HTML w i
2023-07-03 15:05:40 +02:00
field_inner ispassword title placeholder action value validity cond
= div_field
2023-07-08 03:47:13 +02:00
[ div_field_label
2023-07-03 15:05:40 +02:00
, div_field_content $ render_input ispassword placeholder action value validity cond
2023-06-09 00:28:03 +02:00
]
2023-07-03 15:05:40 +02:00
where
2023-07-08 01:50:11 +02:00
div_field = HH.div [ HP.classes (C.field <> C.horizontal) ]
2023-07-08 03:47:13 +02:00
div_field_label
2023-07-08 01:50:11 +02:00
= HH.div [ HP.classes (C.field_label <> C.normal) ]
[HH.label [ HP.classes C.label ] [ HH.text title ]]
2023-07-03 15:05:40 +02:00
div_field_content content
2023-07-08 03:47:13 +02:00
= HH.div [ HP.classes C.field_body ]
2023-07-08 01:50:11 +02:00
[ HH.div [HP.classes C.field ]
[ HH.div [HP.classes C.control ] [ content ]
2023-07-03 15:05:40 +02:00
]
]
2023-06-09 00:28:03 +02:00
2023-07-08 03:47:13 +02:00
box_input :: forall w i.
String -> String -> (String -> i) -> String -> Boolean -> (HP.IProp DHI.HTMLinput i) -> HH.HTML w i
2023-07-03 15:05:40 +02:00
box_input = field_inner false
2023-07-08 03:47:13 +02:00
box_password :: forall w i.
String -> String -> (String -> i) -> String -> Boolean -> (HP.IProp DHI.HTMLinput i) -> HH.HTML w i
2023-07-03 15:05:40 +02:00
box_password = field_inner true
2023-06-09 00:28:03 +02:00
2023-07-08 04:00:32 +02:00
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
2023-07-08 01:50:11 +02:00
section_medium = HH.section [ HP.classes (C.section <> C.medium) ]
2023-07-05 06:50:30 +02:00
field :: forall w i. Array HH.ClassName -> Array (HH.HTML w i) -> HH.HTML w i
2023-07-08 01:50:11 +02:00
field classes = HH.div [ HP.classes (C.field <> classes) ]
2023-07-05 07:00:42 +02:00
2023-07-08 03:47:13 +02:00
new_domain_field :: forall w i.
(String -> i) -> String -> Array (HP.IProp DHI.HTMLselect i) -> Array String -> HH.HTML w i
2023-07-05 06:50:30 +02:00
new_domain_field inputaction text selectaction accepted_domains
2023-07-08 01:50:11 +02:00
= field C.has_addons
2023-07-05 06:50:30 +02:00
[ HH.p
2023-07-08 01:50:11 +02:00
[ HP.classes C.control ]
2023-07-05 06:50:30 +02:00
[ HH.input $
[ HE.onValueInput inputaction
, HP.placeholder "www"
, HP.value text
, HP.type_ HP.InputText
2023-07-08 01:50:11 +02:00
, HP.classes (C.is_primary <> C.input)
2023-07-05 06:50:30 +02:00
]
]
, HH.p
2023-07-08 01:50:11 +02:00
[ HP.classes C.control ]
2023-07-05 06:50:30 +02:00
[ select selectaction $ map option accepted_domains ]
, HH.p
2023-07-08 01:50:11 +02:00
[ HP.classes C.control ]
2023-07-05 06:50:30 +02:00
[ HH.button
[ HP.type_ HP.ButtonSubmit
2023-07-08 01:50:11 +02:00
, HP.classes C.button
2023-07-05 06:50:30 +02:00
]
[ HH.text "add a new domain!" ]
]
]
2023-06-13 20:17:27 +02:00
--box_button action value validity cond
-- = HH.label [ ]
2023-07-08 01:50:11 +02:00
-- [ HH.label [HP.classes C.label ] [ HH.text title ]
-- , HH.div [HP.classes C.control ]
2023-06-13 20:17:27 +02:00
-- [ render_input ispassword placeholder action value validity cond ]
-- ]
2023-06-08 21:51:12 +02:00
p :: forall w i. String -> HH.HTML w i
p str = HH.p_ [ HH.text str ]
box :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
2023-07-08 01:50:11 +02:00
box = HH.div [HP.classes C.box]
2023-07-01 17:32:15 +02:00
option :: forall w i. String -> HH.HTML w i
option value = HH.option_ [HH.text value]
2023-07-02 00:05:38 +02:00
select :: forall w i. HH.Node DHI.HTMLselect w i
select action options
2023-07-08 01:50:11 +02:00
= HH.div [ HP.classes (C.select <> C.is_primary) ]
2023-07-02 00:05:38 +02:00
[ HH.select action options]
2023-07-05 06:50:30 +02:00
hero :: forall w i. String -> String -> HH.HTML w i
hero title subtitle
2023-07-08 01:50:11 +02:00
= 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 ]
2023-07-05 06:50:30 +02:00
]
]
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
2023-07-08 01:50:11 +02:00
container = HH.div [HP.classes (C.container <> C.is_info)]
2023-07-08 00:22:23 +02:00
data_target :: forall r i. String -> HP.IProp r i
data_target = HP.attr (AttrName "data-target")
2023-07-08 01:50:11 +02:00
modal_domain_delete :: forall w i. String -> HH.HTML w i
modal_domain_delete domain =
modal
[ modal_background
, modal_card [modal_header, modal_body]
, modal_foot [modal_delete_button, modal_cancel_button]
]
where
modal = HH.div [HP.classes (C.modal <> C.is_active)]
modal_background = HH.div [HP.classes C.modal_background] []
modal_card = HH.div [HP.classes C.modal_card]
modal_header = HH.header [HP.classes C.modal_card_head]
[ HH.p [HP.classes C.modal_card_title] [HH.text "Deleting a domain"]
--, HH.button [HP.classes C.delete, ARIA.label "close"] []
]
modal_body = HH.section [HP.classes C.modal_card_body] [ warning_message ]
modal_foot = HH.div [HP.classes C.modal_card_foot]
modal_delete_button = HH.button [HP.classes (C.button <> C.is_success)] [HH.text "Delete the domain."]
modal_cancel_button = HH.button [HP.classes C.button] [HH.text "Cancel"]
warning_message
= HH.p [] [ HH.text $ "You are about to delete your domain '"
<> domain
<> "'. Are you sure you want to do this? This is "
, HH.strong_ [ HH.text "irreversible" ]
, HH.text "."
]
2023-07-09 14:26:47 +02:00
hr :: forall w i. HH.HTML w i
hr = HH.hr_
tile :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
tile = HH.div [HP.classes (C.tile <> C.is_primary <> C.box)]