WIP: explanations. Text can now be justified. Dedicated `explanation` function.

dev
Philippe Pittoli 2024-03-04 03:24:03 +01:00
parent 7e311d7ba0
commit 896254092a
4 changed files with 63 additions and 24 deletions

View File

@ -6,6 +6,12 @@
<link rel="stylesheet" href="./bulma.css">
<title>DNS Manager (beta)</title>
</head>
<style>
.justified {
text-justify: auto;
text-align: justify
}
</style>
<body>
<script src="./index.js" type="module"></script>
</body>

View File

@ -0,0 +1,28 @@
module App.Text.Explanations where
import Halogen.HTML as HH
spf_introduction :: forall w i. Array (HH.HTML w i)
spf_introduction =
[ HH.p []
[ HH.text "Sender Policy Framework (SPF) is a way to tell "
, HH.u_ [HH.text "other mail servers"]
, HH.text " what are mail servers susceptible to send mails with "
, HH.u_ [HH.text "our email address"]
, HH.text ". "
]
, HH.p []
[ HH.text """
This way, we can mitigate spam.
A server receiving a mail with our email address but coming from an IP address we didn't list as authorized will be discarded.
This is not a bullet-proof technique, but it's simple enough and works great with the most basic forms of spam.
"""
]
, HH.p []
[ HH.text "A correctly configured domain with a mail server should only advertise the right IP addresses that can possibly send mails from the domain."
]
]
spf_default_behavior :: forall w i. Array (HH.HTML w i)
spf_default_behavior = [HH.text """
What should someone do when receiving a mail with your email address but not from a listed domain or IP address?
"""]

View File

