WIP: DKIM. Interface is now here, but still very much WIP.
This commit is contained in:
parent
e039daa4ac
commit
682746141a
@ -28,6 +28,9 @@ codec = CA.object "DKIM"
|
|||||||
, n: CAR.optional CA.string
|
, n: CAR.optional CA.string
|
||||||
})
|
})
|
||||||
|
|
||||||
|
emptyDKIMRR :: DKIM
|
||||||
|
emptyDKIMRR = { v: Nothing, k: Just RSA, h: Just SHA256, p: "", n: Nothing }
|
||||||
|
|
||||||
-- RFC6376 section 3.6.2.1
|
-- RFC6376 section 3.6.2.1
|
||||||
-- All DKIM keys are stored in a subdomain named "_domainkey". Given a
|
-- All DKIM keys are stored in a subdomain named "_domainkey". Given a
|
||||||
-- DKIM-Signature field with a "d=" tag of "example.com" and an "s=" tag
|
-- DKIM-Signature field with a "d=" tag of "example.com" and an "s=" tag
|
||||||
@ -35,6 +38,7 @@ codec = CA.object "DKIM"
|
|||||||
-- "foo.bar._domainkey.example.com".
|
-- "foo.bar._domainkey.example.com".
|
||||||
|
|
||||||
data HashingAlgorithm = SHA1 | SHA256
|
data HashingAlgorithm = SHA1 | SHA256
|
||||||
|
hash_algos = ["sha1", "sha256"] :: Array String
|
||||||
|
|
||||||
-- | Codec for just encoding a single value of type `HashingAlgorithm`.
|
-- | Codec for just encoding a single value of type `HashingAlgorithm`.
|
||||||
codecHashingAlgorithm :: CA.JsonCodec HashingAlgorithm
|
codecHashingAlgorithm :: CA.JsonCodec HashingAlgorithm
|
||||||
@ -52,6 +56,7 @@ show_hashing_algorithm = case _ of
|
|||||||
SHA256 -> "sha256"
|
SHA256 -> "sha256"
|
||||||
|
|
||||||
data SignatureAlgorithm = RSA
|
data SignatureAlgorithm = RSA
|
||||||
|
sign_algos = ["rsa"] :: Array String
|
||||||
|
|
||||||
-- | Codec for just encoding a single value of type `SignatureAlgorithm`.
|
-- | Codec for just encoding a single value of type `SignatureAlgorithm`.
|
||||||
codecSignatureAlgorithm :: CA.JsonCodec SignatureAlgorithm
|
codecSignatureAlgorithm :: CA.JsonCodec SignatureAlgorithm
|
||||||
|
@ -2,6 +2,18 @@ module App.Text.Explanations where
|
|||||||
import Halogen.HTML as HH
|
import Halogen.HTML as HH
|
||||||
import Bulma as Bulma
|
import Bulma as Bulma
|
||||||
|
|
||||||
|
dkim_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
|
dkim_introduction =
|
||||||
|
[ Bulma.p """
|
||||||
|
DKIM is a way to share a public signature key for the domain.
|
||||||
|
This allows emails to be signed by the sender, and for the receiver to prove the origin of the mail.
|
||||||
|
"""
|
||||||
|
, Bulma.p """
|
||||||
|
Default values should be fine (RSA + SHA256), change them only if you know what you are doing.
|
||||||
|
Just enter your public key.
|
||||||
|
"""
|
||||||
|
]
|
||||||
|
|
||||||
spf_introduction :: forall w i. Array (HH.HTML w i)
|
spf_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
spf_introduction =
|
spf_introduction =
|
||||||
[ HH.p []
|
[ HH.p []
|
||||||
|
@ -50,7 +50,7 @@ import App.ResourceRecord (ResourceRecord, emptyRR
|
|||||||
, all_qualifiers
|
, all_qualifiers
|
||||||
, mechanism_types, qualifier_types, modifier_types)
|
, mechanism_types, qualifier_types, modifier_types)
|
||||||
import App.ResourceRecord (Mechanism, Modifier, Qualifier(..)) as RR
|
import App.ResourceRecord (Mechanism, Modifier, Qualifier(..)) as RR
|
||||||
import App.DKIM (show_hashing_algorithm, show_signature_algorithm)
|
import App.DKIM as DKIM
|
||||||
|
|
||||||
import App.DisplayErrors (error_to_paragraph)
|
import App.DisplayErrors (error_to_paragraph)
|
||||||
|
|
||||||
@ -170,6 +170,11 @@ data Action
|
|||||||
-- | Add a SPF modifier to the currently modified (SPF) entry (see `_currentRR`).
|
-- | Add a SPF modifier to the currently modified (SPF) entry (see `_currentRR`).
|
||||||
| SPF_Modifier_Add
|
| SPF_Modifier_Add
|
||||||
|
|
||||||
|
| DKIM_hash_algo Int
|
||||||
|
| DKIM_sign_algo Int
|
||||||
|
| DKIM_pubkey String
|
||||||
|
| DKIM_note String
|
||||||
|
|
||||||
data RRModal
|
data RRModal
|
||||||
= NoModal
|
= NoModal
|
||||||
| NewRRModal AcceptedRRTypes
|
| NewRRModal AcceptedRRTypes
|
||||||
@ -223,6 +228,8 @@ type State =
|
|||||||
, spf_modifier_t :: String
|
, spf_modifier_t :: String
|
||||||
, spf_modifier_v :: String
|
, spf_modifier_v :: String
|
||||||
|
|
||||||
|
, dkim :: DKIM.DKIM
|
||||||
|
|
||||||
, _zonefile :: Maybe String
|
, _zonefile :: Maybe String
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -272,6 +279,7 @@ initialState domain =
|
|||||||
, spf_mechanism_v: ""
|
, spf_mechanism_v: ""
|
||||||
, spf_modifier_t: "redirect"
|
, spf_modifier_t: "redirect"
|
||||||
, spf_modifier_v: ""
|
, spf_modifier_v: ""
|
||||||
|
, dkim: DKIM.emptyDKIMRR
|
||||||
}
|
}
|
||||||
|
|
||||||
type SortableRecord l = Record (rrtype :: String, rrid :: Int | l)
|
type SortableRecord l = Record (rrtype :: String, rrid :: Int | l)
|
||||||
@ -446,47 +454,32 @@ render state
|
|||||||
]
|
]
|
||||||
modal_content_dkim :: Array (HH.HTML w Action)
|
modal_content_dkim :: Array (HH.HTML w Action)
|
||||||
modal_content_dkim =
|
modal_content_dkim =
|
||||||
[ Bulma.p "HELLO THIS IS Work-In-Progress. 😂"]
|
[ Bulma.div_content [Bulma.explanation Explanations.dkim_introduction]
|
||||||
---- [ Bulma.div_content [Bulma.explanation Explanations.dkim_introduction]
|
, render_errors
|
||||||
--[ render_errors
|
, Bulma.input_with_side_text "domainDKIM" "Name" "default._domainkey"
|
||||||
--, Bulma.input_with_side_text "domainDKIM" "Name" "Let this alone."
|
(updateForm Field_Domain)
|
||||||
-- (updateForm Field_Domain)
|
state._currentRR.name
|
||||||
-- state._currentRR.name
|
display_domain_side
|
||||||
-- display_domain_side
|
, Bulma.box_input "ttlDKIM" "TTL" "600"
|
||||||
--, Bulma.box_input "ttlDKIM" "TTL" "600"
|
(updateForm Field_TTL)
|
||||||
-- (updateForm Field_TTL)
|
(show state._currentRR.ttl)
|
||||||
-- (show state._currentRR.ttl)
|
should_be_disabled
|
||||||
-- should_be_disabled
|
, Bulma.hr
|
||||||
--, Bulma.hr
|
, Bulma.selection_field "idDKIMSignature" "Signature algo"
|
||||||
--, maybe (Bulma.p "no mechanism") display_mechanisms state._currentRR.mechanisms
|
DKIM_sign_algo
|
||||||
--, Bulma.box
|
DKIM.sign_algos
|
||||||
-- [ Bulma.h3 "New mechanism"
|
(DKIM.show_signature_algorithm $ fromMaybe DKIM.RSA state.dkim.k)
|
||||||
-- , Bulma.selection_field "idMechanismQ" "Policy" DKIM_Mechanism_q qualifier_types state.spf_mechanism_q
|
, Bulma.selection_field "idDKIMHash" "Hash algo"
|
||||||
-- , Bulma.selection_field "idMechanismT" "Type" DKIM_Mechanism_t mechanism_types state.spf_mechanism_t
|
DKIM_hash_algo
|
||||||
-- , Bulma.box_input "valueNewMechanismDKIM" "Value" ""
|
DKIM.hash_algos
|
||||||
-- DKIM_Mechanism_v
|
(DKIM.show_hashing_algorithm $ fromMaybe DKIM.SHA256 state.dkim.h)
|
||||||
-- state.spf_mechanism_v
|
, Bulma.box_input "pkDKIM" "Public Key" "Your public key, such as 'MIIBIjANBgqh...'"
|
||||||
-- should_be_disabled
|
DKIM_pubkey state.dkim.p should_be_disabled
|
||||||
-- , Bulma.btn "Add" DKIM_Mechanism_Add
|
, Bulma.box_input "noteDKIM" "Note" "Note for fellow administrators."
|
||||||
-- ]
|
DKIM_note
|
||||||
--, Bulma.hr
|
(fromMaybe "" state.dkim.n)
|
||||||
--, maybe (Bulma.p "no modifier") display_modifiers state._currentRR.modifiers
|
should_be_disabled
|
||||||
--, Bulma.box
|
]
|
||||||
-- [ Bulma.h3 "New modifier"
|
|
||||||
-- , Bulma.selection_field "idModifierT" "Modifier" DKIM_Modifier_t modifier_types state.spf_modifier_t
|
|
||||||
-- , Bulma.box_input "valueNewModifierDKIM" "Value" ""
|
|
||||||
-- DKIM_Modifier_v
|
|
||||||
-- state.spf_modifier_v
|
|
||||||
-- should_be_disabled
|
|
||||||
-- , Bulma.btn "Add" DKIM_Modifier_Add
|
|
||||||
-- ]
|
|
||||||
--, Bulma.hr
|
|
||||||
--, Bulma.box
|
|
||||||
-- [ Bulma.h3 "Default behavior"
|
|
||||||
-- , Bulma.div_content [Bulma.explanation Explanations.spf_default_behavior]
|
|
||||||
-- , Bulma.selection DKIM_Qualifier qualifier_types (maybe default_qualifier_str show_qualifier state._currentRR.q)
|
|
||||||
-- ]
|
|
||||||
--]
|
|
||||||
|
|
||||||
display_domain_side = (if state._currentRR.name == (state._domain <> ".") then "" else "." <> state._domain)
|
display_domain_side = (if state._currentRR.name == (state._domain <> ".") then "" else "." <> state._domain)
|
||||||
should_be_disabled = (if true then (HP.enabled true) else (HP.disabled true))
|
should_be_disabled = (if true then (HP.enabled true) else (HP.disabled true))
|
||||||
@ -541,7 +534,7 @@ handleAction = case _ of
|
|||||||
, mechanisms = Just default_mechanisms
|
, mechanisms = Just default_mechanisms
|
||||||
, q = Just RR.HardFail
|
, q = Just RR.HardFail
|
||||||
}
|
}
|
||||||
default_rr_DKIM = emptyRR { rrtype = "DKIM", name = "_default._dkim", target = "" }
|
default_rr_DKIM = emptyRR { rrtype = "DKIM", name = "default._domainkey", target = "" }
|
||||||
|
|
||||||
case t of
|
case t of
|
||||||
A -> H.modify_ _ { _currentRR = default_rr_A }
|
A -> H.modify_ _ { _currentRR = default_rr_A }
|
||||||
@ -675,7 +668,15 @@ handleAction = case _ of
|
|||||||
[] -> Nothing
|
[] -> Nothing
|
||||||
v -> Just v
|
v -> Just v
|
||||||
H.modify_ _ { _currentRR { modifiers = new_value }}
|
H.modify_ _ { _currentRR { modifiers = new_value }}
|
||||||
|
|
||||||
|
DKIM_hash_algo v -> H.modify_ _ { dkim { h = mod_dkim_h v } }
|
||||||
|
DKIM_sign_algo v -> H.modify_ _ { dkim { k = mod_dkim_k v } }
|
||||||
|
DKIM_pubkey v -> H.modify_ _ { dkim { p = v } }
|
||||||
|
DKIM_note v -> H.modify_ _ { dkim { n = Just v } }
|
||||||
|
|
||||||
where
|
where
|
||||||
|
mod_dkim_h v = DKIM.str_to_hashing_algorithm $ fromMaybe "sha256" $ DKIM.hash_algos A.!! v
|
||||||
|
mod_dkim_k v = DKIM.str_to_signature_algorithm $ fromMaybe "rsa" $ DKIM.sign_algos A.!! v
|
||||||
-- In case the `name` part of the resource record is empty replace it with the domain name.
|
-- In case the `name` part of the resource record is empty replace it with the domain name.
|
||||||
replace_name domain rr = case rr.name of
|
replace_name domain rr = case rr.name of
|
||||||
"" -> rr { name = domain <> "." }
|
"" -> rr { name = domain <> "." }
|
||||||
@ -855,9 +856,9 @@ render_resources records
|
|||||||
Just dkim ->
|
Just dkim ->
|
||||||
[
|
[
|
||||||
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DKIM1.
|
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DKIM1.
|
||||||
HH.td_ [ Bulma.p $ maybe "" show_hashing_algorithm dkim.h ]
|
HH.td_ [ Bulma.p $ maybe "" DKIM.show_hashing_algorithm dkim.h ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show_signature_algorithm dkim.k ]
|
, HH.td_ [ Bulma.p $ maybe "" DKIM.show_signature_algorithm dkim.k ]
|
||||||
, HH.td_ [ Bulma.p dkim.p ]
|
, HH.td_ [ Bulma.p dkim.p ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Bulma.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid) ]
|
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid) ]
|
||||||
|
@ -189,7 +189,7 @@ textarea action value validity
|
|||||||
]
|
]
|
||||||
|
|
||||||
btn_modify :: forall w i. i -> HH.HTML w i
|
btn_modify :: forall w i. i -> HH.HTML w i
|
||||||
btn_modify action = btn_ (C.is_small <> C.is_info) "modify" action
|
btn_modify action = btn_ (C.is_small <> C.is_info) "⚒" action
|
||||||
|
|
||||||
btn_save :: forall w i. i -> HH.HTML w i
|
btn_save :: forall w i. i -> HH.HTML w i
|
||||||
btn_save action = btn_ C.is_info "Save" action
|
btn_save action = btn_ C.is_info "Save" action
|
||||||
@ -198,7 +198,7 @@ btn_add :: forall w i. i -> HH.HTML w i
|
|||||||
btn_add action = btn_ C.is_info "Add" action
|
btn_add action = btn_ C.is_info "Add" action
|
||||||
|
|
||||||
btn_delete :: forall w i. i -> HH.HTML w i
|
btn_delete :: forall w i. i -> HH.HTML w i
|
||||||
btn_delete action = btn_ (C.is_small <> C.is_danger) "remove" action
|
btn_delete action = btn_ (C.is_small <> C.is_danger) "✖" action
|
||||||
|
|
||||||
btn_modify_ro :: forall w i. HH.HTML w i
|
btn_modify_ro :: forall w i. HH.HTML w i
|
||||||
btn_modify_ro = btn_ro (C.is_small <> C.is_warning) "modify"
|
btn_modify_ro = btn_ro (C.is_small <> C.is_warning) "modify"
|
||||||
|
Loading…
Reference in New Issue
Block a user