ZoneInterface now uses mostly the Bulma module.

beta
Philippe Pittoli 2023-07-10 18:14:56 +02:00
parent 44004ec96e
commit c0db4a93e0
4 changed files with 315 additions and 336 deletions

View File

@ -2,6 +2,7 @@ module App.Style where
import Prelude
import CSSClasses as C
import Halogen.HTML as HH
import Halogen.HTML.Properties as HP
import Halogen.HTML.Events as HE
@ -11,50 +12,28 @@ import Halogen.HTML.Core (PropName(..))
-- import Web.Event.Event (type_, Event, EventType(..))
import Web.UIEvent.MouseEvent (MouseEvent)
-- This file is mostly a wrapper around BULMA.
class_columns :: Array (HH.ClassName)
class_columns = [HH.ClassName "columns" ]
class_column :: Array (HH.ClassName)
class_column = [HH.ClassName "column" ]
class_title :: Array (HH.ClassName)
class_title = [HH.ClassName "title" ]
class_subtitle :: Array (HH.ClassName)
class_subtitle = [HH.ClassName "subtitle" ]
class_is5 :: Array (HH.ClassName)
class_is5 = [HH.ClassName "is-5" ]
class_is4 :: Array (HH.ClassName)
class_is4 = [HH.ClassName "is-4" ]
class_box :: Array (HH.ClassName)
class_box = [HH.ClassName "box" ]
class_label :: Array (HH.ClassName)
class_label = [HH.ClassName "label" ]
class_control :: Array (HH.ClassName)
class_control = [HH.ClassName "control" ]
columns :: forall (w :: Type) (i :: Type).
Array (HH.ClassName) -> Array (HH.HTML w i) -> HH.HTML w i
columns classes = HH.div [ HP.classes (class_columns <> classes) ]
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 (class_column <> classes) ]
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 (class_title) ] [ HH.text title ]
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.h1 [ HP.classes (class_title <> class_is5) ] [ HH.text title ]
h3 title = HH.h1 [ HP.classes (C.title <> C.is5) ] [ HH.text title ]
subtitle :: forall (w :: Type) (a :: Type). String -> HH.HTML w a
subtitle title = HH.h2 [ HP.classes (class_subtitle <> class_is4) ] [ HH.text title ]
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"] ]
@ -124,8 +103,8 @@ input_email action email validity
box_input_email :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_email action email validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Email" ]
, HH.div [HP.classes class_control ] [ input_email action email validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Email" ]
, HH.div [HP.classes C.control ] [ input_email action email validity ]
]
@ -142,8 +121,8 @@ input_password action password validity
box_input_password :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_password action password validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Password" ]
, HH.div [HP.classes class_control ] [ input_password action password validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Password" ]
, HH.div [HP.classes C.control ] [ input_password action password validity ]
]
@ -164,8 +143,8 @@ input_domain action domain validity
box_input_domain :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_domain action domain validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Domain" ]
, HH.div [HP.classes class_control ] [ input_domain action domain validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Domain" ]
, HH.div [HP.classes C.control ] [ input_domain action domain validity ]
]
input_ttl :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
@ -180,8 +159,8 @@ input_ttl action ttl validity
box_input_ttl :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_ttl action value validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "TTL" ]
, HH.div [HP.classes class_control ] [ input_ttl action value validity ]
[ HH.label [HP.classes C.label ] [ HH.text "TTL" ]
, HH.div [HP.classes C.control ] [ input_ttl action value validity ]
]
@ -197,8 +176,8 @@ input_priority action priority validity
box_input_priority :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_priority action value validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Priority" ]
, HH.div [HP.classes class_control ] [ input_priority action value validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Priority" ]
, HH.div [HP.classes C.control ] [ input_priority action value validity ]
]
@ -213,8 +192,8 @@ input_value action value validity
box_input_value :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_value action value validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Value" ]
, HH.div [HP.classes class_control ] [ input_value action value validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Value" ]
, HH.div [HP.classes C.control ] [ input_value action value validity ]
]
@ -230,8 +209,8 @@ input_weight action weight validity
box_input_weight :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_weight action weight validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Weight" ]
, HH.div [HP.classes class_control ] [ input_weight action weight validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Weight" ]
, HH.div [HP.classes C.control ] [ input_weight action weight validity ]
]
@ -247,8 +226,8 @@ input_port action port validity
box_input_port :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_port action port validity = HH.label [ ]
[ HH.label [HP.classes class_label ] [ HH.text "Port" ]
, HH.div [HP.classes class_control ] [ input_port action port validity ]
[ HH.label [HP.classes C.label ] [ HH.text "Port" ]
, HH.div [HP.classes C.control ] [ input_port action port validity ]
]
@ -287,4 +266,4 @@ btn_add action1 action2 validity
_ -> HE.onClick \_ -> action2
box :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
box = HH.div [HP.classes class_box]
box = HH.div [HP.classes C.box]

View File

@ -569,16 +569,17 @@ class_title_size = [HH.ClassName "is-4"]
render_records :: forall (w :: Type). Array (SimpleRR ()) -> HH.HTML w Action
render_records []
= S.columns [] [ left_block, right_block ]
where left_block = S.column class_title_size
[ Bulma.zone_rr_title "NS, A, AAAA, CNAME"
, S.subtitle "and TXT records" ]
right_block = S.column_ [ S.subtitle "No records for now" ]
= Bulma.columns [] [ left_block, right_block ]
where left_block = Bulma.column class_title_size
[ Bulma.zone_rr_title "NS, A, AAAA, CNAME"
, Bulma.subtitle "and TXT records"
]
right_block = Bulma.column_ [ Bulma.subtitle "No records for now" ]
render_records records
= S.columns [] [ S.column class_title_size [Bulma.zone_rr_title title_txt, S.subtitle subtitle_txt ]
, S.column_ [ Bulma.tile [ table_rr ] ]
]
= Bulma.columns [] [ Bulma.column class_title_size [Bulma.zone_rr_title title_txt, Bulma.subtitle subtitle_txt ]
, Bulma.column_ [ Bulma.tile [ table_rr ] ]
]
where
title_txt = "NS, A, AAAA, CNAME"
subtitle_txt = "and TXT records"
@ -589,62 +590,62 @@ render_records records
row rr = HH.tr_ $
[ S.txt_name rr.t
, HH.td_ [ S.input_domain ((UpdateLocalSRRForm rr.id) <<< Update_SRR_Domain) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl ((UpdateLocalSRRForm rr.id) <<< Update_SRR_TTL ) rr.ttl rr.valid ]
, HH.td_ [ S.input_value ((UpdateLocalSRRForm rr.id) <<< Update_SRR_Value) rr.value rr.valid ]
, HH.td_ [ S.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ S.btn_delete (\_ -> DeleteSimple rr.id) ]
, HH.td_ [ Bulma.input_domain ((UpdateLocalSRRForm rr.id) <<< Update_SRR_Domain) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl ((UpdateLocalSRRForm rr.id) <<< Update_SRR_TTL ) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_value ((UpdateLocalSRRForm rr.id) <<< Update_SRR_Value) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ Bulma.btn_delete (\_ -> DeleteSimple rr.id) ]
]
render_mx_records :: forall (w :: Type) (l :: Row Type)
. Array (MXRR l) -> HH.HTML w Action
render_mx_records []
= S.columns [] [ left_block, right_block ]
where left_block = S.column class_title_size [ Bulma.zone_rr_title "MX records" ]
right_block = S.column_ [ S.subtitle "No records for now" ]
= Bulma.columns [] [ left_block, right_block ]
where left_block = Bulma.column class_title_size [ Bulma.zone_rr_title "MX records" ]
right_block = Bulma.column_ [ Bulma.subtitle "No records for now" ]
render_mx_records records
= S.columns [] [ S.column class_title_size [ Bulma.zone_rr_title title_txt ]
, S.column_ [ Bulma.tile [ table_rr ] ]
]
= Bulma.columns [] [ Bulma.column class_title_size [ Bulma.zone_rr_title title_txt ]
, Bulma.column_ [ Bulma.tile [ table_rr ] ]
]
where
title_txt = "MX records"
table_rr = HH.table [] [ S.mx_table_header, table_content ]
table_content = HH.tbody_ $ map row records
row rr = HH.tr_ $
[ HH.td_ [ S.input_domain ((UpdateLocalMXForm rr.id) <<< Update_MX_Domain) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl ((UpdateLocalMXForm rr.id) <<< Update_MX_TTL) rr.ttl rr.valid ]
, HH.td_ [ S.input_priority ((UpdateLocalMXForm rr.id) <<< Update_MX_Priority) rr.priority rr.valid ]
, HH.td_ [ S.input_value ((UpdateLocalMXForm rr.id) <<< Update_MX_Value) rr.value rr.valid ]
, HH.td_ [ S.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ S.btn_delete (\_ -> DeleteMX rr.id) ]
[ HH.td_ [ Bulma.input_domain ((UpdateLocalMXForm rr.id) <<< Update_MX_Domain) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl ((UpdateLocalMXForm rr.id) <<< Update_MX_TTL) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_priority ((UpdateLocalMXForm rr.id) <<< Update_MX_Priority) rr.priority rr.valid ]
, HH.td_ [ Bulma.input_value ((UpdateLocalMXForm rr.id) <<< Update_MX_Value) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ Bulma.btn_delete (\_ -> DeleteMX rr.id) ]
]
render_srv_records :: forall (w :: Type) (l :: Row Type)
. Array (SRVRR l) -> HH.HTML w Action
render_srv_records []
= S.columns [] [ left_block, right_block ]
where left_block = S.column class_title_size [ Bulma.zone_rr_title "SRV records" ]
right_block = S.column_ [ S.subtitle "No records for now" ]
= Bulma.columns [] [ left_block, right_block ]
where left_block = Bulma.column class_title_size [ Bulma.zone_rr_title "SRV records" ]
right_block = Bulma.column_ [ Bulma.subtitle "No records for now" ]
render_srv_records records
= S.columns [] [ S.column class_title_size [ Bulma.zone_rr_title title_txt]
, S.column_ [ Bulma.tile [ table_rr ] ] ]
= Bulma.columns [] [ Bulma.column class_title_size [ Bulma.zone_rr_title title_txt]
, Bulma.column_ [ Bulma.tile [ table_rr ] ] ]
where
title_txt = "SRV records"
table_rr = HH.table [] [ S.srv_table_header, table_content ]
table_content = HH.tbody_ $ map row records
row rr = HH.tr_ $
[ HH.td_ [ S.input_domain ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Domain ) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl ((UpdateLocalSRVForm rr.id) <<< Update_SRV_TTL ) rr.ttl rr.valid ]
, HH.td_ [ S.input_priority ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Priority) rr.priority rr.valid ]
, HH.td_ [ S.input_weight ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Weight ) rr.weight rr.valid ]
, HH.td_ [ S.input_port ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Port ) rr.port rr.valid ]
, HH.td_ [ S.input_value ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Value ) rr.value rr.valid ]
, HH.td_ [ S.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ S.btn_delete (\_ -> DeleteSRV rr.id) ]
[ HH.td_ [ Bulma.input_domain ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Domain ) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl ((UpdateLocalSRVForm rr.id) <<< Update_SRV_TTL ) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_priority ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Priority) rr.priority rr.valid ]
, HH.td_ [ Bulma.input_weight ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Weight ) rr.weight rr.valid ]
, HH.td_ [ Bulma.input_port ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Port ) rr.port rr.valid ]
, HH.td_ [ Bulma.input_value ((UpdateLocalSRVForm rr.id) <<< Update_SRV_Value ) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_change (SyncRR rr.id) (TellSomethingWentWrong rr.id "cannot update") rr.modified rr.valid ]
, HH.td_ [ Bulma.btn_delete (\_ -> DeleteSRV rr.id) ]
]
@ -653,7 +654,7 @@ baseRecords = [ "NS", "A", "AAAA", "CNAME", "TXT" ]
render_new_record :: forall (w :: Type). (SimpleRR ()) -> HH.HTML w Action
render_new_record rr
= S.hdiv [ Bulma.zone_rr_title "New record (NS, A, AAAA, CNAME, TXT)", table ]
= Bulma.hdiv [ Bulma.zone_rr_title "New record (NS, A, AAAA, CNAME, TXT)", table ]
where
table = HH.table [] [ S.simple_table_header, render_record_builder ]
@ -662,10 +663,10 @@ render_new_record rr
render_record_builder
= HH.tr_
[ HH.td_ [ type_selection ]
, HH.td_ [ S.input_domain (UpdateNewSRRForm <<< Update_SRR_Domain) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl (UpdateNewSRRForm <<< Update_SRR_TTL) rr.ttl rr.valid ]
, HH.td_ [ S.input_value (UpdateNewSRRForm <<< Update_SRR_Value) rr.value rr.valid ]
, HH.td_ [ S.btn_add AddSRR (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
, HH.td_ [ Bulma.input_domain (UpdateNewSRRForm <<< Update_SRR_Domain) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl (UpdateNewSRRForm <<< Update_SRR_TTL) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_value (UpdateNewSRRForm <<< Update_SRR_Value) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_add AddSRR (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
]
-- type_selection :: forall w i. HH.HTML w i
@ -681,7 +682,7 @@ render_new_record rr
render_mx_new_record :: forall (w :: Type). (MXRR ()) -> HH.HTML w Action
render_mx_new_record rr
= S.hdiv [ Bulma.zone_rr_title "New MX record", table ]
= Bulma.hdiv [ Bulma.zone_rr_title "New MX record", table ]
where
table = HH.table [] [ S.mx_table_header, render_record_builder ]
@ -689,30 +690,30 @@ render_mx_new_record rr
-- render_record_builder :: forall w. HH.HTML w Action
render_record_builder
= HH.tr_
[ HH.td_ [ S.input_domain (UpdateNewMXForm <<< Update_MX_Domain) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl (UpdateNewMXForm <<< Update_MX_TTL) rr.ttl rr.valid ]
, HH.td_ [ S.input_priority (UpdateNewMXForm <<< Update_MX_Priority) rr.priority rr.valid ]
, HH.td_ [ S.input_value (UpdateNewMXForm <<< Update_MX_Value) rr.value rr.valid ]
, HH.td_ [ S.btn_add AddMX (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
[ HH.td_ [ Bulma.input_domain (UpdateNewMXForm <<< Update_MX_Domain) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl (UpdateNewMXForm <<< Update_MX_TTL) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_priority (UpdateNewMXForm <<< Update_MX_Priority) rr.priority rr.valid ]
, HH.td_ [ Bulma.input_value (UpdateNewMXForm <<< Update_MX_Value) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_add AddMX (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
]
render_srv_new_record :: forall (w :: Type). (SRVRR ()) -> HH.HTML w Action
render_srv_new_record rr
= S.hdiv [ Bulma.zone_rr_title "New SRV record", table ]
= Bulma.hdiv [ Bulma.zone_rr_title "New SRV record", table ]
where
table = HH.table [] [ S.srv_table_header, render_record_builder ]
-- render_record_builder :: forall w. HH.HTML w Action
render_record_builder
= HH.tr_
[ HH.td_ [ S.input_domain (UpdateNewSRVForm <<< Update_SRV_Domain) rr.domain rr.valid ]
, HH.td_ [ S.input_ttl (UpdateNewSRVForm <<< Update_SRV_TTL) rr.ttl rr.valid ]
, HH.td_ [ S.input_priority (UpdateNewSRVForm <<< Update_SRV_Priority) rr.priority rr.valid ]
, HH.td_ [ S.input_weight (UpdateNewSRVForm <<< Update_SRV_Weight) rr.weight rr.valid ]
, HH.td_ [ S.input_port (UpdateNewSRVForm <<< Update_SRV_Port) rr.port rr.valid ]
, HH.td_ [ S.input_value (UpdateNewSRVForm <<< Update_SRV_Value) rr.value rr.valid ]
, HH.td_ [ S.btn_add AddSRV (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
[ HH.td_ [ Bulma.input_domain (UpdateNewSRVForm <<< Update_SRV_Domain) rr.domain rr.valid ]
, HH.td_ [ Bulma.input_ttl (UpdateNewSRVForm <<< Update_SRV_TTL) rr.ttl rr.valid ]
, HH.td_ [ Bulma.input_priority (UpdateNewSRVForm <<< Update_SRV_Priority) rr.priority rr.valid ]
, HH.td_ [ Bulma.input_weight (UpdateNewSRVForm <<< Update_SRV_Weight) rr.weight rr.valid ]
, HH.td_ [ Bulma.input_port (UpdateNewSRVForm <<< Update_SRV_Port) rr.port rr.valid ]
, HH.td_ [ Bulma.input_value (UpdateNewSRVForm <<< Update_SRV_Value) rr.value rr.valid ]
, HH.td_ [ Bulma.btn_add AddSRV (TellSomethingWentWrong rr.id "cannot add") rr.valid ]
]
@ -720,10 +721,10 @@ render_srv_new_record rr
render_new_records :: forall (w :: Type). State -> HH.HTML w Action
render_new_records state
= S.hdiv
= Bulma.hdiv
[ Bulma.h1 "Adding new records"
, Bulma.hr
, S.columns []
, Bulma.columns []
[ render_new_record_column_simple state._current_entry
, render_new_record_colunm_mx state._current_entry_mx
, render_new_record_colunm_srv state._current_entry_srv
@ -736,13 +737,13 @@ render_new_records state
render_new_record_column_simple :: forall (w :: Type).
(SimpleRR ()) -> HH.HTML w Action
render_new_record_column_simple rr
= S.column_ $ [ S.box
= Bulma.column_ $ [ S.box
[ Bulma.zone_rr_title "NS, A, AAAA, CNAME, TXT"
, type_selection
, S.box_input_domain (UpdateNewSRRForm <<< Update_SRR_Domain) rr.domain rr.valid
, S.box_input_ttl (UpdateNewSRRForm <<< Update_SRR_TTL) rr.ttl rr.valid
, S.box_input_value (UpdateNewSRRForm <<< Update_SRR_Value) rr.value rr.valid
, S.btn_add AddSRR (TellSomethingWentWrong rr.id "cannot add") rr.valid
, Bulma.box_input_domain (UpdateNewSRRForm <<< Update_SRR_Domain) rr.domain rr.valid
, Bulma.box_input_ttl (UpdateNewSRRForm <<< Update_SRR_TTL) rr.ttl rr.valid
, Bulma.box_input_value (UpdateNewSRRForm <<< Update_SRR_Value) rr.value rr.valid
, Bulma.btn_add AddSRR (TellSomethingWentWrong rr.id "cannot add") rr.valid
]
]
where
@ -759,27 +760,27 @@ render_new_record_column_simple rr
render_new_record_colunm_mx :: forall (w :: Type). (MXRR ()) -> HH.HTML w Action
render_new_record_colunm_mx rr
= S.column_ $ [ S.box
= Bulma.column_ $ [ S.box
[ Bulma.zone_rr_title "MX"
, S.box_input_domain (UpdateNewMXForm <<< Update_MX_Domain) rr.domain rr.valid
, S.box_input_ttl (UpdateNewMXForm <<< Update_MX_TTL) rr.ttl rr.valid
, S.box_input_priority (UpdateNewMXForm <<< Update_MX_Priority) rr.priority rr.valid
, S.box_input_value (UpdateNewMXForm <<< Update_MX_Value) rr.value rr.valid
, S.btn_add AddMX (TellSomethingWentWrong rr.id "cannot add") rr.valid
, Bulma.box_input_domain (UpdateNewMXForm <<< Update_MX_Domain) rr.domain rr.valid
, Bulma.box_input_ttl (UpdateNewMXForm <<< Update_MX_TTL) rr.ttl rr.valid
, Bulma.box_input_priority (UpdateNewMXForm <<< Update_MX_Priority) rr.priority rr.valid
, Bulma.box_input_value (UpdateNewMXForm <<< Update_MX_Value) rr.value rr.valid
, Bulma.btn_add AddMX (TellSomethingWentWrong rr.id "cannot add") rr.valid
]
]
render_new_record_colunm_srv :: forall (w :: Type). (SRVRR ()) -> HH.HTML w Action
render_new_record_colunm_srv rr
= S.column_ $ [ S.box
= Bulma.column_ $ [ S.box
[ Bulma.zone_rr_title "SRV"
, S.box_input_domain (UpdateNewSRVForm <<< Update_SRV_Domain) rr.domain rr.valid
, S.box_input_ttl (UpdateNewSRVForm <<< Update_SRV_TTL) rr.ttl rr.valid
, S.box_input_priority (UpdateNewSRVForm <<< Update_SRV_Priority) rr.priority rr.valid
, S.box_input_weight (UpdateNewSRVForm <<< Update_SRV_Weight) rr.weight rr.valid
, S.box_input_port (UpdateNewSRVForm <<< Update_SRV_Port) rr.port rr.valid
, S.box_input_value (UpdateNewSRVForm <<< Update_SRV_Value) rr.value rr.valid
, S.btn_add AddSRV (TellSomethingWentWrong rr.id "cannot add") rr.valid
, Bulma.box_input_domain (UpdateNewSRVForm <<< Update_SRV_Domain) rr.domain rr.valid
, Bulma.box_input_ttl (UpdateNewSRVForm <<< Update_SRV_TTL) rr.ttl rr.valid
, Bulma.box_input_priority (UpdateNewSRVForm <<< Update_SRV_Priority) rr.priority rr.valid
, Bulma.box_input_weight (UpdateNewSRVForm <<< Update_SRV_Weight) rr.weight rr.valid
, Bulma.box_input_port (UpdateNewSRVForm <<< Update_SRV_Port) rr.port rr.valid
, Bulma.box_input_value (UpdateNewSRVForm <<< Update_SRV_Value) rr.value rr.valid
, Bulma.btn_add AddSRV (TellSomethingWentWrong rr.id "cannot add") rr.valid
]
]

View File

@ -10,16 +10,18 @@ import Halogen.HTML.Events as HE
import CSSClasses as C
-- HTML PropName used with HP.prop
import Halogen.HTML.Core (AttrName(..))
--import Halogen.HTML.Core (PropName(..))
import Halogen.HTML.Core (PropName(..), AttrName(..))
-- import Web.Event.Event (type_, Event, EventType(..))
--import Web.UIEvent.MouseEvent (MouseEvent)
import Web.UIEvent.MouseEvent (MouseEvent)
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) ]
--prop_size :: HP.PropName "size"
prop_size :: forall r i. Int -> HP.IProp r i
prop_size = HP.prop (PropName "size")
columns_ :: forall (w :: Type) (i :: Type). Array (HH.HTML w i) -> HH.HTML w i
columns_ = columns []
@ -41,26 +43,25 @@ zone_rr_title title
= HH.h3 [ HP.classes (C.title <> C.is5 <> 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"] ]
--
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 :: 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" ]
input_classes :: Boolean -> Array HH.ClassName
input_classes true = C.input <> C.is_small <> C.is_info
input_classes false = C.input <> C.is_small <> C.is_danger
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" ]
btn_classes :: Boolean -> Array HH.ClassName
btn_classes true = C.button <> C.is_small <> C.is_info
btn_classes false = C.button <> C.is_small <> C.is_danger
--simple_table_header :: forall w i. HH.HTML w i
--simple_table_header
@ -100,13 +101,16 @@ btn_classes false = HP.classes [ HH.ClassName "button is-small is-danger" ]
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 ]
= HH.input [ HE.onValueInput action
, HP.placeholder "email"
, HP.classes $ input_classes validity
]
input_email action email validity
= HH.input
[ HE.onValueInput action
, HP.value email
, HP.placeholder "email"
, input_classes validity
, HP.classes $ input_classes validity
]
box_input_email :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
@ -117,13 +121,16 @@ box_input_email action email validity = HH.label [ ]
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 ]
= HH.input [ HE.onValueInput action
, HP.placeholder "password"
, HP.classes $ input_classes validity
]
input_password action password validity
= HH.input
[ HE.onValueInput action
, HP.value password
, HP.placeholder "password"
, input_classes validity
, HP.classes $ input_classes validity
]
box_input_password :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
@ -132,152 +139,142 @@ box_input_password action password validity = HH.label [ ]
, HH.div [HP.classes C.control ] [ input_password action password validity ]
]
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"
, HP.classes $ input_classes validity
]
---- 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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "Domain" ]
-- , HH.div [HP.classes C.control ] [ input_domain action domain validity ]
-- ]
--
--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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "TTL" ]
-- , HH.div [HP.classes C.control ] [ input_ttl action value validity ]
-- ]
--
--
--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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "Priority" ]
-- , HH.div [HP.classes C.control ] [ input_priority action value validity ]
-- ]
--
--
--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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "Value" ]
-- , HH.div [HP.classes C.control ] [ input_value action value validity ]
-- ]
--
--
--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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "Weight" ]
-- , HH.div [HP.classes C.control ] [ input_weight action weight validity ]
-- ]
--
--
--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 [ ]
-- [ HH.label [HP.classes C.label ] [ HH.text "Port" ]
-- , HH.div [HP.classes C.control ] [ input_port action port validity ]
-- ]
--
--
--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
box_input_domain :: forall w i. (String -> i) -> String -> Boolean -> HH.HTML w i
box_input_domain action domain validity = HH.label [ ]
[ HH.label [HP.classes C.label ] [ HH.text "Domain" ]
, HH.div [HP.classes C.control ] [ input_domain action domain validity ]
]
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
, prop_size 6
, HP.placeholder "ttl"
, HP.classes $ 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 [ ]
[ HH.label [HP.classes C.label ] [ HH.text "TTL" ]
, HH.div [HP.classes C.control ] [ input_ttl action value validity ]
]
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
, prop_size 6
, HP.placeholder "priority"
, HP.classes $ 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 [ ]
[ HH.label [HP.classes C.label ] [ HH.text "Priority" ]
, HH.div [HP.classes C.control ] [ input_priority action value validity ]
]
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"
, HP.classes $ 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 [ ]
[ HH.label [HP.classes C.label ] [ HH.text "Value" ]
, HH.div [HP.classes C.control ] [ input_value action value validity ]
]
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
, prop_size 6
, HP.placeholder "weight"
, HP.classes $ 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 [ ]
[ HH.label [HP.classes C.label ] [ HH.text "Weight" ]
, HH.div [HP.classes C.control ] [ input_weight action weight validity ]
]
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
, prop_size 6
, HP.placeholder "port"
, HP.classes $ 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 [ ]
[ HH.label [HP.classes C.label ] [ HH.text "Port" ]
, HH.div [HP.classes C.control ] [ input_port action port validity ]
]
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
, HP.classes $ 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
, HP.classes $ btn_classes validity
] [ HH.text "Add" ]
where
btn_add_action = case _ of
true -> HE.onClick \_ -> action1
_ -> HE.onClick \_ -> action2
btn :: forall w action. String -> action -> action -> Boolean -> HH.HTML w action
btn title action1 action2 validity
= HH.button
[ btn_add_action validity
, btn_classes validity
, HP.classes $ btn_classes validity
] [ HH.text title ]
where
btn_add_action = case _ of
@ -291,7 +288,7 @@ render_input password placeholder action value validity cond
[ HE.onValueInput action
, HP.value value
, HP.placeholder placeholder
, input_classes validity
, HP.classes $ input_classes validity
, cond
] <> case password of
false -> []

View File

@ -2,109 +2,111 @@ module CSSClasses where
import Halogen.HTML as HH
box :: Array (HH.ClassName)
box :: Array HH.ClassName
box = [HH.ClassName "box"]
button :: Array (HH.ClassName)
button :: Array HH.ClassName
button = [HH.ClassName "button"]
buttons :: Array (HH.ClassName)
buttons :: Array HH.ClassName
buttons = [HH.ClassName "buttons"]
column :: Array (HH.ClassName)
column :: Array HH.ClassName
column = [HH.ClassName "column"]
columns :: Array (HH.ClassName)
columns :: Array HH.ClassName
columns = [HH.ClassName "columns"]
container :: Array (HH.ClassName)
container :: Array HH.ClassName
container = [HH.ClassName "container"]
control :: Array (HH.ClassName)
control :: Array HH.ClassName
control = [HH.ClassName "control"]
delete :: Array (HH.ClassName)
delete :: Array HH.ClassName
delete = [HH.ClassName "delete"]
field :: Array (HH.ClassName)
field :: Array HH.ClassName
field = [HH.ClassName "field"]
field_body :: Array (HH.ClassName)
field_body :: Array HH.ClassName
field_body = [HH.ClassName "field-body"]
field_label :: Array (HH.ClassName)
field_label :: Array HH.ClassName
field_label = [HH.ClassName "field-label"]
has_addons :: Array (HH.ClassName)
has_addons :: Array HH.ClassName
has_addons = [HH.ClassName "has-addons"]
has_background_dark :: Array (HH.ClassName)
has_background_dark :: Array HH.ClassName
has_background_dark = [HH.ClassName "has-background-dark"]
has_text_light :: Array (HH.ClassName)
has_text_light :: Array HH.ClassName
has_text_light = [HH.ClassName "has-text-light"]
has_dropdown :: Array (HH.ClassName)
has_dropdown :: Array HH.ClassName
has_dropdown = [HH.ClassName "has-dropdown"]
hero :: Array (HH.ClassName)
hero :: Array HH.ClassName
hero = [HH.ClassName "hero"]
hero_body :: Array (HH.ClassName)
hero_body :: Array HH.ClassName
hero_body = [HH.ClassName "hero-body"]
horizontal :: Array (HH.ClassName)
horizontal :: Array HH.ClassName
horizontal = [HH.ClassName "is-horizontal"]
input :: Array (HH.ClassName)
input :: Array HH.ClassName
input = [HH.ClassName "input"]
is4 :: Array (HH.ClassName)
is4 :: Array HH.ClassName
is4 = [HH.ClassName "is-4"]
is5 :: Array (HH.ClassName)
is5 :: Array HH.ClassName
is5 = [HH.ClassName "is-5"]
is_active :: Array (HH.ClassName)
is_active :: Array HH.ClassName
is_active = [HH.ClassName "is-active"]
is_hoverable :: Array (HH.ClassName)
is_danger :: Array HH.ClassName
is_danger = [HH.ClassName "is-danger"]
is_hoverable :: Array HH.ClassName
is_hoverable = [HH.ClassName "is-hoverable"]
is_info :: Array (HH.ClassName)
is_info :: Array HH.ClassName
is_info = [HH.ClassName "is-info"]
is_light :: Array (HH.ClassName)
is_light :: Array HH.ClassName
is_light = [HH.ClassName "is-light"]
is_primary :: Array (HH.ClassName)
is_primary :: Array HH.ClassName
is_primary = [HH.ClassName "is-primary"]
is_small :: Array (HH.ClassName)
is_small :: Array HH.ClassName
is_small = [HH.ClassName "is-small"]
is_success :: Array (HH.ClassName)
is_success :: Array HH.ClassName
is_success = [HH.ClassName "is-success"]
label :: Array (HH.ClassName)
label :: Array HH.ClassName
label = [HH.ClassName "label"]
medium :: Array (HH.ClassName)
medium :: Array HH.ClassName
medium = [HH.ClassName "is-medium"]
modal :: Array (HH.ClassName)
modal :: Array HH.ClassName
modal = [HH.ClassName "modal"]
modal_background :: Array (HH.ClassName)
modal_background :: Array HH.ClassName
modal_background = [HH.ClassName "modal-background"]
modal_card :: Array (HH.ClassName)
modal_card :: Array HH.ClassName
modal_card = [HH.ClassName "modal-card"]
modal_card_body :: Array (HH.ClassName)
modal_card_body :: Array HH.ClassName
modal_card_body = [HH.ClassName "modal-card-body"]
modal_card_foot :: Array (HH.ClassName)
modal_card_foot :: Array HH.ClassName
modal_card_foot = [HH.ClassName "modal-card-foot"]
modal_card_head :: Array (HH.ClassName)
modal_card_head :: Array HH.ClassName
modal_card_head = [HH.ClassName "modal-card-head"]
modal_card_title :: Array (HH.ClassName)
modal_card_title :: Array HH.ClassName
modal_card_title = [HH.ClassName "modal-card-title"]
navbar :: Array (HH.ClassName)
navbar :: Array HH.ClassName
navbar = [HH.ClassName "navbar"]
navbar_brand :: Array (HH.ClassName)
navbar_brand :: Array HH.ClassName
navbar_brand = [HH.ClassName "navbar-brand"]
navbar_burger :: Array (HH.ClassName)
navbar_burger :: Array HH.ClassName
navbar_burger = [HH.ClassName "navbar-burger"]
navbar_divider :: Array (HH.ClassName)
navbar_divider :: Array HH.ClassName
navbar_divider = [HH.ClassName "navbar-divider"]
navbar_dropdown :: Array (HH.ClassName)
navbar_dropdown :: Array HH.ClassName
navbar_dropdown = [HH.ClassName "navbar-dropdown"]
navbar_end :: Array (HH.ClassName)
navbar_end :: Array HH.ClassName
navbar_end = [HH.ClassName "navbar-end"]
navbar_item :: Array (HH.ClassName)
navbar_item :: Array HH.ClassName
navbar_item = [HH.ClassName "navbar-item"]
navbar_link :: Array (HH.ClassName)
navbar_link :: Array HH.ClassName
navbar_link = [HH.ClassName "navbar-link"]
navbar_menu :: Array (HH.ClassName)
navbar_menu :: Array HH.ClassName
navbar_menu = [HH.ClassName "navbar-menu"]
navbar_start :: Array (HH.ClassName)
navbar_start :: Array HH.ClassName
navbar_start = [HH.ClassName "navbar-start"]
normal :: Array (HH.ClassName)
normal :: Array HH.ClassName
normal = [HH.ClassName "is-normal"]
section :: Array (HH.ClassName)
section :: Array HH.ClassName
section = [HH.ClassName "section"]
select :: Array (HH.ClassName)
select :: Array HH.ClassName
select = [HH.ClassName "select"]
subtitle :: Array (HH.ClassName)
subtitle :: Array HH.ClassName
subtitle = [HH.ClassName "subtitle"]
tile :: Array (HH.ClassName)
tile :: Array HH.ClassName
tile = [HH.ClassName "tile"]
title :: Array (HH.ClassName)
title :: Array HH.ClassName
title = [HH.ClassName "title"]