@ -39,6 +39,8 @@ import Halogen.HTML.Properties as HP
import Bulma as Bulma
import CSSClasses as C
import App.Text.Explanations as Explanations
import App.AcceptedRRTypes (AcceptedRRTypes(..))
import App.ResourceRecord (ResourceRecord, emptyRR
, show_qualifier, show_qualifier_char
@ -301,14 +303,14 @@ render state
render_current_rr_modal :: forall w. HH.HTML w Action
render_current_rr_modal =
case state._currentRR.rrtype of
"A" -> template content_simple (foot_content A)
"AAAA" -> template content_simple (foot_content AAAA)
"TXT" -> template content_simple (foot_content TXT)
"CNAME" -> template content_simple (foot_content CNAME)
"NS" -> template content_simple (foot_content NS)
"MX" -> template content_mx (foot_content MX)
"SRV" -> template content_srv (foot_content SRV)
"SPF" -> template content_spf (foot_content SPF)
"A" -> template modal_content_simple (foot_content A)
"AAAA" -> template modal_content_simple (foot_content AAAA)
"TXT" -> template modal_content_simple (foot_content TXT)
"CNAME" -> template modal_content_simple (foot_content CNAME)
"NS" -> template modal_content_simple (foot_content NS)
"MX" -> template modal_content_mx (foot_content MX)
"SRV" -> template modal_content_srv (foot_content SRV)
"SPF" -> template modal_content_spf (foot_content SPF)
_ -> Bulma.p $ "Invalid type: " <> state._currentRR.rrtype
where
-- DRY
@ -316,8 +318,8 @@ render state
render_errors = if A.length state._currentRR_errors > 0
then HH.div_ $ [ Bulma.h3 "Errors: " ] <> map error_to_paragraph state._currentRR_errors
else HH.div_ [ ]
content_simple :: Array (HH.HTML w Action)
content_simple =
modal_content_simple :: Array (HH.HTML w Action)
modal_content_simple =
[ render_errors
, Bulma.input_with_side_text ("domain" <> state._currentRR.rrtype) "Name" "www"
(updateForm Field_Domain)
@ -332,8 +334,8 @@ render state
state._currentRR.target
should_be_disabled
]
content_mx :: Array (HH.HTML w Action)
content_mx =
modal_content_mx :: Array (HH.HTML w Action)
modal_content_mx =
[ render_errors
, Bulma.input_with_side_text "domainMX" "Name" "www"
(updateForm Field_Domain)
@ -352,8 +354,8 @@ render state
(maybe "" show state._currentRR.priority)
should_be_disabled
]
content_srv :: Array (HH.HTML w Action)
content_srv =
modal_content_srv :: Array (HH.HTML w Action)
modal_content_srv =
[ render_errors
, Bulma.input_with_side_text "domainSRV" "Name" "www"
(updateForm Field_Domain)
@ -384,9 +386,10 @@ render state
(fromMaybe "tcp" state._currentRR.protocol)
should_be_disabled
]
content_spf :: Array (HH.HTML w Action)
content_spf =
[ render_errors
modal_content_spf :: Array (HH.HTML w Action)
modal_content_spf =
[ Bulma.div_content [Bulma.explanation Explanations.spf_introduction]
, render_errors
, Bulma.input_with_side_text "domainSPF" "Name" "www"
(updateForm Field_Domain)
state._currentRR.name
@ -395,9 +398,9 @@ render state
(updateForm Field_TTL)
(show state._currentRR.ttl)
should_be_disabled
, case state._currentRR.v of
Nothing -> Bulma.p "default value for the version (spf1)"
Just v -> Bulma.box_input "vSPF" "Version" "spf1" (updateForm Field_SPF_v) v should_be_disabled
--, case state._currentRR.v of
-- Nothing -> Bulma.p "default value for the version (spf1)"
-- Just v -> Bulma.box_input "vSPF" "Version" "spf1" (updateForm Field_SPF_v) v should_be_disabled
, Bulma.hr
, maybe (Bulma.p "no mechanism") display_mechanisms state._currentRR.mechanisms
, Bulma.box
@ -424,6 +427,7 @@ render state
, Bulma.hr
, Bulma.box
[ Bulma.h3 "Default behavior"
, Bulma.div_content [Bulma.explanation Explanations.spf_default_behavior]
, Bulma.selection SPF_Qualifier qualifier_types (maybe default_qualifier_str show_qualifier state._currentRR.q)
]
]
@ -770,7 +774,7 @@ render_resources records
"SPF" ->
[ HH.td_ [ Bulma.p rr.name]
, HH.td_ [ Bulma.p $ show rr.ttl ]
, HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ]
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed.
, HH.td_ [ Bulma.p $ maybe "" (A.fold <<< A.intersperse " " <<< map show_mechanism) rr.mechanisms ]
, HH.td_ [ Bulma.p $ maybe "" (A.fold <<< A.intersperse " " <<< map show_modifier) rr.modifiers ]
, HH.td_ [ Bulma.p $ maybe "" fancy_qualifier_display rr.q ]

View File

@ -128,14 +128,12 @@ spf_table_header :: forall w i. HH.HTML w i
spf_table_header
= HH.thead_ [ HH.tr_ [ HH.th_ [ HH.text "Name" ]
, HH.th_ [ HH.text "TTL" ]
, HH.th_ [ HH.text "Version" ]
-- , HH.th_ [ HH.text "Version" ] -- For now, version isn't displayed.
, HH.th_ [ HH.text "Mechanisms" ]
, HH.th_ [ HH.text "Modifiers" ]
, HH.th_ [ HH.text "Default Policy" ]
, HH.th_ [ HH.text "" ]
, HH.th_ [ HH.text "" ]
, HH.th_ [ HH.text "" ]
, HH.th_ [ HH.text "" ]
]
]
@ -479,3 +477,6 @@ div_large_content content = HH.div [HP.classes (C.is_large <> C.content)] conten
div_content :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
div_content content = HH.div [HP.classes (C.content)] content
explanation :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
explanation content = HH.blockquote [HP.classes [HH.ClassName "justified"]] content