Removing Bulma from pages.
This commit is contained in:
parent
2555a0ffc9
commit
138488e52c
14 changed files with 629 additions and 565 deletions
|
@ -45,7 +45,7 @@ module App.Container where
|
||||||
|
|
||||||
import Prelude (Unit, bind, discard, unit, ($), (=<<), (<>), show, pure, (+), (&&), (>))
|
import Prelude (Unit, bind, discard, unit, ($), (=<<), (<>), show, pure, (+), (&&), (>))
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import Data.Array as A
|
import Data.Array as A
|
||||||
import Data.ArrayBuffer.Types (ArrayBuffer)
|
import Data.ArrayBuffer.Types (ArrayBuffer)
|
||||||
|
@ -299,9 +299,9 @@ render state
|
||||||
Migration -> render_migration
|
Migration -> render_migration
|
||||||
LegalNotice -> render_legal_notice
|
LegalNotice -> render_legal_notice
|
||||||
-- The footer includes logs and both the WS child components.
|
-- The footer includes logs and both the WS child components.
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.columns_ [ Bulma.column_ [ Bulma.h3 "Logs (watch this if something fails 😅)", render_logs ]
|
, Style.columns_ [ Style.column_ [ Style.h3 "Logs (watch this if something fails 😅)", render_logs ]
|
||||||
, Bulma.column_ [ Bulma.level
|
, Style.column_ [ Style.level
|
||||||
[ render_auth_WS
|
[ render_auth_WS
|
||||||
, render_dnsmanager_WS
|
, render_dnsmanager_WS
|
||||||
, legal_notice_btn
|
, legal_notice_btn
|
||||||
|
@ -317,12 +317,12 @@ render state
|
||||||
migration_warning :: forall w. HH.HTML w Action
|
migration_warning :: forall w. HH.HTML w Action
|
||||||
migration_warning =
|
migration_warning =
|
||||||
HH.div [HP.classes [C.notification, C.is_warning]]
|
HH.div [HP.classes [C.notification, C.is_warning]]
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
⚠️ (FR) le service a été migré d'une ancienne base de code récemment.
|
⚠️ (FR) le service a été migré d'une ancienne base de code récemment.
|
||||||
Le développement se poursuit mais le service devrait être stable, mis à part quelques redémarrages de temps à autre.
|
Le développement se poursuit mais le service devrait être stable, mis à part quelques redémarrages de temps à autre.
|
||||||
Merci de nous contacter si vous voyez une erreur.
|
Merci de nous contacter si vous voyez une erreur.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
⚠️ (EN) migration from old codebase was performed.
|
⚠️ (EN) migration from old codebase was performed.
|
||||||
Development is still on-going but the service should be fairly stable.
|
Development is still on-going but the service should be fairly stable.
|
||||||
Reboots will happen on occasion.
|
Reboots will happen on occasion.
|
||||||
|
@ -335,23 +335,23 @@ render state
|
||||||
case state.user_data of
|
case state.user_data of
|
||||||
Just (Tuple Nothing _) ->
|
Just (Tuple Nothing _) ->
|
||||||
HH.div [HP.classes [C.notification, C.is_warning]]
|
HH.div [HP.classes [C.notification, C.is_warning]]
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
⚠️ MIGRATION (FR): veuillez indiquer une adresse email pour votre compte.
|
⚠️ MIGRATION (FR): veuillez indiquer une adresse email pour votre compte.
|
||||||
Tout compte sans adresse email sera supprimé sous 6 mois.
|
Tout compte sans adresse email sera supprimé sous 6 mois.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
⚠️ MIGRATION (EN): please associate an email address to your account.
|
⚠️ MIGRATION (EN): please associate an email address to your account.
|
||||||
Accounts without a validated email address will be discarded within 6 months.
|
Accounts without a validated email address will be discarded within 6 months.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
_ -> HH.text ""
|
_ -> HH.text ""
|
||||||
|
|
||||||
legal_notice_btn = Bulma.btn_ [] "Legal notice" (Routing LegalNotice)
|
legal_notice_btn = Style.btn_ [] "Legal notice" (Routing LegalNotice)
|
||||||
reconnection_bar :: forall w. HH.HTML w Action
|
reconnection_bar :: forall w. HH.HTML w Action
|
||||||
reconnection_bar =
|
reconnection_bar =
|
||||||
if (state.are_we_connected_to_authd && state.are_we_connected_to_dnsmanagerd)
|
if (state.are_we_connected_to_authd && state.are_we_connected_to_dnsmanagerd)
|
||||||
then HH.div_ []
|
then HH.div_ []
|
||||||
else Bulma.btn_ [C.is_large, C.is_danger] "You have been disconnected. Click here to reconnect." Reconnection
|
else Style.btn_ [C.is_large, C.is_danger] "You have been disconnected. Click here to reconnect." Reconnection
|
||||||
render_auth_WS :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_auth_WS :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_auth_WS = HH.slot _ws_auth unit WS.component (Tuple wsURLauthd "authd") AuthenticationDaemonEvent
|
render_auth_WS = HH.slot _ws_auth unit WS.component (Tuple wsURLauthd "authd") AuthenticationDaemonEvent
|
||||||
|
|
||||||
|
@ -361,8 +361,8 @@ render state
|
||||||
render_notifications =
|
render_notifications =
|
||||||
case state.notif of
|
case state.notif of
|
||||||
NoNotification -> HH.div_ []
|
NoNotification -> HH.div_ []
|
||||||
GoodNotification v -> Bulma.box [Bulma.notification_success v CloseNotif]
|
GoodNotification v -> Style.box [Style.notification_success v CloseNotif]
|
||||||
BadNotification v -> Bulma.box [Bulma.notification_danger v CloseNotif]
|
BadNotification v -> Style.box [Style.notification_danger v CloseNotif]
|
||||||
|
|
||||||
render_home :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_home :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_home = HH.slot_ _ho unit HomeInterface.component unit
|
render_home = HH.slot_ _ho unit HomeInterface.component unit
|
||||||
|
@ -375,7 +375,7 @@ render state
|
||||||
render_setup :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_setup :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_setup = case state.user_data of
|
render_setup = case state.user_data of
|
||||||
Just user_data -> HH.slot _setupi unit SetupInterface.component user_data SetupInterfaceEvent
|
Just user_data -> HH.slot _setupi unit SetupInterface.component user_data SetupInterfaceEvent
|
||||||
Nothing -> Bulma.p "You shouldn't see this page. Please, reconnect."
|
Nothing -> Style.p "You shouldn't see this page. Please, reconnect."
|
||||||
render_mail_validation :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_mail_validation :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_mail_validation = HH.slot _mvi unit MVI.component unit MailValidationInterfaceEvent
|
render_mail_validation = HH.slot _mvi unit MVI.component unit MailValidationInterfaceEvent
|
||||||
render_zone :: forall monad. String -> MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_zone :: forall monad. String -> MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
|
@ -388,8 +388,8 @@ render state
|
||||||
|
|
||||||
render_legal_notice :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_legal_notice :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_legal_notice
|
render_legal_notice
|
||||||
= Bulma.section_small [ Explanations.legal_notice
|
= Style.section_small [ Explanations.legal_notice
|
||||||
, Bulma.btn_ [C.is_large, C.margin_top 3, C.is_info] "Home page" (Routing Home)
|
, Style.btn_ [C.is_large, C.margin_top 3, C.is_info] "Home page" (Routing Home)
|
||||||
]
|
]
|
||||||
|
|
||||||
render_nav :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_nav :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
|
@ -409,7 +409,7 @@ render state
|
||||||
]
|
]
|
||||||
|
|
||||||
render_logs :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
render_logs :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
|
||||||
render_logs = Bulma.container [ HH.slot_ _log unit AppLog.component unit ]
|
render_logs = Style.container [ HH.slot_ _log unit AppLog.component unit ]
|
||||||
|
|
||||||
ref_paypal_div :: H.RefLabel
|
ref_paypal_div :: H.RefLabel
|
||||||
ref_paypal_div = H.RefLabel "paypal-div"
|
ref_paypal_div = H.RefLabel "paypal-div"
|
||||||
|
|
|
@ -15,37 +15,37 @@ import App.Validation.Label as ValidationLabel
|
||||||
import GenericParser.DomainParser.Common (DomainError(..)) as DomainParser
|
import GenericParser.DomainParser.Common (DomainError(..)) as DomainParser
|
||||||
import GenericParser.IPAddress as IPAddress
|
import GenericParser.IPAddress as IPAddress
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
error_to_paragraph :: forall w i. ValidationDNS.Error -> HH.HTML w i
|
error_to_paragraph :: forall w i. ValidationDNS.Error -> HH.HTML w i
|
||||||
error_to_paragraph v = Bulma.error_message (Bulma.p $ show_error_title v)
|
error_to_paragraph v = Style.error_message (Style.p $ show_error_title v)
|
||||||
(case v of
|
(case v of
|
||||||
ValidationDNS.UNKNOWN -> Bulma.p "An internal error happened."
|
ValidationDNS.UNKNOWN -> Style.p "An internal error happened."
|
||||||
ValidationDNS.VEIPv4 err -> maybe default_error show_error_ip4 err.error
|
ValidationDNS.VEIPv4 err -> maybe default_error show_error_ip4 err.error
|
||||||
ValidationDNS.VEIPv6 err -> maybe default_error show_error_ip6 err.error
|
ValidationDNS.VEIPv6 err -> maybe default_error show_error_ip6 err.error
|
||||||
ValidationDNS.VEName err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VEName err -> maybe default_error show_error_domain err.error
|
||||||
ValidationDNS.VETTL min max n ->
|
ValidationDNS.VETTL min max n ->
|
||||||
Bulma.p $ "TTL should have a value between "
|
Style.p $ "TTL should have a value between "
|
||||||
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
||||||
ValidationDNS.VEDMARCpct min max n ->
|
ValidationDNS.VEDMARCpct min max n ->
|
||||||
Bulma.p $ "DMARC sample rate should have a value between "
|
Style.p $ "DMARC sample rate should have a value between "
|
||||||
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
||||||
ValidationDNS.VEDMARCri min max n ->
|
ValidationDNS.VEDMARCri min max n ->
|
||||||
Bulma.p $ "DMARC report interval should have a value between "
|
Style.p $ "DMARC report interval should have a value between "
|
||||||
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
<> show min <> " and " <> show max <> ", current value: " <> show n <> "."
|
||||||
ValidationDNS.VETXT err -> maybe default_error show_error_txt err.error
|
ValidationDNS.VETXT err -> maybe default_error show_error_txt err.error
|
||||||
ValidationDNS.VECNAME err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VECNAME err -> maybe default_error show_error_domain err.error
|
||||||
ValidationDNS.VENS err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VENS err -> maybe default_error show_error_domain err.error
|
||||||
ValidationDNS.VEMX err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VEMX err -> maybe default_error show_error_domain err.error
|
||||||
ValidationDNS.VEPriority min max n -> Bulma.p $ "Priority should have a value between " <> show min <> " and " <> show max
|
ValidationDNS.VEPriority min max n -> Style.p $ "Priority should have a value between " <> show min <> " and " <> show max
|
||||||
<> ", current value: " <> show n <> "."
|
<> ", current value: " <> show n <> "."
|
||||||
ValidationDNS.VESRV err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VESRV err -> maybe default_error show_error_domain err.error
|
||||||
ValidationDNS.VEPort min max n -> Bulma.p $ "Port should have a value between " <> show min <> " and " <> show max
|
ValidationDNS.VEPort min max n -> Style.p $ "Port should have a value between " <> show min <> " and " <> show max
|
||||||
<> ", current value: " <> show n <> "."
|
<> ", current value: " <> show n <> "."
|
||||||
ValidationDNS.VEWeight min max n -> Bulma.p $ "Weight should have a value between " <> show min <> " and " <> show max
|
ValidationDNS.VEWeight min max n -> Style.p $ "Weight should have a value between " <> show min <> " and " <> show max
|
||||||
<> ", current value: " <> show n <> "."
|
<> ", current value: " <> show n <> "."
|
||||||
|
|
||||||
ValidationDNS.VECAAflag min max n -> Bulma.p $ "CAA flag should have a value between " <> show min <> " and " <> show max
|
ValidationDNS.VECAAflag min max n -> Style.p $ "CAA flag should have a value between " <> show min <> " and " <> show max
|
||||||
<> ", current value: " <> show n <> "."
|
<> ", current value: " <> show n <> "."
|
||||||
|
|
||||||
-- SPF dedicated RR
|
-- SPF dedicated RR
|
||||||
|
@ -56,13 +56,13 @@ error_to_paragraph v = Bulma.error_message (Bulma.p $ show_error_title v)
|
||||||
|
|
||||||
ValidationDNS.DKIMInvalidKeySize min max -> show_error_key_sizes min max
|
ValidationDNS.DKIMInvalidKeySize min max -> show_error_key_sizes min max
|
||||||
)
|
)
|
||||||
where default_error = Bulma.p ""
|
where default_error = Style.p ""
|
||||||
|
|
||||||
show_error_key_sizes :: forall w i. Int -> Int -> HH.HTML w i
|
show_error_key_sizes :: forall w i. Int -> Int -> HH.HTML w i
|
||||||
show_error_key_sizes min max
|
show_error_key_sizes min max
|
||||||
= if min == max
|
= if min == max
|
||||||
then Bulma.p $ "Chosen signature algorithm only accepts public key input of " <> show min <> " characters."
|
then Style.p $ "Chosen signature algorithm only accepts public key input of " <> show min <> " characters."
|
||||||
else Bulma.p $ "Chosen signature algorithm only accepts public key input between "
|
else Style.p $ "Chosen signature algorithm only accepts public key input between "
|
||||||
<> show min <> " and " <> show max <> " characters."
|
<> show min <> " and " <> show max <> " characters."
|
||||||
|
|
||||||
-- | `show_error_title` provide a simple title string to display to the user in case of an error with an entry.
|
-- | `show_error_title` provide a simple title string to display to the user in case of an error with an entry.
|
||||||
|
@ -96,12 +96,12 @@ show_error_title v = case v of
|
||||||
show_error_domain :: forall w i. DomainParser.DomainError -> HH.HTML w i
|
show_error_domain :: forall w i. DomainParser.DomainError -> HH.HTML w i
|
||||||
show_error_domain e = case e of
|
show_error_domain e = case e of
|
||||||
DomainParser.LabelTooLarge size ->
|
DomainParser.LabelTooLarge size ->
|
||||||
Bulma.p $ "The label contains too many characters (" <> show size <> ")."
|
Style.p $ "The label contains too many characters (" <> show size <> ")."
|
||||||
DomainParser.DomainTooLarge size ->
|
DomainParser.DomainTooLarge size ->
|
||||||
Bulma.p $ "The domain contains too many characters (" <> show size <> ")."
|
Style.p $ "The domain contains too many characters (" <> show size <> ")."
|
||||||
-- DomainParser.InvalidCharacter
|
-- DomainParser.InvalidCharacter
|
||||||
-- DomainParser.EOFExpected
|
-- DomainParser.EOFExpected
|
||||||
_ -> Bulma.p """
|
_ -> Style.p """
|
||||||
The domain (or label) contains invalid characters.
|
The domain (or label) contains invalid characters.
|
||||||
A domain label should start with a letter,
|
A domain label should start with a letter,
|
||||||
then possibly a series of letters, digits and hyphenations ("-"),
|
then possibly a series of letters, digits and hyphenations ("-"),
|
||||||
|
@ -111,31 +111,31 @@ show_error_domain e = case e of
|
||||||
show_error_ip6 :: forall w i. IPAddress.IPv6Error -> HH.HTML w i
|
show_error_ip6 :: forall w i. IPAddress.IPv6Error -> HH.HTML w i
|
||||||
show_error_ip6 e = case e of
|
show_error_ip6 e = case e of
|
||||||
IPAddress.IP6TooManyHexaDecimalCharacters ->
|
IPAddress.IP6TooManyHexaDecimalCharacters ->
|
||||||
Bulma.p "IP6TooManyHexaDecimalCharacters"
|
Style.p "IP6TooManyHexaDecimalCharacters"
|
||||||
IPAddress.IP6NotEnoughChunks ->
|
IPAddress.IP6NotEnoughChunks ->
|
||||||
Bulma.p """
|
Style.p """
|
||||||
The IPv6 representation is erroneous, it should contain 8 groups of hexadecimal characters or
|
The IPv6 representation is erroneous, it should contain 8 groups of hexadecimal characters or
|
||||||
being shortened with a double ':' character, such as "2000::1".
|
being shortened with a double ':' character, such as "2000::1".
|
||||||
"""
|
"""
|
||||||
IPAddress.IP6TooManyChunks ->
|
IPAddress.IP6TooManyChunks ->
|
||||||
Bulma.p "The IPv6 representation is erroneous. It should contain only up to 8 groups of hexadecimal characters."
|
Style.p "The IPv6 representation is erroneous. It should contain only up to 8 groups of hexadecimal characters."
|
||||||
IPAddress.IP6IrrelevantShortRepresentation ->
|
IPAddress.IP6IrrelevantShortRepresentation ->
|
||||||
Bulma.p "IPv6 address has been unnecessarily shortened (with two ':')."
|
Style.p "IPv6 address has been unnecessarily shortened (with two ':')."
|
||||||
IPAddress.IP6InvalidRange -> Bulma.p "IPv6 address or range isn't valid."
|
IPAddress.IP6InvalidRange -> Style.p "IPv6 address or range isn't valid."
|
||||||
|
|
||||||
show_error_ip4 :: forall w i. IPAddress.IPv4Error -> HH.HTML w i
|
show_error_ip4 :: forall w i. IPAddress.IPv4Error -> HH.HTML w i
|
||||||
show_error_ip4 e = case e of
|
show_error_ip4 e = case e of
|
||||||
IPAddress.IP4NumberTooBig n ->
|
IPAddress.IP4NumberTooBig n ->
|
||||||
Bulma.p $ "IPv4 address contains a number too big (should be between 0 and 255). Current entered number: " <> show n
|
Style.p $ "IPv4 address contains a number too big (should be between 0 and 255). Current entered number: " <> show n
|
||||||
IPAddress.IP4IrrelevantShortRepresentation ->
|
IPAddress.IP4IrrelevantShortRepresentation ->
|
||||||
Bulma.p "IPv4 address has been unnecessarily shortened (with two '.')."
|
Style.p "IPv4 address has been unnecessarily shortened (with two '.')."
|
||||||
IPAddress.IP4InvalidRange -> Bulma.p "IPv4 address or range isn't valid."
|
IPAddress.IP4InvalidRange -> Style.p "IPv4 address or range isn't valid."
|
||||||
|
|
||||||
show_error_txt :: forall w i. ValidationDNS.TXTError -> HH.HTML w i
|
show_error_txt :: forall w i. ValidationDNS.TXTError -> HH.HTML w i
|
||||||
show_error_txt e = case e of
|
show_error_txt e = case e of
|
||||||
ValidationDNS.TXTInvalidCharacter -> Bulma.p "The TXT field contains some invalid characters."
|
ValidationDNS.TXTInvalidCharacter -> Style.p "The TXT field contains some invalid characters."
|
||||||
ValidationDNS.TXTTooLong max n ->
|
ValidationDNS.TXTTooLong max n ->
|
||||||
Bulma.p $ "An TXT field is limited to " <> show max <> " characters (currently there are "
|
Style.p $ "An TXT field is limited to " <> show max <> " characters (currently there are "
|
||||||
<> show n <> " characters)."
|
<> show n <> " characters)."
|
||||||
|
|
||||||
domainerror_string :: DomainParser.DomainError -> String
|
domainerror_string :: DomainParser.DomainError -> String
|
||||||
|
@ -146,14 +146,14 @@ domainerror_string (DomainParser.EOFExpected) = "EOFExpected"
|
||||||
|
|
||||||
-- | This `error_to_paragraph` is designed to go along the `Validation.Label` module.
|
-- | This `error_to_paragraph` is designed to go along the `Validation.Label` module.
|
||||||
error_to_paragraph_label :: forall w i. ValidationLabel.Error -> HH.HTML w i
|
error_to_paragraph_label :: forall w i. ValidationLabel.Error -> HH.HTML w i
|
||||||
error_to_paragraph_label v = Bulma.error_message (Bulma.p $ show_error_title_label v)
|
error_to_paragraph_label v = Style.error_message (Style.p $ show_error_title_label v)
|
||||||
(case v of
|
(case v of
|
||||||
ValidationLabel.ParsingError x -> case x.error of
|
ValidationLabel.ParsingError x -> case x.error of
|
||||||
Nothing -> Bulma.p ""
|
Nothing -> Style.p ""
|
||||||
Just (ValidationLabel.CannotParse err) -> show_error_domain err
|
Just (ValidationLabel.CannotParse err) -> show_error_domain err
|
||||||
Just (ValidationLabel.CannotEntirelyParse) -> Bulma.p "Cannot entirely parse the label."
|
Just (ValidationLabel.CannotEntirelyParse) -> Style.p "Cannot entirely parse the label."
|
||||||
Just (ValidationLabel.Size min max n) ->
|
Just (ValidationLabel.Size min max n) ->
|
||||||
Bulma.p $ "Label size should be between " <> show min <> " and " <> show max
|
Style.p $ "Label size should be between " <> show min <> " and " <> show max
|
||||||
<> " (current size: " <> show n <> ")."
|
<> " (current size: " <> show n <> ")."
|
||||||
)
|
)
|
||||||
|
|
||||||
|
|
|
@ -13,7 +13,7 @@ module App.Page.Administration where
|
||||||
import Prelude (Unit, bind, discard, not, pure, show, ($), (<<<), (<>), (=<<), map, (/=), (==), unit)
|
import Prelude (Unit, bind, discard, not, pure, show, ($), (<<<), (<>), (=<<), map, (/=), (==), unit)
|
||||||
import Data.Eq (class Eq)
|
import Data.Eq (class Eq)
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import Data.Maybe (Maybe(..))
|
import Data.Maybe (Maybe(..))
|
||||||
import Data.Array as A
|
import Data.Array as A
|
||||||
|
@ -128,64 +128,64 @@ initialState _ = { addUserForm: { login: "", admin: false, email: "", pass: "
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { addUserForm, searchUserForm, matching_users, current_tab, orphan_domains }
|
render { addUserForm, searchUserForm, matching_users, current_tab, orphan_domains }
|
||||||
= Bulma.section_small
|
= Style.section_small
|
||||||
[ fancy_tab_bar
|
[ fancy_tab_bar
|
||||||
, case current_tab of
|
, case current_tab of
|
||||||
Home -> Bulma.h3 "Select an action"
|
Home -> Style.h3 "Select an action"
|
||||||
Search -> Bulma.columns_
|
Search -> Style.columns_
|
||||||
[ Bulma.column [C.is 3] [Bulma.article (Bulma.p "Search users") render_searchuser_form]
|
[ Style.column [C.is 3] [Style.article (Style.p "Search users") render_searchuser_form]
|
||||||
, Bulma.column_ [ Bulma.h3 "Result", show_found_users ]
|
, Style.column_ [ Style.h3 "Result", show_found_users ]
|
||||||
]
|
]
|
||||||
Add -> Bulma.columns_
|
Add -> Style.columns_
|
||||||
[ Bulma.column [C.is 5] [Bulma.article (Bulma.p "Add a new user") render_adduser_form] ]
|
[ Style.column [C.is 5] [Style.article (Style.p "Add a new user") render_adduser_form] ]
|
||||||
OrphanDomains -> HH.div_
|
OrphanDomains -> HH.div_
|
||||||
[ Bulma.btn_ [C.is_small] "Get orphan domains" ShowOrphanDomains
|
[ Style.btn_ [C.is_small] "Get orphan domains" ShowOrphanDomains
|
||||||
, show_orphan_domains
|
, show_orphan_domains
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
fancy_tab_bar =
|
fancy_tab_bar =
|
||||||
Bulma.fancy_tabs
|
Style.fancy_tabs
|
||||||
[ Bulma.tab_entry (is_tab_active Home) "Home" (ChangeTab Home)
|
[ Style.tab_entry (is_tab_active Home) "Home" (ChangeTab Home)
|
||||||
, Bulma.tab_entry (is_tab_active Search) "Search" (ChangeTab Search)
|
, Style.tab_entry (is_tab_active Search) "Search" (ChangeTab Search)
|
||||||
, Bulma.tab_entry (is_tab_active Add) "Add" (ChangeTab Add)
|
, Style.tab_entry (is_tab_active Add) "Add" (ChangeTab Add)
|
||||||
, Bulma.tab_entry (is_tab_active OrphanDomains) "OrphanDomains" (ChangeTab OrphanDomains)
|
, Style.tab_entry (is_tab_active OrphanDomains) "OrphanDomains" (ChangeTab OrphanDomains)
|
||||||
]
|
]
|
||||||
is_tab_active tab = current_tab == tab
|
is_tab_active tab = current_tab == tab
|
||||||
|
|
||||||
show_found_users = Bulma.box [ HH.ul_ $ map user_card matching_users ]
|
show_found_users = Style.box [ HH.ul_ $ map user_card matching_users ]
|
||||||
user_card user = HH.li_ [ Bulma.btn_delete (RemoveUser user.uid)
|
user_card user = HH.li_ [ Style.btn_delete (RemoveUser user.uid)
|
||||||
, Bulma.btn_ [C.is_small] user.login (ShowUser user.uid)
|
, Style.btn_ [C.is_small] user.login (ShowUser user.uid)
|
||||||
]
|
]
|
||||||
show_orphan_domains = Bulma.box [ HH.ul_ $ map domain_entry orphan_domains ]
|
show_orphan_domains = Style.box [ HH.ul_ $ map domain_entry orphan_domains ]
|
||||||
domain_entry domain = HH.li_ [ Bulma.btn_delete (RemoveDomain domain)
|
domain_entry domain = HH.li_ [ Style.btn_delete (RemoveDomain domain)
|
||||||
, Bulma.btn_ [C.is_small] domain (ShowDomain domain)
|
, Style.btn_ [C.is_small] domain (ShowDomain domain)
|
||||||
]
|
]
|
||||||
up x = HandleAddUserInput <<< x
|
up x = HandleAddUserInput <<< x
|
||||||
|
|
||||||
render_adduser_form =
|
render_adduser_form =
|
||||||
HH.form
|
HH.form
|
||||||
[ HE.onSubmit PreventSubmit ]
|
[ HE.onSubmit PreventSubmit ]
|
||||||
[ Bulma.box_input "login" "User login" "login" (up ADDUSER_INP_login) addUserForm.login
|
[ Style.box_input "login" "User login" "login" (up ADDUSER_INP_login) addUserForm.login
|
||||||
, Bulma.btn_labeled "adminbtn" "Admin" (show addUserForm.admin) (HandleAddUserInput ADDUSER_toggle_admin)
|
, Style.btn_labeled "adminbtn" "Admin" (show addUserForm.admin) (HandleAddUserInput ADDUSER_toggle_admin)
|
||||||
, Bulma.box_input "email" "User email" "email" (up ADDUSER_INP_email) addUserForm.email
|
, Style.box_input "email" "User email" "email" (up ADDUSER_INP_email) addUserForm.email
|
||||||
, Bulma.box_password "password" "User password" "password" (up ADDUSER_INP_pass) addUserForm.pass
|
, Style.box_password "password" "User password" "password" (up ADDUSER_INP_pass) addUserForm.pass
|
||||||
, Bulma.btn "Send" AddUserAttempt
|
, Style.btn "Send" AddUserAttempt
|
||||||
]
|
]
|
||||||
|
|
||||||
render_searchuser_form =
|
render_searchuser_form =
|
||||||
HH.form
|
HH.form
|
||||||
[ HE.onSubmit PreventSubmit ]
|
[ HE.onSubmit PreventSubmit ]
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Following input accepts any regex.
|
Following input accepts any regex.
|
||||||
This is used to search for a user based on their login, full name or email address.
|
This is used to search for a user based on their login, full name or email address.
|
||||||
"""
|
"""
|
||||||
, Bulma.box_input "regex" "Regex" "regex" (up SEARCHUSER_INP_regex) searchUserForm.regex
|
, Style.box_input "regex" "Regex" "regex" (up SEARCHUSER_INP_regex) searchUserForm.regex
|
||||||
--, Bulma.btn_labeled "adminbtn" "Admin" (show searchUserForm.admin)
|
--, Style.btn_labeled "adminbtn" "Admin" (show searchUserForm.admin)
|
||||||
-- (HandleAddUserInput SEARCHUSER_toggle_admin)
|
-- (HandleAddUserInput SEARCHUSER_toggle_admin)
|
||||||
--, Bulma.box_input "domain" "Domain owned" "blah.netlib.re."
|
--, Style.box_input "domain" "Domain owned" "blah.netlib.re."
|
||||||
-- (up SEARCHUSER_INP_domain) searchUserForm.domain
|
-- (up SEARCHUSER_INP_domain) searchUserForm.domain
|
||||||
, Bulma.btn "Send" SearchUserAttempt
|
, Style.btn "Send" SearchUserAttempt
|
||||||
]
|
]
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
|
|
|
@ -17,7 +17,7 @@ import Halogen.HTML.Events as HE
|
||||||
import Web.Event.Event as Event
|
import Web.Event.Event as Event
|
||||||
import Web.Event.Event (Event)
|
import Web.Event.Event (Event)
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import Web.HTML (window) as HTML
|
import Web.HTML (window) as HTML
|
||||||
import Web.HTML.Window (sessionStorage) as Window
|
import Web.HTML.Window (sessionStorage) as Window
|
||||||
|
@ -135,24 +135,24 @@ component =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { current_tab, authenticationForm, passwordRecoveryForm, newPasswordForm, errors } =
|
render { current_tab, authenticationForm, passwordRecoveryForm, newPasswordForm, errors } =
|
||||||
Bulma.section_small
|
Style.section_small
|
||||||
[ fancy_tab_bar
|
[ fancy_tab_bar
|
||||||
, if A.length errors > 0
|
, if A.length errors > 0
|
||||||
-- then HH.div_ [ Bulma.box [ HH.text (A.fold $ map show_error errors) ] ]
|
-- then HH.div_ [ Style.box [ HH.text (A.fold $ map show_error errors) ] ]
|
||||||
then HH.div_ [ Bulma.box [Bulma.notification_danger (A.fold $ map show_error errors) CloseErrorStuff]]
|
then HH.div_ [ Style.box [Style.notification_danger (A.fold $ map show_error errors) CloseErrorStuff]]
|
||||||
else HH.div_ []
|
else HH.div_ []
|
||||||
, case current_tab of
|
, case current_tab of
|
||||||
Auth -> Bulma.box auth_form
|
Auth -> Style.box auth_form
|
||||||
ILostMyPassword -> Bulma.box passrecovery_form
|
ILostMyPassword -> Style.box passrecovery_form
|
||||||
Recovery -> Bulma.box newpass_form
|
Recovery -> Style.box newpass_form
|
||||||
]
|
]
|
||||||
|
|
||||||
where
|
where
|
||||||
fancy_tab_bar =
|
fancy_tab_bar =
|
||||||
Bulma.fancy_tabs
|
Style.fancy_tabs
|
||||||
[ Bulma.tab_entry (is_tab_active Auth) "Authentication" (ChangeTab Auth)
|
[ Style.tab_entry (is_tab_active Auth) "Authentication" (ChangeTab Auth)
|
||||||
, Bulma.tab_entry (is_tab_active ILostMyPassword) "I lost my password! 😟" (ChangeTab ILostMyPassword)
|
, Style.tab_entry (is_tab_active ILostMyPassword) "I lost my password! 😟" (ChangeTab ILostMyPassword)
|
||||||
, Bulma.tab_entry (is_tab_active Recovery) "Recover with a token" (ChangeTab Recovery)
|
, Style.tab_entry (is_tab_active Recovery) "Recover with a token" (ChangeTab Recovery)
|
||||||
]
|
]
|
||||||
is_tab_active tab = current_tab == tab
|
is_tab_active tab = current_tab == tab
|
||||||
|
|
||||||
|
@ -203,45 +203,45 @@ render { current_tab, authenticationForm, passwordRecoveryForm, newPasswordForm,
|
||||||
<> show min <> " and " <> show max
|
<> show min <> " and " <> show max
|
||||||
<> " (currently: " <> show n <> ")"
|
<> " (currently: " <> show n <> ")"
|
||||||
|
|
||||||
auth_form = [ Bulma.h3 "Authentication", render_auth_form ]
|
auth_form = [ Style.h3 "Authentication", render_auth_form ]
|
||||||
passrecovery_form =
|
passrecovery_form =
|
||||||
[ Bulma.h3 "You forgot your password (or your login)"
|
[ Style.h3 "You forgot your password (or your login)"
|
||||||
, Bulma.div_content []
|
, Style.div_content []
|
||||||
[ Bulma.p "Enter either your login or email and you'll receive a recovery token."
|
[ Style.p "Enter either your login or email and you'll receive a recovery token."
|
||||||
]
|
]
|
||||||
, render_password_recovery_form
|
, render_password_recovery_form
|
||||||
]
|
]
|
||||||
newpass_form =
|
newpass_form =
|
||||||
[ Bulma.h3 "You got the password recovery mail"
|
[ Style.h3 "You got the password recovery mail"
|
||||||
, Bulma.div_content []
|
, Style.div_content []
|
||||||
[ Bulma.p "Nice! You get to choose your new password."
|
[ Style.p "Nice! You get to choose your new password."
|
||||||
]
|
]
|
||||||
, render_new_password_form
|
, render_new_password_form
|
||||||
]
|
]
|
||||||
|
|
||||||
render_auth_form = HH.form
|
render_auth_form = HH.form
|
||||||
[ HE.onSubmit AuthenticationAttempt ]
|
[ HE.onSubmit AuthenticationAttempt ]
|
||||||
[ Bulma.username_input "Username" authenticationForm.login (HandleAuthenticationInput <<< AUTH_INP_login)
|
[ Style.username_input "Username" authenticationForm.login (HandleAuthenticationInput <<< AUTH_INP_login)
|
||||||
, Bulma.password_input "Password" authenticationForm.pass (HandleAuthenticationInput <<< AUTH_INP_pass)
|
, Style.password_input "Password" authenticationForm.pass (HandleAuthenticationInput <<< AUTH_INP_pass)
|
||||||
, Bulma.btn_validation
|
, Style.btn_validation
|
||||||
]
|
]
|
||||||
|
|
||||||
render_password_recovery_form = HH.form
|
render_password_recovery_form = HH.form
|
||||||
[ HE.onSubmit PasswordRecoveryAttempt ]
|
[ HE.onSubmit PasswordRecoveryAttempt ]
|
||||||
[ Bulma.username_input "Username" passwordRecoveryForm.login (HandlePasswordRecovery <<< PASSR_INP_login)
|
[ Style.username_input "Username" passwordRecoveryForm.login (HandlePasswordRecovery <<< PASSR_INP_login)
|
||||||
, Bulma.email_input "Email" passwordRecoveryForm.email (HandlePasswordRecovery <<< PASSR_INP_email)
|
, Style.email_input "Email" passwordRecoveryForm.email (HandlePasswordRecovery <<< PASSR_INP_email)
|
||||||
, Bulma.btn_validation
|
, Style.btn_validation
|
||||||
]
|
]
|
||||||
|
|
||||||
render_new_password_form = HH.form
|
render_new_password_form = HH.form
|
||||||
[ HE.onSubmit NewPasswordAttempt ]
|
[ HE.onSubmit NewPasswordAttempt ]
|
||||||
[ Bulma.username_input "Username" newPasswordForm.login (HandleNewPassword <<< NEWPASS_INP_login)
|
[ Style.username_input "Username" newPasswordForm.login (HandleNewPassword <<< NEWPASS_INP_login)
|
||||||
, Bulma.token_input "Token" newPasswordForm.token (HandleNewPassword <<< NEWPASS_INP_token)
|
, Style.token_input "Token" newPasswordForm.token (HandleNewPassword <<< NEWPASS_INP_token)
|
||||||
, Bulma.password_input_new "Password" newPasswordForm.password (HandleNewPassword <<< NEWPASS_INP_password)
|
, Style.password_input_new "Password" newPasswordForm.password (HandleNewPassword <<< NEWPASS_INP_password)
|
||||||
|
|
||||||
, Bulma.password_input_confirmation "Confirmation" newPasswordForm.confirmation
|
, Style.password_input_confirmation "Confirmation" newPasswordForm.confirmation
|
||||||
(HandleNewPassword <<< NEWPASS_INP_confirmation)
|
(HandleNewPassword <<< NEWPASS_INP_confirmation)
|
||||||
, Bulma.btn_validation
|
, Style.btn_validation
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -27,7 +27,7 @@ import Halogen.HTML.Events as HE
|
||||||
import Halogen.HTML.Events as HHE
|
import Halogen.HTML.Events as HHE
|
||||||
import Web.Event.Event as Event
|
import Web.Event.Event as Event
|
||||||
import Web.Event.Event (Event)
|
import Web.Event.Event (Event)
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import App.DisplayErrors (error_to_paragraph_label)
|
import App.DisplayErrors (error_to_paragraph_label)
|
||||||
|
|
||||||
|
@ -179,49 +179,49 @@ initialState _ =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, deletion_modal }
|
render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, deletion_modal }
|
||||||
= Bulma.section_small
|
= Style.section_small
|
||||||
[ case deletion_modal of
|
[ case deletion_modal of
|
||||||
Nothing -> HH.div_ [ Bulma.columns_ domain_line
|
Nothing -> HH.div_ [ Style.columns_ domain_line
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.columns_ new_domain_line
|
, Style.columns_ new_domain_line
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.columns_ explanations_line
|
, Style.columns_ explanations_line
|
||||||
]
|
]
|
||||||
Just domain -> Bulma.modal "Deleting a domain"
|
Just domain -> Style.modal "Deleting a domain"
|
||||||
[warning_message domain] [modal_delete_button domain, modal_cancel_button]
|
[warning_message domain] [modal_delete_button domain, modal_cancel_button]
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
c = Bulma.column_
|
c = Style.column_
|
||||||
|
|
||||||
domain_line = [ c render_my_domains, c render_my_shared_domains ]
|
domain_line = [ c render_my_domains, c render_my_shared_domains ]
|
||||||
new_domain_line = [ c render_new_domain, c render_gain_ownership ]
|
new_domain_line = [ c render_new_domain, c render_gain_ownership ]
|
||||||
explanations_line = [ c render_share_ownership_explanation, c render_transfer_ownership_explanation ]
|
explanations_line = [ c render_share_ownership_explanation, c render_transfer_ownership_explanation ]
|
||||||
|
|
||||||
render_my_domains =
|
render_my_domains =
|
||||||
[ Bulma.h3 "My domains"
|
[ Style.h3 "My domains"
|
||||||
, Bulma.simple_quote "You are the exclusive owner of the following domains."
|
, Style.simple_quote "You are the exclusive owner of the following domains."
|
||||||
, if A.length domains_i_exclusively_own > 0
|
, if A.length domains_i_exclusively_own > 0
|
||||||
then Bulma.table [] [ Bulma.table_header_owned_domains
|
then Style.table [] [ Style.table_header_owned_domains
|
||||||
, HH.tbody_ $ map owned_domain_row domains_i_exclusively_own
|
, HH.tbody_ $ map owned_domain_row domains_i_exclusively_own
|
||||||
]
|
]
|
||||||
else Bulma.p "No domain yet."
|
else Style.p "No domain yet."
|
||||||
]
|
]
|
||||||
render_my_shared_domains =
|
render_my_shared_domains =
|
||||||
[ Bulma.h3 "Shared domains"
|
[ Style.h3 "Shared domains"
|
||||||
, Bulma.simple_quote """
|
, Style.simple_quote """
|
||||||
The following domains are shared with other users.
|
The following domains are shared with other users.
|
||||||
In case you are the last owner, you can "unshare" it and gain exclusive ownership.
|
In case you are the last owner, you can "unshare" it and gain exclusive ownership.
|
||||||
"""
|
"""
|
||||||
, if A.length domains_i_share > 0
|
, if A.length domains_i_share > 0
|
||||||
then Bulma.table [] [ Bulma.table_header_shared_domains
|
then Style.table [] [ Style.table_header_shared_domains
|
||||||
, HH.tbody_ $ map shared_domain_row domains_i_share
|
, HH.tbody_ $ map shared_domain_row domains_i_share
|
||||||
]
|
]
|
||||||
else Bulma.p "No domain yet."
|
else Style.p "No domain yet."
|
||||||
]
|
]
|
||||||
render_new_domain =
|
render_new_domain =
|
||||||
[ Bulma.h3 "New domain"
|
[ Style.h3 "New domain"
|
||||||
, Bulma.quote [ Bulma.p "The heart of dnsmanager! 🎉"
|
, Style.quote [ Style.p "The heart of dnsmanager! 🎉"
|
||||||
, Bulma.p "You can reserve a domain name, right here."
|
, Style.p "You can reserve a domain name, right here."
|
||||||
, HH.text """
|
, HH.text """
|
||||||
Later you will be able to change the content, share, transfer or even delete the domain.
|
Later you will be able to change the content, share, transfer or even delete the domain.
|
||||||
"""
|
"""
|
||||||
|
@ -230,16 +230,16 @@ render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, del
|
||||||
]
|
]
|
||||||
|
|
||||||
render_gain_ownership =
|
render_gain_ownership =
|
||||||
[ Bulma.h3 "Get the ownership of a domain"
|
[ Style.h3 "Get the ownership of a domain"
|
||||||
, Bulma.simple_quote """
|
, Style.simple_quote """
|
||||||
Someone wants to give you (or share with you) the ownership of a domain.
|
Someone wants to give you (or share with you) the ownership of a domain.
|
||||||
Please enter the UUID of the transfer.
|
Please enter the UUID of the transfer.
|
||||||
"""
|
"""
|
||||||
, render_ask_domain_transfer_form
|
, render_ask_domain_transfer_form
|
||||||
]
|
]
|
||||||
render_share_ownership_explanation =
|
render_share_ownership_explanation =
|
||||||
[ Bulma.h3 "Share the ownership of a domain"
|
[ Style.h3 "Share the ownership of a domain"
|
||||||
, Bulma.simple_quote """
|
, Style.simple_quote """
|
||||||
Ask for a "share token" for your domain and give it to other users.
|
Ask for a "share token" for your domain and give it to other users.
|
||||||
All the owners can make modifications to the domain.
|
All the owners can make modifications to the domain.
|
||||||
Don't let the administration of a domain be the burden of a single person!
|
Don't let the administration of a domain be the burden of a single person!
|
||||||
|
@ -247,14 +247,14 @@ render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, del
|
||||||
]
|
]
|
||||||
|
|
||||||
render_transfer_ownership_explanation =
|
render_transfer_ownership_explanation =
|
||||||
[ Bulma.h3 "Transfer the ownership of a domain"
|
[ Style.h3 "Transfer the ownership of a domain"
|
||||||
, Bulma.simple_quote """
|
, Style.simple_quote """
|
||||||
Ask for a transfer token for your domain and give it to the new owner.
|
Ask for a transfer token for your domain and give it to the new owner.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
modal_delete_button domain = Bulma.alert_btn "Delete the domain" (RemoveDomain domain)
|
modal_delete_button domain = Style.alert_btn "Delete the domain" (RemoveDomain domain)
|
||||||
modal_cancel_button = Bulma.cancel_button CancelModal
|
modal_cancel_button = Style.cancel_button CancelModal
|
||||||
|
|
||||||
-- I own all domain without a "share key".
|
-- I own all domain without a "share key".
|
||||||
domains_i_exclusively_own = A.sort $ A.filter (\domain -> domain.share_key == Nothing) my_domains
|
domains_i_exclusively_own = A.sort $ A.filter (\domain -> domain.share_key == Nothing) my_domains
|
||||||
|
@ -267,37 +267,37 @@ render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, del
|
||||||
<> "\". Are you sure you want to do this? This is "
|
<> "\". Are you sure you want to do this? This is "
|
||||||
, HH.strong_ [ HH.text "irreversible" ]
|
, HH.strong_ [ HH.text "irreversible" ]
|
||||||
, HH.text "."
|
, HH.text "."
|
||||||
, Bulma.notification_warning' """
|
, Style.notification_warning' """
|
||||||
In case this domain is shared, it will just be removed from your domains.
|
In case this domain is shared, it will just be removed from your domains.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
shared_domain_row domain = HH.tr_
|
shared_domain_row domain = HH.tr_
|
||||||
[ HH.td_ [ Bulma.btn domain.name (EnterDomain domain.name) ]
|
[ HH.td_ [ Style.btn domain.name (EnterDomain domain.name) ]
|
||||||
, HH.td_ [ HH.text $ fromMaybe "" domain.share_key ]
|
, HH.td_ [ HH.text $ fromMaybe "" domain.share_key ]
|
||||||
, if A.length domain.owners == 1
|
, if A.length domain.owners == 1
|
||||||
then HH.td_ [ Bulma.alert_btn_abbr "Unshare the domain by removing the \"share\" token." "Unshare" (UnShareDomain domain.name) ]
|
then HH.td_ [ Style.alert_btn_abbr "Unshare the domain by removing the \"share\" token." "Unshare" (UnShareDomain domain.name) ]
|
||||||
else HH.td_ [ Bulma.btn_ro [C.is_warning] "Cannot unshare it" ]
|
else HH.td_ [ Style.btn_ro [C.is_warning] "Cannot unshare it" ]
|
||||||
, HH.td_ [ Bulma.alert_btn_abbr "Delete the domain from your list of owned domains. In case you are the only owner, this will also remove all zone data and the domain won't be served anymore." "Delete" (DeleteDomainModal domain.name) ]
|
, HH.td_ [ Style.alert_btn_abbr "Delete the domain from your list of owned domains. In case you are the only owner, this will also remove all zone data and the domain won't be served anymore." "Delete" (DeleteDomainModal domain.name) ]
|
||||||
]
|
]
|
||||||
|
|
||||||
owned_domain_row domain = HH.tr_
|
owned_domain_row domain = HH.tr_
|
||||||
[ HH.td_ [ Bulma.btn domain.name (EnterDomain domain.name) ]
|
[ HH.td_ [ Style.btn domain.name (EnterDomain domain.name) ]
|
||||||
, case domain.transfer_key of
|
, case domain.transfer_key of
|
||||||
Just key -> HH.td_ [ Bulma.p "Token key:", Bulma.p key ]
|
Just key -> HH.td_ [ Style.p "Token key:", Style.p key ]
|
||||||
Nothing -> HH.td_ [ Bulma.btn_abbr "Generate a token to transfer the ownership of a domain." "Transfer" (TransferDomain domain.name) ]
|
Nothing -> HH.td_ [ Style.btn_abbr "Generate a token to transfer the ownership of a domain." "Transfer" (TransferDomain domain.name) ]
|
||||||
, HH.td_ [ Bulma.btn_abbr "Generate a token to share the ownership of a domain." "Share" (ShareDomain domain.name) ]
|
, HH.td_ [ Style.btn_abbr "Generate a token to share the ownership of a domain." "Share" (ShareDomain domain.name) ]
|
||||||
, HH.td_ [ Bulma.alert_btn_abbr "Delete the domain. This will remove all zone data and the domain won't be served anymore." "Delete" (DeleteDomainModal domain.name) ]
|
, HH.td_ [ Style.alert_btn_abbr "Delete the domain. This will remove all zone data and the domain won't be served anymore." "Delete" (DeleteDomainModal domain.name) ]
|
||||||
]
|
]
|
||||||
|
|
||||||
render_add_domain_form = HH.form
|
render_add_domain_form = HH.form
|
||||||
[ HE.onSubmit NewDomainAttempt ]
|
[ HE.onSubmit NewDomainAttempt ]
|
||||||
[ Bulma.new_domain_field
|
[ Style.new_domain_field
|
||||||
(HandleNewDomainInput <<< INP_newdomain)
|
(HandleNewDomainInput <<< INP_newdomain)
|
||||||
newDomainForm.new_domain
|
newDomainForm.new_domain
|
||||||
[ HHE.onSelectedIndexChange domain_choice ]
|
[ HHE.onSelectedIndexChange domain_choice ]
|
||||||
(map (\v -> "." <> v) accepted_domains)
|
(map (\v -> "." <> v) accepted_domains)
|
||||||
, Bulma.btn_validation_ "add a new domain"
|
, Style.btn_validation_ "add a new domain"
|
||||||
, if A.length newDomainForm._errors > 0
|
, if A.length newDomainForm._errors > 0
|
||||||
then HH.div_ $ map error_to_paragraph_label newDomainForm._errors
|
then HH.div_ $ map error_to_paragraph_label newDomainForm._errors
|
||||||
else HH.div_ [ ]
|
else HH.div_ [ ]
|
||||||
|
@ -305,10 +305,10 @@ render { accepted_domains, my_domains, newDomainForm, askDomainTransferForm, del
|
||||||
|
|
||||||
render_ask_domain_transfer_form = HH.form
|
render_ask_domain_transfer_form = HH.form
|
||||||
[ HE.onSubmit AskDomainTransferAttempt ]
|
[ HE.onSubmit AskDomainTransferAttempt ]
|
||||||
[ Bulma.box_input "idTransferToken" "Token" "UUID of the domain"
|
[ Style.box_input "idTransferToken" "Token" "UUID of the domain"
|
||||||
AskDomainTransferUUIDInput
|
AskDomainTransferUUIDInput
|
||||||
askDomainTransferForm.uuid
|
askDomainTransferForm.uuid
|
||||||
, Bulma.btn_validation_ "ask for a domain transfer"
|
, Style.btn_validation_ "ask for a domain transfer"
|
||||||
, if A.length askDomainTransferForm._errors > 0
|
, if A.length askDomainTransferForm._errors > 0
|
||||||
then HH.div_ $ map error_to_paragraph_label askDomainTransferForm._errors
|
then HH.div_ $ map error_to_paragraph_label askDomainTransferForm._errors
|
||||||
else HH.div_ [ ]
|
else HH.div_ [ ]
|
||||||
|
|
|
@ -13,7 +13,7 @@ import Halogen.HTML as HH
|
||||||
import Halogen.HTML.Properties as HP
|
import Halogen.HTML.Properties as HP
|
||||||
|
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
type Input = Unit
|
type Input = Unit
|
||||||
type Action = Unit
|
type Action = Unit
|
||||||
|
@ -41,38 +41,38 @@ initialState _ = unit
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render _ = HH.div_
|
render _ = HH.div_
|
||||||
[ Bulma.hero_danger
|
[ Style.hero_danger
|
||||||
-- "THIS IS A BETA RELEASE"
|
-- "THIS IS A BETA RELEASE"
|
||||||
-- "You can register, login and play a bit with the tool. Feel free to report errors and suggestions."
|
-- "You can register, login and play a bit with the tool. Feel free to report errors and suggestions."
|
||||||
[ HH.text "MESSAGE DE MIGRATION" ]
|
[ HH.text "MESSAGE DE MIGRATION" ]
|
||||||
[ Bulma.p "En bref : le site a été refait à neuf, en anglais (une traduction arrivera… un jour), et les comptes ont été migrés."
|
[ Style.p "En bref : le site a été refait à neuf, en anglais (une traduction arrivera… un jour), et les comptes ont été migrés."
|
||||||
, Bulma.p "Les utilisateurs peuvent se connecter avec leurs identifiants habituels et leurs domaines sont toujours attribués, mais le contenu n'a pas été préservé (il faut re-configurer les zones)."
|
, Style.p "Les utilisateurs peuvent se connecter avec leurs identifiants habituels et leurs domaines sont toujours attribués, mais le contenu n'a pas été préservé (il faut re-configurer les zones)."
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Les comptes migrés sont conservés 6 mois, puis supprimés si aucune connexion n'est faite,
|
Les comptes migrés sont conservés 6 mois, puis supprimés si aucune connexion n'est faite,
|
||||||
afin de purger un certain nombre de vieux comptes de robots.
|
afin de purger un certain nombre de vieux comptes de robots.
|
||||||
"""
|
"""
|
||||||
, HH.p [ HP.classes [C.margin_top 3] ]
|
, HH.p [ HP.classes [C.margin_top 3] ]
|
||||||
[ Bulma.outside_link [C.button, C.is_info] url_linuxfr "Article linuxfr.org présentant la nouvelle version de netlibre" ]
|
[ Style.outside_link [C.button, C.is_info] url_linuxfr "Article linuxfr.org présentant la nouvelle version de netlibre" ]
|
||||||
]
|
]
|
||||||
, Bulma.section_small
|
, Style.section_small
|
||||||
[ Bulma.h1 "Welcome to netlib.re"
|
[ Style.h1 "Welcome to netlib.re"
|
||||||
, Bulma.subtitle "Free domain names for the common folks"
|
, Style.subtitle "Free domain names for the common folks"
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, render_description
|
, render_description
|
||||||
, render_update_why_and_contact
|
, render_update_why_and_contact
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, render_how_and_code
|
, render_how_and_code
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
url_linuxfr = "https://linuxfr.org/news/netlibre-un-service-libre-et-un-nom-de-domaine-gratuit"
|
url_linuxfr = "https://linuxfr.org/news/netlibre-un-service-libre-et-un-nom-de-domaine-gratuit"
|
||||||
title = Bulma.h3
|
title = Style.h3
|
||||||
expl content = Bulma.div_content [] [ Bulma.explanation content ]
|
expl content = Style.div_content [] [ Style.explanation content ]
|
||||||
p = Bulma.p
|
p = Style.p
|
||||||
b x = Bulma.column_ [ Bulma.box [ Bulma.div_content [] x ] ]
|
b x = Style.column_ [ Style.box [ Style.div_content [] x ] ]
|
||||||
|
|
||||||
render_description = Bulma.columns_ [ render_basics, render_no_expert, render_no_housing ]
|
render_description = Style.columns_ [ render_basics, render_no_expert, render_no_housing ]
|
||||||
render_update_why_and_contact = Bulma.columns_ [ render_updates, render_why, render_contact ]
|
render_update_why_and_contact = Style.columns_ [ render_updates, render_why, render_contact ]
|
||||||
|
|
||||||
render_basics
|
render_basics
|
||||||
= b [ title "What is provided?"
|
= b [ title "What is provided?"
|
||||||
|
@ -96,7 +96,7 @@ render _ = HH.div_
|
||||||
render_updates
|
render_updates
|
||||||
= b [ title "Automatic updates"
|
= b [ title "Automatic updates"
|
||||||
, p "Update your records with a single, stupidly simple command. For example:"
|
, p "Update your records with a single, stupidly simple command. For example:"
|
||||||
, expl [ Bulma.strong "wget https://www.netlib.re/token-update/<token>" ]
|
, expl [ Style.strong "wget https://www.netlib.re/token-update/<token>" ]
|
||||||
, p "Every A and AAAA records have tokens for easy updates."
|
, p "Every A and AAAA records have tokens for easy updates."
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -112,7 +112,7 @@ render _ = HH.div_
|
||||||
, p "For legal matter: abuse@netlib.re"
|
, p "For legal matter: abuse@netlib.re"
|
||||||
]
|
]
|
||||||
|
|
||||||
render_how_and_code = Bulma.columns_ [ render_how, render_code ]
|
render_how_and_code = Style.columns_ [ render_how, render_code ]
|
||||||
render_how
|
render_how
|
||||||
= b [ title "How does this work?"
|
= b [ title "How does this work?"
|
||||||
, p "We pay for the domain names (netlib.re and codelib.re) and let you have a subdomain."
|
, p "We pay for the domain names (netlib.re and codelib.re) and let you have a subdomain."
|
||||||
|
@ -137,8 +137,8 @@ render _ = HH.div_
|
||||||
this user-friendly website, so you can manage your zones. 🥰
|
this user-friendly website, so you can manage your zones. 🥰
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.p "But of course, there are a few more technical parts:"
|
, Style.p "But of course, there are a few more technical parts:"
|
||||||
, HH.ul_
|
, HH.ul_
|
||||||
[ link "https://git.baguette.netlib.re/Baguette/libipc" "libIPC"
|
[ link "https://git.baguette.netlib.re/Baguette/libipc" "libIPC"
|
||||||
"""
|
"""
|
||||||
|
@ -154,4 +154,4 @@ render _ = HH.div_
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
link url link_title content
|
link url link_title content
|
||||||
= HH.li_ [ Bulma.outside_link [] url link_title, HH.text ", ", HH.text content ]
|
= HH.li_ [ Style.outside_link [] url link_title, HH.text ", ", HH.text content ]
|
||||||
|
|
|
@ -16,7 +16,7 @@ import Halogen.HTML.Events as HE
|
||||||
import Web.Event.Event as Event
|
import Web.Event.Event as Event
|
||||||
import Web.Event.Event (Event)
|
import Web.Event.Event (Event)
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import App.Type.LogMessage
|
import App.Type.LogMessage
|
||||||
import App.Message.AuthenticationDaemon as AuthD
|
import App.Message.AuthenticationDaemon as AuthD
|
||||||
|
@ -82,21 +82,21 @@ initialState _ =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { mailValidationForm }
|
render { mailValidationForm }
|
||||||
= Bulma.section_small [ Bulma.columns_ [ b mail_validation_form ] ]
|
= Style.section_small [ Style.columns_ [ b mail_validation_form ] ]
|
||||||
|
|
||||||
where
|
where
|
||||||
b e = Bulma.column_ [ Bulma.box e ]
|
b e = Style.column_ [ Style.box e ]
|
||||||
mail_validation_form
|
mail_validation_form
|
||||||
= [ Bulma.h3 "Verify your account"
|
= [ Style.h3 "Verify your account"
|
||||||
, Bulma.div_content [] [Bulma.explanation [Bulma.p "Email addresses must be validated within 30 minutes."]]
|
, Style.div_content [] [Style.explanation [Style.p "Email addresses must be validated within 30 minutes."]]
|
||||||
, render_register_form
|
, render_register_form
|
||||||
]
|
]
|
||||||
|
|
||||||
render_register_form = HH.form
|
render_register_form = HH.form
|
||||||
[ HE.onSubmit ValidateInputs ]
|
[ HE.onSubmit ValidateInputs ]
|
||||||
[ Bulma.username_input "Username" mailValidationForm.login (HandleValidationInput <<< VALIDATION_INP_login)
|
[ Style.username_input "Username" mailValidationForm.login (HandleValidationInput <<< VALIDATION_INP_login)
|
||||||
, Bulma.token_input "Token" mailValidationForm.token (HandleValidationInput <<< VALIDATION_INP_token)
|
, Style.token_input "Token" mailValidationForm.token (HandleValidationInput <<< VALIDATION_INP_token)
|
||||||
, Bulma.btn_validation
|
, Style.btn_validation
|
||||||
]
|
]
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
|
|
|
@ -36,7 +36,7 @@ import Web.Event.Event (Event)
|
||||||
-- import Data.Generic.Rep (class Generic)
|
-- import Data.Generic.Rep (class Generic)
|
||||||
-- import Data.Show.Generic (genericShow)
|
-- import Data.Show.Generic (genericShow)
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
import Scroll (scrollToTop)
|
import Scroll (scrollToTop)
|
||||||
|
|
||||||
import App.Type.LogMessage
|
import App.Type.LogMessage
|
||||||
|
@ -113,39 +113,39 @@ component =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render state
|
render state
|
||||||
= Bulma.section_small [Bulma.columns_
|
= Style.section_small [Style.columns_
|
||||||
[ b email_form
|
[ b email_form
|
||||||
, b token_form
|
, b token_form
|
||||||
]]
|
]]
|
||||||
|
|
||||||
where
|
where
|
||||||
b e = Bulma.column_ [ Bulma.box e ]
|
b e = Style.column_ [ Style.box e ]
|
||||||
|
|
||||||
email_form
|
email_form
|
||||||
= [ Bulma.h3 "New Email address"
|
= [ Style.h3 "New Email address"
|
||||||
-- TODO: put some text here
|
-- TODO: put some text here
|
||||||
, HH.form
|
, HH.form
|
||||||
[ HE.onSubmit (Verify EmailAddress) ]
|
[ HE.onSubmit (Verify EmailAddress) ]
|
||||||
[ email_input, email_error, Bulma.btn_validation ]
|
[ email_input, email_error, Style.btn_validation ]
|
||||||
]
|
]
|
||||||
|
|
||||||
email_input = Bulma.email_input "Email" state.email (UserInput EmailAddress)
|
email_input = Style.email_input "Email" state.email (UserInput EmailAddress)
|
||||||
|
|
||||||
email_error
|
email_error
|
||||||
= case between 0 5 (S.length state.email), E.email state.email of
|
= case between 0 5 (S.length state.email), E.email state.email of
|
||||||
true, _ -> HH.text ""
|
true, _ -> HH.text ""
|
||||||
_, Left errors -> Bulma.error_box "newAddress" "Email error" (show_error $ Email errors)
|
_, Left errors -> Style.error_box "newAddress" "Email error" (show_error $ Email errors)
|
||||||
_, Right _ -> HH.text ""
|
_, Right _ -> HH.text ""
|
||||||
|
|
||||||
token_form
|
token_form
|
||||||
= [ Bulma.h3 "Email validation token"
|
= [ Style.h3 "Email validation token"
|
||||||
-- TODO: put some text here
|
-- TODO: put some text here
|
||||||
, HH.form
|
, HH.form
|
||||||
[ HE.onSubmit (Verify Token) ]
|
[ HE.onSubmit (Verify Token) ]
|
||||||
[ token_input {-, token_error -}, Bulma.btn_validation ]
|
[ token_input {-, token_error -}, Style.btn_validation ]
|
||||||
]
|
]
|
||||||
|
|
||||||
token_input = Bulma.token_input "Token" state.token (UserInput Token)
|
token_input = Style.token_input "Token" state.token (UserInput Token)
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
handleAction = case _ of
|
handleAction = case _ of
|
||||||
|
|
|
@ -18,7 +18,7 @@ import Halogen.HTML.Properties as HP
|
||||||
import Halogen.HTML.Properties.ARIA as ARIA
|
import Halogen.HTML.Properties.ARIA as ARIA
|
||||||
|
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
|
|
||||||
import App.Type.Pages (Page(..))
|
import App.Type.Pages (Page(..))
|
||||||
import App.Type.LogMessage (LogMessage)
|
import App.Type.LogMessage (LogMessage)
|
||||||
|
@ -142,7 +142,7 @@ render { logged, active, admin, login } =
|
||||||
HH.a [ HP.classes $ [C.navbar_burger] <> if active then [C.is_active] else []
|
HH.a [ HP.classes $ [C.navbar_burger] <> if active then [C.is_active] else []
|
||||||
, ARIA.label "menu"
|
, ARIA.label "menu"
|
||||||
, ARIA.expanded "false"
|
, ARIA.expanded "false"
|
||||||
, Bulma.data_target "navbar-netlibre"
|
, Style.data_target "navbar-netlibre"
|
||||||
, HE.onClick (\_ -> ToggleMenu)
|
, HE.onClick (\_ -> ToggleMenu)
|
||||||
] [ HH.span [ARIA.hidden "true"] []
|
] [ HH.span [ARIA.hidden "true"] []
|
||||||
, HH.span [ARIA.hidden "true"] []
|
, HH.span [ARIA.hidden "true"] []
|
||||||
|
@ -192,7 +192,7 @@ render { logged, active, admin, login } =
|
||||||
, HE.onClick (\_ -> action)
|
, HE.onClick (\_ -> action)
|
||||||
] [ (HH.text str) ]
|
] [ (HH.text str) ]
|
||||||
|
|
||||||
dropdown_element classes link str = Bulma.outside_link ([C.navbar_item] <> classes) link str
|
dropdown_element classes link str = Style.outside_link ([C.navbar_item] <> classes) link str
|
||||||
dropdown_element_primary link str = dropdown_element [C.has_background_info_light] link str
|
dropdown_element_primary link str = dropdown_element [C.has_background_info_light] link str
|
||||||
dropdown_element_secondary link str = dropdown_element [C.has_background_warning_light] link str
|
dropdown_element_secondary link str = dropdown_element [C.has_background_warning_light] link str
|
||||||
|
|
||||||
|
|
|
@ -18,7 +18,7 @@ import Web.Event.Event (Event)
|
||||||
|
|
||||||
import App.Text.Explanations as Explanations
|
import App.Text.Explanations as Explanations
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
|
|
||||||
import Data.String as S
|
import Data.String as S
|
||||||
|
@ -96,11 +96,11 @@ component =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { registrationForm }
|
render { registrationForm }
|
||||||
= Bulma.section_small [Bulma.columns_ [ b registration_form ]]
|
= Style.section_small [Style.columns_ [ b registration_form ]]
|
||||||
|
|
||||||
where
|
where
|
||||||
b e = Bulma.column_ [ Bulma.box e ]
|
b e = Style.column_ [ Style.box e ]
|
||||||
registration_form = [ Bulma.h3 "Register", render_register_form ]
|
registration_form = [ Style.h3 "Register", render_register_form ]
|
||||||
|
|
||||||
render_register_form = HH.form
|
render_register_form = HH.form
|
||||||
[ HE.onSubmit ValidateInputs ]
|
[ HE.onSubmit ValidateInputs ]
|
||||||
|
@ -109,39 +109,39 @@ render { registrationForm }
|
||||||
password_input <> password_error <>
|
password_input <> password_error <>
|
||||||
legal_mentions <> validation_btn)
|
legal_mentions <> validation_btn)
|
||||||
|
|
||||||
username_input = [ Bulma.username_input "Username" registrationForm.login (HandleRegisterInput <<< REG_INP_login) ]
|
username_input = [ Style.username_input "Username" registrationForm.login (HandleRegisterInput <<< REG_INP_login) ]
|
||||||
|
|
||||||
username_error
|
username_error
|
||||||
= case between 0 1 (S.length registrationForm.login), L.login registrationForm.login of
|
= case between 0 1 (S.length registrationForm.login), L.login registrationForm.login of
|
||||||
true, _ -> []
|
true, _ -> []
|
||||||
_, Left errors -> [ Bulma.error_box "loginREGISTER" "Login error" (show_error $ Login errors) ]
|
_, Left errors -> [ Style.error_box "loginREGISTER" "Login error" (show_error $ Login errors) ]
|
||||||
_, Right _ -> []
|
_, Right _ -> []
|
||||||
|
|
||||||
email_input = [ Bulma.email_input "Email" registrationForm.email (HandleRegisterInput <<< REG_INP_email) ]
|
email_input = [ Style.email_input "Email" registrationForm.email (HandleRegisterInput <<< REG_INP_email) ]
|
||||||
|
|
||||||
email_error
|
email_error
|
||||||
= case between 0 5 (S.length registrationForm.email), E.email registrationForm.email of
|
= case between 0 5 (S.length registrationForm.email), E.email registrationForm.email of
|
||||||
true, _ -> []
|
true, _ -> []
|
||||||
_, Left errors -> [ Bulma.error_box "emailREGISTER" "Email error" (show_error $ Email errors) ]
|
_, Left errors -> [ Style.error_box "emailREGISTER" "Email error" (show_error $ Email errors) ]
|
||||||
_, Right _ -> []
|
_, Right _ -> []
|
||||||
|
|
||||||
password_input = [ Bulma.password_input "Password" registrationForm.pass (HandleRegisterInput <<< REG_INP_pass) ]
|
password_input = [ Style.password_input "Password" registrationForm.pass (HandleRegisterInput <<< REG_INP_pass) ]
|
||||||
|
|
||||||
password_error
|
password_error
|
||||||
= case between 0 15 (S.length registrationForm.pass), P.password registrationForm.pass of
|
= case between 0 15 (S.length registrationForm.pass), P.password registrationForm.pass of
|
||||||
true, _ -> []
|
true, _ -> []
|
||||||
_, Left errors -> [ Bulma.error_box "passwordREGISTER" "Password error" (show_error $ Password errors) ]
|
_, Left errors -> [ Style.error_box "passwordREGISTER" "Password error" (show_error $ Password errors) ]
|
||||||
_, Right _ -> []
|
_, Right _ -> []
|
||||||
|
|
||||||
legal_mentions = [ Explanations.legal_notice
|
legal_mentions = [ Explanations.legal_notice
|
||||||
, HH.div [HP.classes [C.margin_top 3, C.margin_bottom 3]]
|
, HH.div [HP.classes [C.margin_top 3, C.margin_bottom 3]]
|
||||||
[ Bulma.checkbox
|
[ Style.checkbox
|
||||||
[HH.span [HP.classes [C.margin_left 3]] [HH.text "I have read and accept the terms of service and privacy policy."]]
|
[HH.span [HP.classes [C.margin_left 3]] [HH.text "I have read and accept the terms of service and privacy policy."]]
|
||||||
LegalCheckboxToggle
|
LegalCheckboxToggle
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
validation_btn = [ Bulma.btn_validation ]
|
validation_btn = [ Style.btn_validation ]
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
handleAction = case _ of
|
handleAction = case _ of
|
||||||
|
|
|
@ -15,7 +15,7 @@ import Halogen.HTML.Events as HE
|
||||||
import Web.Event.Event as Event
|
import Web.Event.Event as Event
|
||||||
import Web.Event.Event (Event)
|
import Web.Event.Event (Event)
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
|
|
||||||
import App.Type.Email as Email
|
import App.Type.Email as Email
|
||||||
|
@ -89,50 +89,50 @@ initialState emails =
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render { modal, newPasswordForm, emails } =
|
render { modal, newPasswordForm, emails } =
|
||||||
Bulma.section_small
|
Style.section_small
|
||||||
[ render_emails emails
|
[ render_emails emails
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, case modal of
|
, case modal of
|
||||||
DeleteAccountModal -> render_delete_account_modal
|
DeleteAccountModal -> render_delete_account_modal
|
||||||
NoModal -> Bulma.columns_
|
NoModal -> Style.columns_
|
||||||
[ b [ Bulma.btn_ [C.is_large, C.is_info] "Change email address" RouteChangeEmailAddressPage ]
|
[ b [ Style.btn_ [C.is_large, C.is_info] "Change email address" RouteChangeEmailAddressPage ]
|
||||||
, b [ Bulma.h3 "Change password", render_new_password_form ]
|
, b [ Style.h3 "Change password", render_new_password_form ]
|
||||||
, b [ Bulma.h3 "Delete account", render_delete_account ]
|
, b [ Style.h3 "Delete account", render_delete_account ]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
where
|
where
|
||||||
b e = Bulma.column_ e
|
b e = Style.column_ e
|
||||||
|
|
||||||
render_emails (Tuple current pending) = HH.div [] $ render_current current <> render_pending pending
|
render_emails (Tuple current pending) = HH.div [] $ render_current current <> render_pending pending
|
||||||
where
|
where
|
||||||
render_current (Just (Email.Email e)) = [ Bulma.p $ "Current email address: " ] <>
|
render_current (Just (Email.Email e)) = [ Style.p $ "Current email address: " ] <>
|
||||||
[ Bulma.btn_ro [C.is_small, C.is_warning] e]
|
[ Style.btn_ro [C.is_small, C.is_warning] e]
|
||||||
render_current Nothing = [ Bulma.p "You do not currently have a validated email address." ]
|
render_current Nothing = [ Style.p "You do not currently have a validated email address." ]
|
||||||
|
|
||||||
render_pending (Just (Email.Email e)) = [ Bulma.p $ "Pending email address: " ] <>
|
render_pending (Just (Email.Email e)) = [ Style.p $ "Pending email address: " ] <>
|
||||||
[ Bulma.btn_ro [C.is_small, C.is_warning] e]
|
[ Style.btn_ro [C.is_small, C.is_warning] e]
|
||||||
render_pending Nothing = []
|
render_pending Nothing = []
|
||||||
|
|
||||||
render_delete_account = Bulma.alert_btn "Delete my account" DeleteAccountPopup
|
render_delete_account = Style.alert_btn "Delete my account" DeleteAccountPopup
|
||||||
|
|
||||||
render_new_password_form = HH.form
|
render_new_password_form = HH.form
|
||||||
[ HE.onSubmit ChangePasswordAttempt ]
|
[ HE.onSubmit ChangePasswordAttempt ]
|
||||||
[ Bulma.box_password "passwordNEWPASS" "New Password" "password"
|
[ Style.box_password "passwordNEWPASS" "New Password" "password"
|
||||||
(HandleNewPassword <<< NEWPASS_INP_password)
|
(HandleNewPassword <<< NEWPASS_INP_password)
|
||||||
newPasswordForm.password
|
newPasswordForm.password
|
||||||
, Bulma.box_password "confirmationNEWPASS" "Confirmation" "confirmation"
|
, Style.box_password "confirmationNEWPASS" "Confirmation" "confirmation"
|
||||||
(HandleNewPassword <<< NEWPASS_INP_confirmation)
|
(HandleNewPassword <<< NEWPASS_INP_confirmation)
|
||||||
newPasswordForm.confirmation
|
newPasswordForm.confirmation
|
||||||
, Bulma.btn_validation
|
, Style.btn_validation
|
||||||
]
|
]
|
||||||
|
|
||||||
render_delete_account_modal = Bulma.modal "Delete your account"
|
render_delete_account_modal = Style.modal "Delete your account"
|
||||||
[ Bulma.p "Your account and domains will be removed."
|
[ Style.p "Your account and domains will be removed."
|
||||||
, Bulma.strong "⚠ You won't be able to recover your data."
|
, Style.strong "⚠ You won't be able to recover your data."
|
||||||
]
|
]
|
||||||
[ Bulma.alert_btn "GO AHEAD LOL" DeleteAccount
|
[ Style.alert_btn "GO AHEAD LOL" DeleteAccount
|
||||||
, Bulma.cancel_button CancelModal
|
, Style.cancel_button CancelModal
|
||||||
]
|
]
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
|
|
|
@ -43,7 +43,7 @@ import Halogen as H
|
||||||
import Halogen.HTML as HH
|
import Halogen.HTML as HH
|
||||||
import Halogen.HTML.Properties as HP
|
import Halogen.HTML.Properties as HP
|
||||||
|
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
|
|
||||||
import App.Text.Explanations as Explanations
|
import App.Text.Explanations as Explanations
|
||||||
|
@ -332,7 +332,7 @@ type SortableRecord l = Record (rrtype :: String, rrid :: Int | l)
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
render state
|
render state
|
||||||
= Bulma.section_small
|
= Style.section_small
|
||||||
[ fancy_tab
|
[ fancy_tab
|
||||||
, case state.current_tab of
|
, case state.current_tab of
|
||||||
Zone -> render_zone
|
Zone -> render_zone
|
||||||
|
@ -341,10 +341,10 @@ render state
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
fancy_tab =
|
fancy_tab =
|
||||||
Bulma.fancy_tabs
|
Style.fancy_tabs
|
||||||
[ Bulma.tab_entry (is_tab_active Zone) "Zone" (ChangeTab Zone)
|
[ Style.tab_entry (is_tab_active Zone) "Zone" (ChangeTab Zone)
|
||||||
, Bulma.tab_entry (is_tab_active TheBasics) "The basics 🧠" (ChangeTab TheBasics)
|
, Style.tab_entry (is_tab_active TheBasics) "The basics 🧠" (ChangeTab TheBasics)
|
||||||
, Bulma.tab_entry (is_tab_active TokenExplanation) "Tokens? 🤨" (ChangeTab TokenExplanation)
|
, Style.tab_entry (is_tab_active TokenExplanation) "Tokens? 🤨" (ChangeTab TokenExplanation)
|
||||||
]
|
]
|
||||||
is_tab_active tab = state.current_tab == tab
|
is_tab_active tab = state.current_tab == tab
|
||||||
|
|
||||||
|
@ -354,12 +354,12 @@ render state
|
||||||
NewRRModal _ -> render_current_rr_modal
|
NewRRModal _ -> render_current_rr_modal
|
||||||
UpdateRRModal -> render_current_rr_modal
|
UpdateRRModal -> render_current_rr_modal
|
||||||
NoModal -> HH.div_
|
NoModal -> HH.div_
|
||||||
[ Bulma.level [ Bulma.btn_ [C.is_large, C.is_info] "Back to the domain list" ReturnToDomainList
|
[ Style.level [ Style.btn_ [C.is_large, C.is_info] "Back to the domain list" ReturnToDomainList
|
||||||
, Bulma.h1 state._domain
|
, Style.h1 state._domain
|
||||||
] []
|
] []
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, render_resources $ sorted state._resources
|
, render_resources $ sorted state._resources
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, render_new_records state
|
, render_new_records state
|
||||||
, render_zonefile state._zonefile
|
, render_zonefile state._zonefile
|
||||||
]
|
]
|
||||||
|
@ -372,13 +372,13 @@ render state
|
||||||
# A.concat -- -> [x1 x2 y z1 z2 z3]
|
# A.concat -- -> [x1 x2 y z1 z2 z3]
|
||||||
|
|
||||||
modal_rr_delete :: forall w. Int -> HH.HTML w Action
|
modal_rr_delete :: forall w. Int -> HH.HTML w Action
|
||||||
modal_rr_delete rr_id = Bulma.modal "Deleting a resource record"
|
modal_rr_delete rr_id = Style.modal "Deleting a resource record"
|
||||||
[warning_message] [modal_delete_button, Bulma.cancel_button CancelModal]
|
[warning_message] [modal_delete_button, Style.cancel_button CancelModal]
|
||||||
where
|
where
|
||||||
modal_delete_button = Bulma.alert_btn "Delete the resource record" (RemoveRR rr_id)
|
modal_delete_button = Style.alert_btn "Delete the resource record" (RemoveRR rr_id)
|
||||||
warning_message
|
warning_message
|
||||||
= HH.p [] [ HH.text "You are about to delete a resource record, this action is "
|
= HH.p [] [ HH.text "You are about to delete a resource record, this action is "
|
||||||
, Bulma.strong "irreversible"
|
, Style.strong "irreversible"
|
||||||
, HH.text "."
|
, HH.text "."
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -396,166 +396,166 @@ render state
|
||||||
"SPF" -> template modal_content_spf (foot_content SPF)
|
"SPF" -> template modal_content_spf (foot_content SPF)
|
||||||
"DKIM" -> template modal_content_dkim (foot_content DKIM)
|
"DKIM" -> template modal_content_dkim (foot_content DKIM)
|
||||||
"DMARC" -> template modal_content_dmarc (foot_content DMARC)
|
"DMARC" -> template modal_content_dmarc (foot_content DMARC)
|
||||||
_ -> Bulma.p $ "Invalid type: " <> state._currentRR.rrtype
|
_ -> Style.p $ "Invalid type: " <> state._currentRR.rrtype
|
||||||
where
|
where
|
||||||
side_text_for_name_input name_id = Bulma.side_text_above_input name_id "Name" (HH.text $ "Empty name = root domain (" <> state._domain <> ".)")
|
side_text_for_name_input name_id = Style.side_text_above_input name_id "Name" (HH.text $ "Empty name = root domain (" <> state._domain <> ".)")
|
||||||
-- DRY
|
-- DRY
|
||||||
updateForm x = UpdateCurrentRR <<< x
|
updateForm x = UpdateCurrentRR <<< x
|
||||||
render_errors = if A.length state._currentRR_errors > 0
|
render_errors = if A.length state._currentRR_errors > 0
|
||||||
then HH.div_ $ [ Bulma.h3 "Errors: " ] <> map error_to_paragraph state._currentRR_errors
|
then HH.div_ $ [ Style.h3 "Errors: " ] <> map error_to_paragraph state._currentRR_errors
|
||||||
else HH.div_ [ ]
|
else HH.div_ [ ]
|
||||||
modal_content_simple :: AcceptedRRTypes -> Array (HH.HTML w Action)
|
modal_content_simple :: AcceptedRRTypes -> Array (HH.HTML w Action)
|
||||||
modal_content_simple x =
|
modal_content_simple x =
|
||||||
[ render_errors
|
[ render_errors
|
||||||
, render_introduction_text x
|
, render_introduction_text x
|
||||||
, side_text_for_name_input ("domain" <> state._currentRR.rrtype)
|
, side_text_for_name_input ("domain" <> state._currentRR.rrtype)
|
||||||
, Bulma.input_with_side_text ("domain" <> state._currentRR.rrtype) "" "www"
|
, Style.input_with_side_text ("domain" <> state._currentRR.rrtype) "" "www"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input ("ttl" <> state._currentRR.rrtype) "TTL" "1800"
|
, Style.box_input ("ttl" <> state._currentRR.rrtype) "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
, case state._currentRR.rrtype of
|
, case state._currentRR.rrtype of
|
||||||
"AAAA" -> Bulma.box_input ("target" <> state._currentRR.rrtype) "Target" "2001:db8::1" (updateForm Field_Target) state._currentRR.target
|
"AAAA" -> Style.box_input ("target" <> state._currentRR.rrtype) "Target" "2001:db8::1" (updateForm Field_Target) state._currentRR.target
|
||||||
"TXT" -> Bulma.box_input ("target" <> state._currentRR.rrtype) "Your text" "blah blah" (updateForm Field_Target) state._currentRR.target
|
"TXT" -> Style.box_input ("target" <> state._currentRR.rrtype) "Your text" "blah blah" (updateForm Field_Target) state._currentRR.target
|
||||||
"CNAME" -> Bulma.box_input ("target" <> state._currentRR.rrtype) "Target" "www" (updateForm Field_Target) state._currentRR.target
|
"CNAME" -> Style.box_input ("target" <> state._currentRR.rrtype) "Target" "www" (updateForm Field_Target) state._currentRR.target
|
||||||
"NS" -> Bulma.box_input ("target" <> state._currentRR.rrtype) "Target" "ns0.example.com." (updateForm Field_Target) state._currentRR.target
|
"NS" -> Style.box_input ("target" <> state._currentRR.rrtype) "Target" "ns0.example.com." (updateForm Field_Target) state._currentRR.target
|
||||||
_ -> Bulma.box_input ("target" <> state._currentRR.rrtype) "Target" "198.51.100.5" (updateForm Field_Target) state._currentRR.target
|
_ -> Style.box_input ("target" <> state._currentRR.rrtype) "Target" "198.51.100.5" (updateForm Field_Target) state._currentRR.target
|
||||||
] <> case state.rr_modal of
|
] <> case state.rr_modal of
|
||||||
UpdateRRModal ->
|
UpdateRRModal ->
|
||||||
if A.elem state._currentRR.rrtype ["A", "AAAA"]
|
if A.elem state._currentRR.rrtype ["A", "AAAA"]
|
||||||
then [ Bulma.field_entry ("token" <> state._currentRR.rrtype) "Token"
|
then [ Style.field_entry ("token" <> state._currentRR.rrtype) "Token"
|
||||||
(maybe (Bulma.text "❌") Bulma.p state._currentRR.token)
|
(maybe (Style.text "❌") Style.p state._currentRR.token)
|
||||||
]
|
]
|
||||||
else []
|
else []
|
||||||
_ -> []
|
_ -> []
|
||||||
|
|
||||||
render_introduction_text :: AcceptedRRTypes -> HH.HTML w Action
|
render_introduction_text :: AcceptedRRTypes -> HH.HTML w Action
|
||||||
render_introduction_text = case _ of
|
render_introduction_text = case _ of
|
||||||
A -> Bulma.div_content [] [Bulma.explanation Explanations.a_introduction]
|
A -> Style.div_content [] [Style.explanation Explanations.a_introduction]
|
||||||
AAAA -> Bulma.div_content [] [Bulma.explanation Explanations.aaaa_introduction]
|
AAAA -> Style.div_content [] [Style.explanation Explanations.aaaa_introduction]
|
||||||
TXT -> Bulma.div_content [] [Bulma.explanation Explanations.txt_introduction]
|
TXT -> Style.div_content [] [Style.explanation Explanations.txt_introduction]
|
||||||
CNAME -> Bulma.div_content [] [Bulma.explanation Explanations.cname_introduction]
|
CNAME -> Style.div_content [] [Style.explanation Explanations.cname_introduction]
|
||||||
NS -> Bulma.div_content [] [Bulma.explanation Explanations.ns_introduction]
|
NS -> Style.div_content [] [Style.explanation Explanations.ns_introduction]
|
||||||
_ -> HH.p_ []
|
_ -> HH.p_ []
|
||||||
modal_content_mx :: Array (HH.HTML w Action)
|
modal_content_mx :: Array (HH.HTML w Action)
|
||||||
modal_content_mx =
|
modal_content_mx =
|
||||||
[ render_errors
|
[ render_errors
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.mx_introduction]
|
, Style.div_content [] [Style.explanation Explanations.mx_introduction]
|
||||||
, side_text_for_name_input "domainMX"
|
, side_text_for_name_input "domainMX"
|
||||||
, Bulma.input_with_side_text "domainMX" "" "www"
|
, Style.input_with_side_text "domainMX" "" "www"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input ("ttlMX") "TTL" "1800"
|
, Style.box_input ("ttlMX") "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
, Bulma.box_input ("targetMX") "Target" "www"
|
, Style.box_input ("targetMX") "Target" "www"
|
||||||
(updateForm Field_Target)
|
(updateForm Field_Target)
|
||||||
state._currentRR.target
|
state._currentRR.target
|
||||||
, Bulma.box_input ("priorityMX") "Priority" "10"
|
, Style.box_input ("priorityMX") "Priority" "10"
|
||||||
(updateForm Field_Priority)
|
(updateForm Field_Priority)
|
||||||
(maybe "" show state._currentRR.priority)
|
(maybe "" show state._currentRR.priority)
|
||||||
]
|
]
|
||||||
modal_content_caa :: Array (HH.HTML w Action)
|
modal_content_caa :: Array (HH.HTML w Action)
|
||||||
modal_content_caa =
|
modal_content_caa =
|
||||||
[ render_errors
|
[ render_errors
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.caa_introduction]
|
, Style.div_content [] [Style.explanation Explanations.caa_introduction]
|
||||||
, side_text_for_name_input "domainCAA"
|
, side_text_for_name_input "domainCAA"
|
||||||
, Bulma.input_with_side_text "domainCAA" "" "www"
|
, Style.input_with_side_text "domainCAA" "" "www"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input ("ttlCAA") "TTL" "1800"
|
, Style.box_input ("ttlCAA") "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.box_input ("flagCAA") "Flag" ""
|
, Style.box_input ("flagCAA") "Flag" ""
|
||||||
(updateForm Field_CAA_flag)
|
(updateForm Field_CAA_flag)
|
||||||
(show (fromMaybe default_caa state._currentRR.caa).flag)
|
(show (fromMaybe default_caa state._currentRR.caa).flag)
|
||||||
, Bulma.selection_field'' "tagCAA" "Tag" CAA_tag (A.zip CAA.tags_txt CAA.tags_raw)
|
, Style.selection_field'' "tagCAA" "Tag" CAA_tag (A.zip CAA.tags_txt CAA.tags_raw)
|
||||||
CAA.Issue
|
CAA.Issue
|
||||||
(Just (fromMaybe default_caa state._currentRR.caa).tag)
|
(Just (fromMaybe default_caa state._currentRR.caa).tag)
|
||||||
, HH.div [HP.classes [C.notification, C.is_warning]]
|
, HH.div [HP.classes [C.notification, C.is_warning]]
|
||||||
[ Bulma.p "⚠️ CAA entries aren't thoroughly verified, yet. Also, do not put quotes."
|
[ Style.p "⚠️ CAA entries aren't thoroughly verified, yet. Also, do not put quotes."
|
||||||
]
|
]
|
||||||
, Bulma.box_input "valueCAA" "Value" "" (updateForm Field_CAA_value)
|
, Style.box_input "valueCAA" "Value" "" (updateForm Field_CAA_value)
|
||||||
(fromMaybe default_caa state._currentRR.caa).value
|
(fromMaybe default_caa state._currentRR.caa).value
|
||||||
]
|
]
|
||||||
modal_content_srv :: Array (HH.HTML w Action)
|
modal_content_srv :: Array (HH.HTML w Action)
|
||||||
modal_content_srv =
|
modal_content_srv =
|
||||||
[ Bulma.div_content [] [Bulma.explanation Explanations.srv_introduction]
|
[ Style.div_content [] [Style.explanation Explanations.srv_introduction]
|
||||||
, render_errors
|
, render_errors
|
||||||
, Bulma.box_input ("ttlSRV") "TTL" "1800"
|
, Style.box_input ("ttlSRV") "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
, Bulma.box_input "domainSRV" "Service name" "service name"
|
, Style.box_input "domainSRV" "Service name" "service name"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
, Bulma.selection_field "protocolSRV" "Protocol" SRV_Protocol RR.srv_protocols_txt
|
, Style.selection_field "protocolSRV" "Protocol" SRV_Protocol RR.srv_protocols_txt
|
||||||
(maybe "udp" (toLower <<< show) state._currentRR.protocol)
|
(maybe "udp" (toLower <<< show) state._currentRR.protocol)
|
||||||
, Bulma.box_input ("targetSRV") "Where the server is" "www"
|
, Style.box_input ("targetSRV") "Where the server is" "www"
|
||||||
(updateForm Field_Target)
|
(updateForm Field_Target)
|
||||||
state._currentRR.target
|
state._currentRR.target
|
||||||
, Bulma.box_input ("portSRV") "Port of the service" "5061"
|
, Style.box_input ("portSRV") "Port of the service" "5061"
|
||||||
(updateForm Field_Port)
|
(updateForm Field_Port)
|
||||||
(maybe "" show state._currentRR.port)
|
(maybe "" show state._currentRR.port)
|
||||||
, Bulma.div_content [] [Bulma.explanation [Bulma.p "The priority field is a numeric value that indicates the preference of the server (lower values indicate higher priority)."]]
|
, Style.div_content [] [Style.explanation [Style.p "The priority field is a numeric value that indicates the preference of the server (lower values indicate higher priority)."]]
|
||||||
, Bulma.box_input ("prioritySRV") "Priority" "10"
|
, Style.box_input ("prioritySRV") "Priority" "10"
|
||||||
(updateForm Field_Priority)
|
(updateForm Field_Priority)
|
||||||
(maybe "" show state._currentRR.priority)
|
(maybe "" show state._currentRR.priority)
|
||||||
-- Bulma.div_content [] [Bulma.explanation Explanations.spf_introduction], Bulma.p "Modifiers provide additional instructions, such as explanations for SPF failures or redirecting SPF checks to another domain."
|
-- Style.div_content [] [Style.explanation Explanations.spf_introduction], Style.p "Modifiers provide additional instructions, such as explanations for SPF failures or redirecting SPF checks to another domain."
|
||||||
, Bulma.div_content [] [Bulma.explanation [Bulma.p "The weight field is a relative weight used when multiple servers have the same priority, determining how often they should be used."]]
|
, Style.div_content [] [Style.explanation [Style.p "The weight field is a relative weight used when multiple servers have the same priority, determining how often they should be used."]]
|
||||||
, Bulma.box_input ("weightSRV") "Weight" "100"
|
, Style.box_input ("weightSRV") "Weight" "100"
|
||||||
(updateForm Field_Weight)
|
(updateForm Field_Weight)
|
||||||
(maybe "" show state._currentRR.weight)
|
(maybe "" show state._currentRR.weight)
|
||||||
]
|
]
|
||||||
modal_content_spf :: Array (HH.HTML w Action)
|
modal_content_spf :: Array (HH.HTML w Action)
|
||||||
modal_content_spf =
|
modal_content_spf =
|
||||||
[ Bulma.div_content [] [Bulma.explanation Explanations.spf_introduction]
|
[ Style.div_content [] [Style.explanation Explanations.spf_introduction]
|
||||||
, render_errors
|
, render_errors
|
||||||
, side_text_for_name_input "domainSPF"
|
, side_text_for_name_input "domainSPF"
|
||||||
, Bulma.input_with_side_text "domainSPF" "" "Let this alone."
|
, Style.input_with_side_text "domainSPF" "" "Let this alone."
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input "ttlSPF" "TTL" "1800"
|
, Style.box_input "ttlSPF" "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
--, case state._currentRR.v of
|
--, case state._currentRR.v of
|
||||||
-- Nothing -> Bulma.p "default value for the version (spf1)"
|
-- Nothing -> Style.p "default value for the version (spf1)"
|
||||||
-- Just v -> Bulma.box_input "vSPF" "Version" "spf1" (updateForm Field_SPF_v) v
|
-- Just v -> Style.box_input "vSPF" "Version" "spf1" (updateForm Field_SPF_v) v
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.box_with_tag [C.has_background_info_light] tag_mechanisms
|
, Style.box_with_tag [C.has_background_info_light] tag_mechanisms
|
||||||
[ Bulma.div_content [] [Bulma.explanation [Bulma.p "Mechanisms specify which mail servers are allowed to send mail for the domain and how to evaluate the sending mail server’s IP address."] ]
|
[ Style.div_content [] [Style.explanation [Style.p "Mechanisms specify which mail servers are allowed to send mail for the domain and how to evaluate the sending mail server’s IP address."] ]
|
||||||
, maybe (Bulma.p "You don't have any mechanism.") display_mechanisms state._currentRR.mechanisms
|
, maybe (Style.p "You don't have any mechanism.") display_mechanisms state._currentRR.mechanisms
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h4 "New mechanism"
|
, Style.h4 "New mechanism"
|
||||||
, Bulma.selection_field "idMechanismQ" "Policy" SPF_Mechanism_q qualifier_types state.spf_mechanism_q
|
, Style.selection_field "idMechanismQ" "Policy" SPF_Mechanism_q qualifier_types state.spf_mechanism_q
|
||||||
, Bulma.selection_field "idMechanismT" "Type" SPF_Mechanism_t mechanism_types state.spf_mechanism_t
|
, Style.selection_field "idMechanismT" "Type" SPF_Mechanism_t mechanism_types state.spf_mechanism_t
|
||||||
, Bulma.box_input "valueNewMechanismSPF" "Value" ""
|
, Style.box_input "valueNewMechanismSPF" "Value" ""
|
||||||
SPF_Mechanism_v
|
SPF_Mechanism_v
|
||||||
state.spf_mechanism_v
|
state.spf_mechanism_v
|
||||||
, Bulma.btn "Add a mechanism" SPF_Mechanism_Add
|
, Style.btn "Add a mechanism" SPF_Mechanism_Add
|
||||||
]
|
]
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.box_with_tag [C.has_background_success_light] tag_modifiers
|
, Style.box_with_tag [C.has_background_success_light] tag_modifiers
|
||||||
[ Bulma.div_content [] [Bulma.explanation [Bulma.p "Modifiers provide additional instructions, such as explanations for SPF failures or redirecting SPF checks to another domain."] ]
|
[ Style.div_content [] [Style.explanation [Style.p "Modifiers provide additional instructions, such as explanations for SPF failures or redirecting SPF checks to another domain."] ]
|
||||||
, maybe (Bulma.p "You don't have any modifier.") display_modifiers state._currentRR.modifiers
|
, maybe (Style.p "You don't have any modifier.") display_modifiers state._currentRR.modifiers
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h4 "New modifier"
|
, Style.h4 "New modifier"
|
||||||
, Bulma.selection_field "idModifierT" "Modifier" SPF_Modifier_t modifier_types state.spf_modifier_t
|
, Style.selection_field "idModifierT" "Modifier" SPF_Modifier_t modifier_types state.spf_modifier_t
|
||||||
, Bulma.box_input "valueNewModifierSPF" "Value" ""
|
, Style.box_input "valueNewModifierSPF" "Value" ""
|
||||||
SPF_Modifier_v
|
SPF_Modifier_v
|
||||||
state.spf_modifier_v
|
state.spf_modifier_v
|
||||||
, Bulma.btn "Add a modifier" SPF_Modifier_Add
|
, Style.btn "Add a modifier" SPF_Modifier_Add
|
||||||
]
|
]
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.box
|
, Style.box
|
||||||
[ Bulma.h3 "Default behavior"
|
[ Style.h3 "Default behavior"
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.spf_default_behavior]
|
, Style.div_content [] [Style.explanation Explanations.spf_default_behavior]
|
||||||
, Bulma.selection SPF_Qualifier qualifier_types (maybe default_qualifier_str show_qualifier state._currentRR.q)
|
, Style.selection SPF_Qualifier qualifier_types (maybe default_qualifier_str show_qualifier state._currentRR.q)
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
|
@ -567,120 +567,120 @@ 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.div_content [] [Bulma.explanation Explanations.dkim_introduction]
|
[ Style.div_content [] [Style.explanation Explanations.dkim_introduction]
|
||||||
, render_errors
|
, render_errors
|
||||||
, side_text_for_name_input "domainDKIM"
|
, side_text_for_name_input "domainDKIM"
|
||||||
, Bulma.input_with_side_text "domainDKIM" "" "default._domainkey"
|
, Style.input_with_side_text "domainDKIM" "" "default._domainkey"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input "ttlDKIM" "TTL" "1800"
|
, Style.box_input "ttlDKIM" "TTL" "1800"
|
||||||
(updateForm Field_TTL)
|
(updateForm Field_TTL)
|
||||||
(show state._currentRR.ttl)
|
(show state._currentRR.ttl)
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dkim_default_algorithms]
|
, Style.div_content [] [Style.explanation Explanations.dkim_default_algorithms]
|
||||||
, Bulma.selection_field "idDKIMSignature" "Signature algo"
|
, Style.selection_field "idDKIMSignature" "Signature algo"
|
||||||
DKIM_sign_algo
|
DKIM_sign_algo
|
||||||
(map show DKIM.sign_algos)
|
(map show DKIM.sign_algos)
|
||||||
(show $ fromMaybe DKIM.RSA state.dkim.k)
|
(show $ fromMaybe DKIM.RSA state.dkim.k)
|
||||||
, Bulma.selection_field "idDKIMHash" "Hash algo"
|
, Style.selection_field "idDKIMHash" "Hash algo"
|
||||||
DKIM_hash_algo
|
DKIM_hash_algo
|
||||||
(map show DKIM.hash_algos)
|
(map show DKIM.hash_algos)
|
||||||
(show $ fromMaybe DKIM.SHA256 state.dkim.h)
|
(show $ fromMaybe DKIM.SHA256 state.dkim.h)
|
||||||
, Bulma.box_input "pkDKIM" "Public Key" "Your public key, such as \"MIIBIjANBgqh...\"" DKIM_pubkey state.dkim.p
|
, Style.box_input "pkDKIM" "Public Key" "Your public key, such as \"MIIBIjANBgqh...\"" DKIM_pubkey state.dkim.p
|
||||||
, Bulma.box_input "noteDKIM" "Note" "Note for fellow administrators." DKIM_note (fromMaybe "" state.dkim.n)
|
, Style.box_input "noteDKIM" "Note" "Note for fellow administrators." DKIM_note (fromMaybe "" state.dkim.n)
|
||||||
]
|
]
|
||||||
|
|
||||||
modal_content_dmarc :: Array (HH.HTML w Action)
|
modal_content_dmarc :: Array (HH.HTML w Action)
|
||||||
modal_content_dmarc =
|
modal_content_dmarc =
|
||||||
[ Bulma.div_content [] [Bulma.explanation Explanations.dmarc_introduction]
|
[ Style.div_content [] [Style.explanation Explanations.dmarc_introduction]
|
||||||
, render_errors
|
, render_errors
|
||||||
, side_text_for_name_input "domainDMARC"
|
, side_text_for_name_input "domainDMARC"
|
||||||
, Bulma.input_with_side_text "domainDMARC" "" "_dmarc"
|
, Style.input_with_side_text "domainDMARC" "" "_dmarc"
|
||||||
(updateForm Field_Domain)
|
(updateForm Field_Domain)
|
||||||
state._currentRR.name
|
state._currentRR.name
|
||||||
display_domain_side
|
display_domain_side
|
||||||
, Bulma.box_input "ttlDMARC" "TTL" "1800" (updateForm Field_TTL) (show state._currentRR.ttl)
|
, Style.box_input "ttlDMARC" "TTL" "1800" (updateForm Field_TTL) (show state._currentRR.ttl)
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_policy]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_policy]
|
||||||
, Bulma.selection_field' "idDMARCPolicy" "Policy" DMARC_policy
|
, Style.selection_field' "idDMARCPolicy" "Policy" DMARC_policy
|
||||||
(A.zip DMARC.policies_txt DMARC.policies_raw)
|
(A.zip DMARC.policies_txt DMARC.policies_raw)
|
||||||
(show state.dmarc.p)
|
(show state.dmarc.p)
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_sp_policy]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_sp_policy]
|
||||||
, Bulma.selection_field' "idDMARCPolicy_sp" "Policy for subdomains" DMARC_sp_policy
|
, Style.selection_field' "idDMARCPolicy_sp" "Policy for subdomains" DMARC_sp_policy
|
||||||
(zip_nullable DMARC.policies_txt_with_null DMARC.policies_raw)
|
(zip_nullable DMARC.policies_txt_with_null DMARC.policies_raw)
|
||||||
(maybe "-" show state.dmarc.sp)
|
(maybe "-" show state.dmarc.sp)
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_adkim]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_adkim]
|
||||||
, Bulma.selection_field' "idDMARCadkim" "Consistency Policy for DKIM" DMARC_adkim
|
, Style.selection_field' "idDMARCadkim" "Consistency Policy for DKIM" DMARC_adkim
|
||||||
(zip_nullable DMARC.consistency_policies_txt DMARC.consistency_policies_raw)
|
(zip_nullable DMARC.consistency_policies_txt DMARC.consistency_policies_raw)
|
||||||
(maybe "-" show state.dmarc.adkim)
|
(maybe "-" show state.dmarc.adkim)
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_aspf]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_aspf]
|
||||||
, Bulma.selection_field' "idDMARCaspf" "Consistency Policy for SPF" DMARC_aspf
|
, Style.selection_field' "idDMARCaspf" "Consistency Policy for SPF" DMARC_aspf
|
||||||
(zip_nullable DMARC.consistency_policies_txt DMARC.consistency_policies_raw)
|
(zip_nullable DMARC.consistency_policies_txt DMARC.consistency_policies_raw)
|
||||||
(maybe "-" show state.dmarc.aspf)
|
(maybe "-" show state.dmarc.aspf)
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_pct]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_pct]
|
||||||
, Bulma.box_input "idDMARCpct" "Sample rate (between 0 and 100)" "100" DMARC_pct (maybe "100" show state.dmarc.pct)
|
, Style.box_input "idDMARCpct" "Sample rate (between 0 and 100)" "100" DMARC_pct (maybe "100" show state.dmarc.pct)
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.selection_field' "idDMARCfo" "When to send a report" DMARC_fo
|
, Style.selection_field' "idDMARCfo" "When to send a report" DMARC_fo
|
||||||
(zip_nullable DMARC.report_occasions_txt DMARC.report_occasions_raw)
|
(zip_nullable DMARC.report_occasions_txt DMARC.report_occasions_raw)
|
||||||
(maybe "-" show state.dmarc.fo)
|
(maybe "-" show state.dmarc.fo)
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_contact]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_contact]
|
||||||
, Bulma.box_with_tag [C.has_background_info_light] tag_aggregated_reports
|
, Style.box_with_tag [C.has_background_info_light] tag_aggregated_reports
|
||||||
[ maybe (Bulma.p "There is no address to send aggregated reports to.")
|
[ maybe (Style.p "There is no address to send aggregated reports to.")
|
||||||
(display_dmarc_mail_addresses DMARC_remove_rua)
|
(display_dmarc_mail_addresses DMARC_remove_rua)
|
||||||
state.dmarc.rua
|
state.dmarc.rua
|
||||||
]
|
]
|
||||||
, Bulma.box_with_tag [C.has_background_success_light] tag_detailed_reports
|
, Style.box_with_tag [C.has_background_success_light] tag_detailed_reports
|
||||||
[ maybe (Bulma.p "There is no address to send detailed reports to.")
|
[ maybe (Style.p "There is no address to send detailed reports to.")
|
||||||
(display_dmarc_mail_addresses DMARC_remove_ruf)
|
(display_dmarc_mail_addresses DMARC_remove_ruf)
|
||||||
state.dmarc.ruf
|
state.dmarc.ruf
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, render_dmarc_mail_errors
|
, render_dmarc_mail_errors
|
||||||
, Bulma.box_input "idDMARCmail" "Address to contact" "admin@example.com" DMARC_mail state.dmarc_mail
|
, Style.box_input "idDMARCmail" "Address to contact" "admin@example.com" DMARC_mail state.dmarc_mail
|
||||||
, Bulma.box_input "idDMARCmaillimit" "Report size limit (in KB)" "2000" DMARC_mail_limit (maybe "0" show state.dmarc_mail_limit)
|
, Style.box_input "idDMARCmaillimit" "Report size limit (in KB)" "2000" DMARC_mail_limit (maybe "0" show state.dmarc_mail_limit)
|
||||||
, Bulma.level [ Bulma.btn_ [C.has_background_info_light] "New address for aggregated report" DMARC_rua_Add
|
, Style.level [ Style.btn_ [C.has_background_info_light] "New address for aggregated report" DMARC_rua_Add
|
||||||
, Bulma.btn_ [C.has_background_success_light] "New address for specific report" DMARC_ruf_Add
|
, Style.btn_ [C.has_background_success_light] "New address for specific report" DMARC_ruf_Add
|
||||||
] []
|
] []
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.div_content [] [Bulma.explanation Explanations.dmarc_ri]
|
, Style.div_content [] [Style.explanation Explanations.dmarc_ri]
|
||||||
, Bulma.box_input "idDMARCri" "Report interval (in seconds)" "86400" DMARC_ri (maybe "0" show state.dmarc.ri)
|
, Style.box_input "idDMARCri" "Report interval (in seconds)" "86400" DMARC_ri (maybe "0" show state.dmarc.ri)
|
||||||
]
|
]
|
||||||
|
|
||||||
render_dmarc_mail_errors
|
render_dmarc_mail_errors
|
||||||
= if A.length state._dmarc_mail_errors > 0
|
= if A.length state._dmarc_mail_errors > 0
|
||||||
then Bulma.notification_danger_block'
|
then Style.notification_danger_block'
|
||||||
$ [ Bulma.h3 "Invalid mail 😥" ] <> map (Bulma.p <<< show_error_email) state._dmarc_mail_errors
|
$ [ Style.h3 "Invalid mail 😥" ] <> map (Style.p <<< show_error_email) state._dmarc_mail_errors
|
||||||
else HH.div_ [ ]
|
else HH.div_ [ ]
|
||||||
|
|
||||||
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)
|
||||||
newtokenbtn = Bulma.btn (maybe "🏁 Ask for a token" (\_ -> "🏁 Ask for a new token") state._currentRR.token) (NewToken state._currentRR.rrid)
|
newtokenbtn = Style.btn (maybe "🏁 Ask for a token" (\_ -> "🏁 Ask for a new token") state._currentRR.token) (NewToken state._currentRR.rrid)
|
||||||
foot_content x =
|
foot_content x =
|
||||||
case state.rr_modal of
|
case state.rr_modal of
|
||||||
NewRRModal _ -> [Bulma.btn_add (ValidateRR x)]
|
NewRRModal _ -> [Style.btn_add (ValidateRR x)]
|
||||||
UpdateRRModal -> [Bulma.btn_save ValidateLocal] <> case x of
|
UpdateRRModal -> [Style.btn_save ValidateLocal] <> case x of
|
||||||
A -> [newtokenbtn]
|
A -> [newtokenbtn]
|
||||||
AAAA -> [newtokenbtn]
|
AAAA -> [newtokenbtn]
|
||||||
_ -> []
|
_ -> []
|
||||||
_ -> [Bulma.p "state.rr_modal should either be NewRRModal or UpdateRRModal."]
|
_ -> [Style.p "state.rr_modal should either be NewRRModal or UpdateRRModal."]
|
||||||
template content foot_ = Bulma.modal title content foot
|
template content foot_ = Style.modal title content foot
|
||||||
where
|
where
|
||||||
title = case state.rr_modal of
|
title = case state.rr_modal of
|
||||||
NoModal -> "Error: no modal should be displayed"
|
NoModal -> "Error: no modal should be displayed"
|
||||||
NewRRModal t_ -> "New " <> show t_ <> " resource record"
|
NewRRModal t_ -> "New " <> show t_ <> " resource record"
|
||||||
UpdateRRModal -> "Update " <> state._currentRR.rrtype <> " Resource Record"
|
UpdateRRModal -> "Update " <> state._currentRR.rrtype <> " Resource Record"
|
||||||
RemoveRRModal rr_id -> "Error: should display removal modal instead (for resource record " <> show rr_id <> ")"
|
RemoveRRModal rr_id -> "Error: should display removal modal instead (for resource record " <> show rr_id <> ")"
|
||||||
foot = foot_ <> [Bulma.cancel_button CancelModal]
|
foot = foot_ <> [Style.cancel_button CancelModal]
|
||||||
|
|
||||||
zip_nullable :: forall a. Array a -> Array String -> Array (Tuple a String)
|
zip_nullable :: forall a. Array a -> Array String -> Array (Tuple a String)
|
||||||
zip_nullable txt raw = A.zip txt ([""] <> raw)
|
zip_nullable txt raw = A.zip txt ([""] <> raw)
|
||||||
|
@ -1067,18 +1067,18 @@ tags xs = HH.span [HP.classes [C.tags, C.no_margin_bottom, C.no_padding_bottom]]
|
||||||
|
|
||||||
-- | Render all Resource Records.
|
-- | Render all Resource Records.
|
||||||
render_resources :: forall w. Array ResourceRecord -> HH.HTML w Action
|
render_resources :: forall w. Array ResourceRecord -> HH.HTML w Action
|
||||||
render_resources [] = Bulma.box [Bulma.zone_rr_title "Resource records", Bulma.subtitle "No records for now"]
|
render_resources [] = Style.box [Style.zone_rr_title "Resource records", Style.subtitle "No records for now"]
|
||||||
render_resources records
|
render_resources records
|
||||||
= HH.div_ $
|
= HH.div_ $
|
||||||
(rr_box [bg_color_ro] tag_soa Bulma.soa_table_header table_content all_soa_rr)
|
(rr_box [bg_color_ro] tag_soa Style.soa_table_header table_content all_soa_rr)
|
||||||
<> (rr_box [] tag_basic Bulma.simple_table_header table_content_w_seps all_basic_rr)
|
<> (rr_box [] tag_basic Style.simple_table_header table_content_w_seps all_basic_rr)
|
||||||
<> (rr_box [] tag_mx Bulma.mx_table_header table_content all_mx_rr)
|
<> (rr_box [] tag_mx Style.mx_table_header table_content all_mx_rr)
|
||||||
<> (rr_box [] tag_caa Bulma.caa_table_header table_content all_caa_rr)
|
<> (rr_box [] tag_caa Style.caa_table_header table_content all_caa_rr)
|
||||||
<> (rr_box [] tag_srv Bulma.srv_table_header table_content all_srv_rr)
|
<> (rr_box [] tag_srv Style.srv_table_header table_content all_srv_rr)
|
||||||
<> (rr_box [] tag_spf Bulma.spf_table_header table_content all_spf_rr)
|
<> (rr_box [] tag_spf Style.spf_table_header table_content all_spf_rr)
|
||||||
<> (rr_box [] tag_dkim Bulma.dkim_table_header table_content all_dkim_rr)
|
<> (rr_box [] tag_dkim Style.dkim_table_header table_content all_dkim_rr)
|
||||||
<> (rr_box [] tag_dmarc Bulma.dmarc_table_header table_content all_dmarc_rr)
|
<> (rr_box [] tag_dmarc Style.dmarc_table_header table_content all_dmarc_rr)
|
||||||
<> (rr_box [bg_color_ro] tag_basic_ro Bulma.simple_table_header_ro table_content_w_seps all_basic_ro_rr)
|
<> (rr_box [bg_color_ro] tag_basic_ro Style.simple_table_header_ro table_content_w_seps all_basic_ro_rr)
|
||||||
where
|
where
|
||||||
all_basic_rr = A.filter (\rr -> A.elem rr.rrtype baseRecords && not rr.readonly) records
|
all_basic_rr = A.filter (\rr -> A.elem rr.rrtype baseRecords && not rr.readonly) records
|
||||||
all_basic_ro_rr = A.filter (\rr -> A.elem rr.rrtype baseRecords && rr.readonly) records
|
all_basic_ro_rr = A.filter (\rr -> A.elem rr.rrtype baseRecords && rr.readonly) records
|
||||||
|
@ -1109,7 +1109,7 @@ render_resources records
|
||||||
-> Array (HH.HTML w Action)
|
-> Array (HH.HTML w Action)
|
||||||
rr_box colors title header dp rrs =
|
rr_box colors title header dp rrs =
|
||||||
if A.length rrs > 0
|
if A.length rrs > 0
|
||||||
then [ Bulma.box_with_tag colors title [Bulma.table_ [C.margin_left 3] [] [header, dp rrs]] ]
|
then [ Style.box_with_tag colors title [Style.table_ [C.margin_left 3] [] [header, dp rrs]] ]
|
||||||
else []
|
else []
|
||||||
--title_col_props = C.is 1
|
--title_col_props = C.is 1
|
||||||
|
|
||||||
|
@ -1120,7 +1120,7 @@ render_resources records
|
||||||
# A.intersperse [emptyline] -- -> [[hh], [line], [hh], [line], [h]]
|
# A.intersperse [emptyline] -- -> [[hh], [line], [hh], [line], [h]]
|
||||||
# A.concat -- -> [h h line h h line h]
|
# A.concat -- -> [h h line h h line h]
|
||||||
|
|
||||||
emptyline = HH.tr_ [ Bulma.txt_name "", HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [] ]
|
emptyline = HH.tr_ [ Style.txt_name "", HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [] ]
|
||||||
|
|
||||||
table_content records_ = HH.tbody_ $ map rows records_
|
table_content records_ = HH.tbody_ $ map rows records_
|
||||||
rows rr = if rr.readonly
|
rows rr = if rr.readonly
|
||||||
|
@ -1142,141 +1142,141 @@ render_resources records
|
||||||
, HH.td_ [ HH.text $ maybe "" show rr.minttl ]
|
, HH.td_ [ HH.text $ maybe "" show rr.minttl ]
|
||||||
]
|
]
|
||||||
"SRV" ->
|
"SRV" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "tcp" show rr.protocol ]
|
, HH.td_ [ Style.p $ maybe "tcp" show rr.protocol ]
|
||||||
, HH.td_ [ Bulma.p rr.target ]
|
, HH.td_ [ Style.p rr.target ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show rr.port ]
|
, HH.td_ [ Style.p $ maybe "" show rr.port ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show rr.priority ]
|
, HH.td_ [ Style.p $ maybe "" show rr.priority ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show rr.weight ]
|
, HH.td_ [ Style.p $ maybe "" show rr.weight ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
"CAA" ->
|
"CAA" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
] <> case rr.caa of
|
] <> case rr.caa of
|
||||||
Just caa ->
|
Just caa ->
|
||||||
[ HH.td_ [ Bulma.p $ show caa.flag ]
|
[ HH.td_ [ Style.p $ show caa.flag ]
|
||||||
, HH.td_ [ Bulma.p $ show caa.tag ]
|
, HH.td_ [ Style.p $ show caa.tag ]
|
||||||
, HH.td_ [ Bulma.p caa.value ]
|
, HH.td_ [ Style.p caa.value ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
Nothing -> [Bulma.p "Problem: there is no CAA data." ]
|
Nothing -> [Style.p "Problem: there is no CAA data." ]
|
||||||
"SPF" ->
|
"SPF" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed.
|
-- , HH.td_ [ Style.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_ [ Style.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_ [ Style.p $ maybe "" (A.fold <<< A.intersperse " " <<< map show_modifier) rr.modifiers ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" fancy_qualifier_display rr.q ]
|
, HH.td_ [ Style.p $ maybe "" fancy_qualifier_display rr.q ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
"DKIM" ->
|
"DKIM" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
] <> case rr.dkim of
|
] <> case rr.dkim of
|
||||||
Just dkim ->
|
Just dkim ->
|
||||||
[
|
[
|
||||||
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DKIM1.
|
-- , HH.td_ [ Style.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DKIM1.
|
||||||
HH.td_ [ Bulma.p $ maybe "" show dkim.h ]
|
HH.td_ [ Style.p $ maybe "" show dkim.h ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dkim.k ]
|
, HH.td_ [ Style.p $ maybe "" show dkim.k ]
|
||||||
, HH.td_ [ Bulma.p $ CP.take 20 dkim.p ]
|
, HH.td_ [ Style.p $ CP.take 20 dkim.p ]
|
||||||
, HH.td_ [ Bulma.p $ fromMaybe "" dkim.n ]
|
, HH.td_ [ Style.p $ fromMaybe "" dkim.n ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
Nothing -> [Bulma.p "Problem: there is no DKIM data." ]
|
Nothing -> [Style.p "Problem: there is no DKIM data." ]
|
||||||
"DMARC" ->
|
"DMARC" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
] <> case rr.dmarc of
|
] <> case rr.dmarc of
|
||||||
Just dmarc ->
|
Just dmarc ->
|
||||||
[
|
[
|
||||||
-- , HH.td_ [ Bulma.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DMARC1.
|
-- , HH.td_ [ Style.p $ maybe "(default)" id rr.v ] -- For now, version isn't displayed. Assume DMARC1.
|
||||||
HH.td_ [ Bulma.p $ show dmarc.p ]
|
HH.td_ [ Style.p $ show dmarc.p ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.sp ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.sp ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.adkim ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.adkim ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.aspf ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.aspf ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.pct ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.pct ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.fo ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.fo ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show dmarc.ri ]
|
, HH.td_ [ Style.p $ maybe "" show dmarc.ri ]
|
||||||
-- TODO? rua & ruf
|
-- TODO? rua & ruf
|
||||||
-- , HH.td_ [ ] -- For now, assume AFRF.
|
-- , HH.td_ [ ] -- For now, assume AFRF.
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
Nothing -> [Bulma.p "Problem: there is no DMARC data." ]
|
Nothing -> [Style.p "Problem: there is no DMARC data." ]
|
||||||
"MX" ->
|
"MX" ->
|
||||||
[ HH.td_ [ Bulma.p rr.name ]
|
[ HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "" show rr.priority ]
|
, HH.td_ [ Style.p $ maybe "" show rr.priority ]
|
||||||
, HH.td_ [ Bulma.p rr.target ]
|
, HH.td_ [ Style.p rr.target ]
|
||||||
, if rr.readonly
|
, if rr.readonly
|
||||||
then HH.td_ [ Bulma.btn_readonly ]
|
then HH.td_ [ Style.btn_readonly ]
|
||||||
else HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
]
|
]
|
||||||
_ ->
|
_ ->
|
||||||
[ Bulma.txt_name rr.rrtype
|
[ Style.txt_name rr.rrtype
|
||||||
, HH.td_ [ Bulma.p rr.name ]
|
, HH.td_ [ Style.p rr.name ]
|
||||||
, HH.td_ [ Bulma.p $ show rr.ttl ]
|
, HH.td_ [ Style.p $ show rr.ttl ]
|
||||||
, HH.td_ [ Bulma.p rr.target ]
|
, HH.td_ [ Style.p rr.target ]
|
||||||
] <> if rr.readonly
|
] <> if rr.readonly
|
||||||
then [ HH.td_ [ Bulma.btn_readonly ] ]
|
then [ HH.td_ [ Style.btn_readonly ] ]
|
||||||
else [ HH.td_ [ Bulma.btn_modify (CreateUpdateRRModal rr.rrid), Bulma.btn_delete (DeleteRRModal rr.rrid) ]
|
else [ HH.td_ [ Style.btn_modify (CreateUpdateRRModal rr.rrid), Style.btn_delete (DeleteRRModal rr.rrid) ]
|
||||||
, HH.td_ [ maybe (show_token_or_btn rr) Bulma.p rr.token ]
|
, HH.td_ [ maybe (show_token_or_btn rr) Style.p rr.token ]
|
||||||
]
|
]
|
||||||
|
|
||||||
show_token_or_btn rr =
|
show_token_or_btn rr =
|
||||||
case rr.rrtype of
|
case rr.rrtype of
|
||||||
"A" -> Bulma.btn_ [C.is_small] "🏁 Ask for a token" (NewToken rr.rrid)
|
"A" -> Style.btn_ [C.is_small] "🏁 Ask for a token" (NewToken rr.rrid)
|
||||||
"AAAA" -> Bulma.btn_ [C.is_small] "🏁 Ask for a token" (NewToken rr.rrid)
|
"AAAA" -> Style.btn_ [C.is_small] "🏁 Ask for a token" (NewToken rr.rrid)
|
||||||
_ -> HH.text ""
|
_ -> HH.text ""
|
||||||
|
|
||||||
fancy_qualifier_display :: RR.Qualifier -> String
|
fancy_qualifier_display :: RR.Qualifier -> String
|
||||||
fancy_qualifier_display qualifier = "(" <> show_qualifier_char qualifier <> ") " <> show_qualifier qualifier
|
fancy_qualifier_display qualifier = "(" <> show_qualifier_char qualifier <> ") " <> show_qualifier qualifier
|
||||||
|
|
||||||
display_mechanisms :: forall w. Array RR.Mechanism -> HH.HTML w Action
|
display_mechanisms :: forall w. Array RR.Mechanism -> HH.HTML w Action
|
||||||
display_mechanisms [] = Bulma.p "You don't have any mechanism."
|
display_mechanisms [] = Style.p "You don't have any mechanism."
|
||||||
display_mechanisms ms =
|
display_mechanisms ms =
|
||||||
Bulma.table [] [ Bulma.mechanism_table_header, HH.tbody_ $ map render_mechanism_row $ attach_id 0 ms]
|
Style.table [] [ Style.mechanism_table_header, HH.tbody_ $ map render_mechanism_row $ attach_id 0 ms]
|
||||||
where
|
where
|
||||||
render_mechanism_row :: (Tuple Int RR.Mechanism) -> HH.HTML w Action
|
render_mechanism_row :: (Tuple Int RR.Mechanism) -> HH.HTML w Action
|
||||||
render_mechanism_row (Tuple i m) = HH.tr_
|
render_mechanism_row (Tuple i m) = HH.tr_
|
||||||
[ Bulma.txt_name $ maybe "" show_qualifier m.q
|
[ Style.txt_name $ maybe "" show_qualifier m.q
|
||||||
, HH.td_ [ Bulma.p $ show_mechanism_type m.t ]
|
, HH.td_ [ Style.p $ show_mechanism_type m.t ]
|
||||||
, HH.td_ [ Bulma.p m.v ]
|
, HH.td_ [ Style.p m.v ]
|
||||||
, HH.td_ [ Bulma.alert_btn "x" (SPF_remove_mechanism i) ]
|
, HH.td_ [ Style.alert_btn "x" (SPF_remove_mechanism i) ]
|
||||||
]
|
]
|
||||||
|
|
||||||
display_modifiers :: forall w. Array RR.Modifier -> HH.HTML w Action
|
display_modifiers :: forall w. Array RR.Modifier -> HH.HTML w Action
|
||||||
display_modifiers [] = Bulma.p "You don't have any modifier."
|
display_modifiers [] = Style.p "You don't have any modifier."
|
||||||
display_modifiers ms =
|
display_modifiers ms =
|
||||||
Bulma.table [] [ Bulma.modifier_table_header, HH.tbody_ $ map render_modifier_row $ attach_id 0 ms]
|
Style.table [] [ Style.modifier_table_header, HH.tbody_ $ map render_modifier_row $ attach_id 0 ms]
|
||||||
where
|
where
|
||||||
render_modifier_row :: (Tuple Int RR.Modifier) -> HH.HTML w Action
|
render_modifier_row :: (Tuple Int RR.Modifier) -> HH.HTML w Action
|
||||||
render_modifier_row (Tuple i m) = HH.tr_
|
render_modifier_row (Tuple i m) = HH.tr_
|
||||||
[ HH.td_ [ Bulma.p $ show_modifier_type m.t ]
|
[ HH.td_ [ Style.p $ show_modifier_type m.t ]
|
||||||
, HH.td_ [ Bulma.p m.v ]
|
, HH.td_ [ Style.p m.v ]
|
||||||
, HH.td_ [ Bulma.alert_btn "x" (SPF_remove_modifier i) ]
|
, HH.td_ [ Style.alert_btn "x" (SPF_remove_modifier i) ]
|
||||||
]
|
]
|
||||||
|
|
||||||
display_dmarc_mail_addresses :: forall w. (Int -> Action) -> Array DMARC.DMARCURI -> HH.HTML w Action
|
display_dmarc_mail_addresses :: forall w. (Int -> Action) -> Array DMARC.DMARCURI -> HH.HTML w Action
|
||||||
display_dmarc_mail_addresses f ms =
|
display_dmarc_mail_addresses f ms =
|
||||||
Bulma.table [] [ Bulma.dmarc_dmarcuri_table_header, HH.tbody_ $ map render_dmarcuri_row $ attach_id 0 ms]
|
Style.table [] [ Style.dmarc_dmarcuri_table_header, HH.tbody_ $ map render_dmarcuri_row $ attach_id 0 ms]
|
||||||
where
|
where
|
||||||
render_dmarcuri_row :: (Tuple Int DMARC.DMARCURI) -> HH.HTML w Action
|
render_dmarcuri_row :: (Tuple Int DMARC.DMARCURI) -> HH.HTML w Action
|
||||||
render_dmarcuri_row (Tuple i m) = HH.tr_
|
render_dmarcuri_row (Tuple i m) = HH.tr_
|
||||||
[ HH.td_ [ Bulma.p m.mail ]
|
[ HH.td_ [ Style.p m.mail ]
|
||||||
, HH.td_ [ Bulma.p $ maybe "(no size limit)" show m.limit ]
|
, HH.td_ [ Style.p $ maybe "(no size limit)" show m.limit ]
|
||||||
, HH.td_ [ Bulma.alert_btn "x" (f i) ]
|
, HH.td_ [ Style.alert_btn "x" (f i) ]
|
||||||
]
|
]
|
||||||
|
|
||||||
baseRecords :: Array String
|
baseRecords :: Array String
|
||||||
|
@ -1286,35 +1286,35 @@ baseRecords = [ "A", "AAAA", "CNAME", "TXT", "NS" ]
|
||||||
|
|
||||||
render_new_records :: forall (w :: Type). State -> HH.HTML w Action
|
render_new_records :: forall (w :: Type). State -> HH.HTML w Action
|
||||||
render_new_records _
|
render_new_records _
|
||||||
= Bulma.hdiv
|
= Style.hdiv
|
||||||
[ Bulma.h1 "Adding new records"
|
[ Style.h1 "Adding new records"
|
||||||
-- use "level" to get horizontal buttons next to each other (probably vertical on mobile)
|
-- use "level" to get horizontal buttons next to each other (probably vertical on mobile)
|
||||||
, Bulma.level [
|
, Style.level [
|
||||||
Bulma.btn "A" (CreateNewRRModal A)
|
Style.btn "A" (CreateNewRRModal A)
|
||||||
, Bulma.btn "AAAA" (CreateNewRRModal AAAA)
|
, Style.btn "AAAA" (CreateNewRRModal AAAA)
|
||||||
, Bulma.btn "TXT" (CreateNewRRModal TXT)
|
, Style.btn "TXT" (CreateNewRRModal TXT)
|
||||||
, Bulma.btn "CNAME" (CreateNewRRModal CNAME)
|
, Style.btn "CNAME" (CreateNewRRModal CNAME)
|
||||||
, Bulma.btn "NS" (CreateNewRRModal NS)
|
, Style.btn "NS" (CreateNewRRModal NS)
|
||||||
, Bulma.btn "MX" (CreateNewRRModal MX)
|
, Style.btn "MX" (CreateNewRRModal MX)
|
||||||
, Bulma.btn "SRV" (CreateNewRRModal SRV)
|
, Style.btn "SRV" (CreateNewRRModal SRV)
|
||||||
] []
|
] []
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h1 "Special records about certifications and the mail system"
|
, Style.h1 "Special records about certifications and the mail system"
|
||||||
-- use "level" to get horizontal buttons next to each other (probably vertical on mobile)
|
-- use "level" to get horizontal buttons next to each other (probably vertical on mobile)
|
||||||
, Bulma.level [
|
, Style.level [
|
||||||
Bulma.btn "CAA" (CreateNewRRModal CAA)
|
Style.btn "CAA" (CreateNewRRModal CAA)
|
||||||
, Bulma.btn "SPF" (CreateNewRRModal SPF)
|
, Style.btn "SPF" (CreateNewRRModal SPF)
|
||||||
, Bulma.btn "DKIM" (CreateNewRRModal DKIM)
|
, Style.btn "DKIM" (CreateNewRRModal DKIM)
|
||||||
, Bulma.btn "DMARC" (CreateNewRRModal DMARC)
|
, Style.btn "DMARC" (CreateNewRRModal DMARC)
|
||||||
] []
|
] []
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.level [
|
, Style.level [
|
||||||
Bulma.btn "Get the final zone file" AskZoneFile
|
Style.btn "Get the final zone file" AskZoneFile
|
||||||
] [HH.text "For debug purposes. ⚠"]
|
] [HH.text "For debug purposes. ⚠"]
|
||||||
]
|
]
|
||||||
|
|
||||||
render_zonefile :: forall (w :: Type). Maybe String -> HH.HTML w Action
|
render_zonefile :: forall (w :: Type). Maybe String -> HH.HTML w Action
|
||||||
render_zonefile zonefile = Bulma.box [ maybe (HH.text "") (\x -> HH.pre_ [HH.text x]) zonefile ]
|
render_zonefile zonefile = Style.box [ maybe (HH.text "") (\x -> HH.pre_ [HH.text x]) zonefile ]
|
||||||
|
|
||||||
-- ACTIONS
|
-- ACTIONS
|
||||||
|
|
||||||
|
|
|
@ -1,12 +1,75 @@
|
||||||
module App.Style where
|
module App.Style
|
||||||
|
( module Bulma
|
||||||
|
, alert_btn_abbr
|
||||||
|
, btn_abbr
|
||||||
|
, btn_abbr_
|
||||||
|
, btn_add
|
||||||
|
, btn_delete
|
||||||
|
, btn_delete_ro
|
||||||
|
, btn_modify
|
||||||
|
, btn_modify_ro
|
||||||
|
, btn_readonly
|
||||||
|
, btn_ro
|
||||||
|
, btn_save
|
||||||
|
, btn_validation
|
||||||
|
, btn_validation_
|
||||||
|
, caa_table_header
|
||||||
|
, dkim_notes_header
|
||||||
|
, dkim_table_header
|
||||||
|
, dmarc_dkim_policy_header
|
||||||
|
, dmarc_dmarcuri_table_header
|
||||||
|
, dmarc_policy_header
|
||||||
|
, dmarc_report_interval_header
|
||||||
|
, dmarc_report_on_header
|
||||||
|
, dmarc_sample_rate_header
|
||||||
|
, dmarc_spf_policy_header
|
||||||
|
, dmarc_subdom_policy_header
|
||||||
|
, dmarc_table_header
|
||||||
|
, email_input
|
||||||
|
, expire_soa_header
|
||||||
|
, mechanism_table_header
|
||||||
|
, minttl_soa_header
|
||||||
|
, mname_soa_header
|
||||||
|
, modifier_table_header
|
||||||
|
, mx_table_header
|
||||||
|
, name_header
|
||||||
|
, name_soa_header
|
||||||
|
, password_input
|
||||||
|
, password_input_confirmation
|
||||||
|
, password_input_new
|
||||||
|
, port_header
|
||||||
|
, priority_header
|
||||||
|
, protocol_header
|
||||||
|
, refresh_soa_header
|
||||||
|
, retry_soa_header
|
||||||
|
, rname_soa_header
|
||||||
|
, serial_soa_header
|
||||||
|
, simple_table_header
|
||||||
|
, simple_table_header_ro
|
||||||
|
, soa_table_header
|
||||||
|
, spf_table_header
|
||||||
|
, srv_default_policy_header
|
||||||
|
, srv_mechanisms_header
|
||||||
|
, srv_modifiers_header
|
||||||
|
, srv_table_header
|
||||||
|
, table_header_owned_domains
|
||||||
|
, table_header_shared_domains
|
||||||
|
, target_header
|
||||||
|
, token_header
|
||||||
|
, token_input
|
||||||
|
, ttl_header
|
||||||
|
, txt_name
|
||||||
|
, username_input
|
||||||
|
, weight_header
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Prelude (($), (<>))
|
||||||
import Bulma
|
import Bulma
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
|
|
||||||
import Data.Maybe (Maybe, fromMaybe)
|
import DOM.HTML.Indexed.AutocompleteType (AutocompleteType(..))
|
||||||
import Data.Tuple (Tuple, fst, snd)
|
|
||||||
import Halogen.HTML as HH
|
import Halogen.HTML as HH
|
||||||
import DOM.HTML.Indexed as DHI
|
|
||||||
import Halogen.HTML.Properties as HP
|
import Halogen.HTML.Properties as HP
|
||||||
import Halogen.HTML.Events as HE
|
import Halogen.HTML.Events as HE
|
||||||
|
|
||||||
|
@ -449,6 +512,7 @@ soa_table_header
|
||||||
, HH.th_ [ expire_soa_header ]
|
, HH.th_ [ expire_soa_header ]
|
||||||
, HH.th_ [ minttl_soa_header ]
|
, HH.th_ [ minttl_soa_header ]
|
||||||
]
|
]
|
||||||
|
]
|
||||||
|
|
||||||
btn_validation_ :: forall w i. String -> HH.HTML w i
|
btn_validation_ :: forall w i. String -> HH.HTML w i
|
||||||
btn_validation_ str = HH.button
|
btn_validation_ str = HH.button
|
||||||
|
|
|
@ -1,22 +1,22 @@
|
||||||
module App.Text.Explanations where
|
module App.Text.Explanations where
|
||||||
import Halogen.HTML as HH
|
import Halogen.HTML as HH
|
||||||
import Halogen.HTML.Properties as HP
|
import Halogen.HTML.Properties as HP
|
||||||
import Bulma as Bulma
|
import App.Style as Style
|
||||||
import CSSClasses as C
|
import CSSClasses as C
|
||||||
|
|
||||||
expl' :: forall w i. String -> HH.HTML w i
|
expl' :: forall w i. String -> HH.HTML w i
|
||||||
expl' text = expl [Bulma.p text]
|
expl' text = expl [Style.p text]
|
||||||
expl :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
expl :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
||||||
expl content = Bulma.div_content [] [ Bulma.explanation content ]
|
expl content = Style.div_content [] [ Style.explanation content ]
|
||||||
expl_txt :: forall w i. String -> HH.HTML w i
|
expl_txt :: forall w i. String -> HH.HTML w i
|
||||||
expl_txt content = Bulma.explanation [ Bulma.p content ]
|
expl_txt content = Style.explanation [ Style.p content ]
|
||||||
|
|
||||||
col :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
col :: forall w i. Array (HH.HTML w i) -> HH.HTML w i
|
||||||
col arr = Bulma.column_ [ Bulma.box arr ]
|
col arr = Style.column_ [ Style.box arr ]
|
||||||
|
|
||||||
tokens :: forall w i. HH.HTML w i
|
tokens :: forall w i. HH.HTML w i
|
||||||
tokens = HH.div_
|
tokens = HH.div_
|
||||||
[ Bulma.h3 "What are tokens?"
|
[ Style.h3 "What are tokens?"
|
||||||
, expl' """
|
, expl' """
|
||||||
Tokens are a simple way to update a resource record (A or AAAA) with your current IP address.
|
Tokens are a simple way to update a resource record (A or AAAA) with your current IP address.
|
||||||
"""
|
"""
|
||||||
|
@ -30,61 +30,61 @@ tokens = HH.div_
|
||||||
, HH.u_ [HH.text "<your-token>"]
|
, HH.u_ [HH.text "<your-token>"]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
, Bulma.p "For example: https://www.netlib.re/token-update/53be0c45-61c4-4d29-8ae9-c2cc8767603d"
|
, Style.p "For example: https://www.netlib.re/token-update/53be0c45-61c4-4d29-8ae9-c2cc8767603d"
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "How to automate the update of my IP address?"
|
, Style.h3 "How to automate the update of my IP address?"
|
||||||
, Bulma.p "On Linux, you can make your computer access the update link with the following command."
|
, Style.p "On Linux, you can make your computer access the update link with the following command."
|
||||||
, expl [ Bulma.strong "wget https://www.netlib.re/token-update/<your-token>" ]
|
, expl [ Style.strong "wget https://www.netlib.re/token-update/<your-token>" ]
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
No need for a more complex program. This works just fine.
|
No need for a more complex program. This works just fine.
|
||||||
And you can run this command every hour.
|
And you can run this command every hour.
|
||||||
For example, in your crontab (Linux and Unix related):
|
For example, in your crontab (Linux and Unix related):
|
||||||
"""
|
"""
|
||||||
, expl [ Bulma.strong "0 * * * * wget <url>" ]
|
, expl [ Style.strong "0 * * * * wget <url>" ]
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Commands for other operating systems may differ, but you get the idea.
|
Commands for other operating systems may differ, but you get the idea.
|
||||||
"""
|
"""
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "The obvious trap ⚠"
|
, Style.h3 "The obvious trap ⚠"
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Make sure to access the website using the related IP address.
|
Make sure to access the website using the related IP address.
|
||||||
To update an IPv6 address (AAAA), force your application to access the URL using an IPv6 address.
|
To update an IPv6 address (AAAA), force your application to access the URL using an IPv6 address.
|
||||||
"""
|
"""
|
||||||
, expl [ HH.p_ [ Bulma.strong "wget -6 <url>" ]
|
, expl [ HH.p_ [ Style.strong "wget -6 <url>" ]
|
||||||
, HH.p_ [ HH.text "To force the use of an IPv6 address." ]
|
, HH.p_ [ HH.text "To force the use of an IPv6 address." ]
|
||||||
, HH.p_ [ Bulma.strong "wget -4 <url>" ]
|
, HH.p_ [ Style.strong "wget -4 <url>" ]
|
||||||
, HH.p_ [ HH.text "To force the use of an IPv4 address." ]
|
, HH.p_ [ HH.text "To force the use of an IPv4 address." ]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
basics :: forall w i. HH.HTML w i
|
basics :: forall w i. HH.HTML w i
|
||||||
basics = HH.div_
|
basics = HH.div_
|
||||||
[ Bulma.h3 "Basics of DNS"
|
[ Style.h3 "Basics of DNS"
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
The domain name system (DNS) enables people share a name instead of an address to find a website or service.
|
The domain name system (DNS) enables people share a name instead of an address to find a website or service.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
To configure a zone, the first steps are trivial.
|
To configure a zone, the first steps are trivial.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "I have something to host (A and AAAA records)."
|
, Style.h3 "I have something to host (A and AAAA records)."
|
||||||
, expl' "Let's assume you have a web server and you host your website somewhere."
|
, expl' "Let's assume you have a web server and you host your website somewhere."
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
You want an A (IPv4) or AAAA (IPv6) record pointing to your server, named "enigma" for example.
|
You want an A (IPv4) or AAAA (IPv6) record pointing to your server, named "enigma" for example.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "You need other names pointing to your server (CNAME records)."
|
, Style.h3 "You need other names pointing to your server (CNAME records)."
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
You may not want to use the name of your server "enigma" directly.
|
You may not want to use the name of your server "enigma" directly.
|
||||||
Instead, you may want the usual names for your services, such as "www" or "blog".
|
Instead, you may want the usual names for your services, such as "www" or "blog".
|
||||||
CNAME records are basically aliases, exactly to that end.
|
CNAME records are basically aliases, exactly to that end.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "If you have other servers, just add more A or AAAA records."
|
, Style.h3 "If you have other servers, just add more A or AAAA records."
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Tip: choose relevant names for your servers then add CNAME records.
|
Tip: choose relevant names for your servers then add CNAME records.
|
||||||
For example, you can have an A record named "server1" and a CNAME "www" pointing to it.
|
For example, you can have an A record named "server1" and a CNAME "www" pointing to it.
|
||||||
The service isn't pointing to an actual IP address directly,
|
The service isn't pointing to an actual IP address directly,
|
||||||
|
@ -92,24 +92,24 @@ basics = HH.div_
|
||||||
You don't need to remember the IP address of each of your servers.
|
You don't need to remember the IP address of each of your servers.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "I want an email server."
|
, Style.h3 "I want an email server."
|
||||||
, expl' """
|
, expl' """
|
||||||
Hosting a mail server is quite complex.
|
Hosting a mail server is quite complex.
|
||||||
This section will focus on the main parts regarding the DNS.
|
This section will focus on the main parts regarding the DNS.
|
||||||
"""
|
"""
|
||||||
, Bulma.notification_danger' """
|
, Style.notification_danger' """
|
||||||
The actual configuration of your mail server is complex and depends on your choice of software.
|
The actual configuration of your mail server is complex and depends on your choice of software.
|
||||||
This won't be covered here.
|
This won't be covered here.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
You need an MX record pointing to your "www" A (or AAAA) record.
|
You need an MX record pointing to your "www" A (or AAAA) record.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Having an MX record isn't enough to handle a mail server.
|
Having an MX record isn't enough to handle a mail server.
|
||||||
You need to use a few spam mitigation mechanisms.
|
You need to use a few spam mitigation mechanisms.
|
||||||
"""
|
"""
|
||||||
, Bulma.columns_
|
, Style.columns_
|
||||||
[ col
|
[ col
|
||||||
[ expl' """
|
[ expl' """
|
||||||
Spam mitigation 1: tell what are the right mail servers for your domain with Sender Policy Framework (SPF).
|
Spam mitigation 1: tell what are the right mail servers for your domain with Sender Policy Framework (SPF).
|
||||||
|
@ -138,27 +138,27 @@ basics = HH.div_
|
||||||
, expl_txt """
|
, expl_txt """
|
||||||
Last but not least, DMARC.
|
Last but not least, DMARC.
|
||||||
"""
|
"""
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
DMARC enables to check the "From:" field of a mail, based on the SPF and DKIM mechanisms.
|
DMARC enables to check the "From:" field of a mail, based on the SPF and DKIM mechanisms.
|
||||||
Thus, domains with a DMARC record enable to only allow verified mails.
|
Thus, domains with a DMARC record enable to only allow verified mails.
|
||||||
Valid emails come from an authorized IP address (SPF), are signed by the verified email server (DKIM) and have an email address coming from a verified domain (DMARC) related to the two previous spam mitigation mechanisms.
|
Valid emails come from an authorized IP address (SPF), are signed by the verified email server (DKIM) and have an email address coming from a verified domain (DMARC) related to the two previous spam mitigation mechanisms.
|
||||||
"""
|
"""
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
With DMARC, you won't accept an email from "hacker@example.com" because it was sent by another domain with a valid SPF and DKIM.
|
With DMARC, you won't accept an email from "hacker@example.com" because it was sent by another domain with a valid SPF and DKIM.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.hr
|
, Style.hr
|
||||||
, Bulma.h3 "How to automate the update of my IP address?"
|
, Style.h3 "How to automate the update of my IP address?"
|
||||||
, Bulma.p "Check out the \"Tokens? 🤨\" tab."
|
, Style.p "Check out the \"Tokens? 🤨\" tab."
|
||||||
]
|
]
|
||||||
|
|
||||||
a_introduction :: forall w i. Array (HH.HTML w i)
|
a_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
a_introduction =
|
a_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The A record enables to bind an IPv4 address to a domain.
|
The A record enables to bind an IPv4 address to a domain.
|
||||||
"""
|
"""
|
||||||
, HH.p []
|
, HH.p []
|
||||||
|
@ -175,7 +175,7 @@ a_introduction =
|
||||||
|
|
||||||
aaaa_introduction :: forall w i. Array (HH.HTML w i)
|
aaaa_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
aaaa_introduction =
|
aaaa_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The AAAA record enables to bind an IPv6 address to a domain.
|
The AAAA record enables to bind an IPv6 address to a domain.
|
||||||
"""
|
"""
|
||||||
, HH.p []
|
, HH.p []
|
||||||
|
@ -192,7 +192,7 @@ aaaa_introduction =
|
||||||
|
|
||||||
cname_introduction :: forall w i. Array (HH.HTML w i)
|
cname_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
cname_introduction =
|
cname_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The CNAME record enables to provide alternative names to records.
|
The CNAME record enables to provide alternative names to records.
|
||||||
"""
|
"""
|
||||||
, HH.p []
|
, HH.p []
|
||||||
|
@ -209,7 +209,7 @@ cname_introduction =
|
||||||
|
|
||||||
mx_introduction :: forall w i. Array (HH.HTML w i)
|
mx_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
mx_introduction =
|
mx_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The MX record enables to add a mail server to your zone.
|
The MX record enables to add a mail server to your zone.
|
||||||
"""
|
"""
|
||||||
, HH.p []
|
, HH.p []
|
||||||
|
@ -221,20 +221,20 @@ mx_introduction =
|
||||||
This page talks about the DNS aspect of it, but doesn't cover all you need to know to actually host a mail server, by a long shot.
|
This page talks about the DNS aspect of it, but doesn't cover all you need to know to actually host a mail server, by a long shot.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Anyway, the MX record itself is simple to understand.
|
Anyway, the MX record itself is simple to understand.
|
||||||
Let's say you have a server named "server1" with your mail service.
|
Let's say you have a server named "server1" with your mail service.
|
||||||
The MX record can be named "mail" and it will target "server1".
|
The MX record can be named "mail" and it will target "server1".
|
||||||
Of course, "server1" needs a record for its IP address (A or AAAA).
|
Of course, "server1" needs a record for its IP address (A or AAAA).
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
The priority field is important only in case you have multiple mail servers; keep the default value.
|
The priority field is important only in case you have multiple mail servers; keep the default value.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
txt_introduction :: forall w i. Array (HH.HTML w i)
|
txt_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
txt_introduction =
|
txt_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The TXT record enables to declare a small text.
|
The TXT record enables to declare a small text.
|
||||||
"""
|
"""
|
||||||
, HH.p []
|
, HH.p []
|
||||||
|
@ -246,7 +246,7 @@ txt_introduction =
|
||||||
TXT records are used in several places, for example for mail security through SPF, DKIM and DMARC records.
|
TXT records are used in several places, for example for mail security through SPF, DKIM and DMARC records.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
, Bulma.notification_danger' """
|
, Style.notification_danger' """
|
||||||
All of these specific records have a dedicated user interface on this website;
|
All of these specific records have a dedicated user interface on this website;
|
||||||
use them instead of writing these records by yourself.
|
use them instead of writing these records by yourself.
|
||||||
"""
|
"""
|
||||||
|
@ -254,19 +254,19 @@ txt_introduction =
|
||||||
|
|
||||||
ns_introduction :: forall w i. Array (HH.HTML w i)
|
ns_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
ns_introduction =
|
ns_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The NS record enables to declare a new Name Server, meaning a new server that would serve this zone.
|
The NS record enables to declare a new Name Server, meaning a new server that would serve this zone.
|
||||||
"""
|
"""
|
||||||
, Bulma.notification_danger' "🚨 Advice for beginners: do not use this resource record."
|
, Style.notification_danger' "🚨 Advice for beginners: do not use this resource record."
|
||||||
]
|
]
|
||||||
|
|
||||||
caa_introduction :: forall w i. Array (HH.HTML w i)
|
caa_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
caa_introduction =
|
caa_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
The CAA record enables to specify a certification authority that is authorized to issue certificates for the domain.
|
The CAA record enables to specify a certification authority that is authorized to issue certificates for the domain.
|
||||||
The idea is to reduce the risk of unintended certificate mis-issue.
|
The idea is to reduce the risk of unintended certificate mis-issue.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
Certification authorities (CA) may issue certificates for any domain.
|
Certification authorities (CA) may issue certificates for any domain.
|
||||||
Thus, any CA may provide certificates for a domain (let's say google.com) to any hacker that can now impersonate the domain.
|
Thus, any CA may provide certificates for a domain (let's say google.com) to any hacker that can now impersonate the domain.
|
||||||
The CAA record allows to say what is the authorized CA for the domain, preventing this kind of attacks.
|
The CAA record allows to say what is the authorized CA for the domain, preventing this kind of attacks.
|
||||||
|
@ -282,7 +282,7 @@ caa_introduction =
|
||||||
|
|
||||||
dkim_introduction :: forall w i. Array (HH.HTML w i)
|
dkim_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
dkim_introduction =
|
dkim_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
DKIM is a way to share a public signature key for the domain.
|
DKIM is a way to share a public signature key for the domain.
|
||||||
This enables emails to be signed by the sender and for the receiver to verify the origin of the mail.
|
This enables emails to be signed by the sender and for the receiver to verify the origin of the mail.
|
||||||
"""
|
"""
|
||||||
|
@ -293,14 +293,14 @@ dkim_introduction =
|
||||||
"""
|
"""
|
||||||
, HH.u_ [HH.text "selector"]
|
, HH.u_ [HH.text "selector"]
|
||||||
, HH.text " is "
|
, HH.text " is "
|
||||||
, Bulma.strong "default"
|
, Style.strong "default"
|
||||||
, HH.text "."
|
, HH.text "."
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_introduction :: forall w i. Array (HH.HTML w i)
|
dmarc_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_introduction =
|
dmarc_introduction =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
DMARC is a spam mitigation mechanism on top of SPF and DKIM.
|
DMARC is a spam mitigation mechanism on top of SPF and DKIM.
|
||||||
Upon receiving a mail, the server checks whether the "From:" field of the mail is consistent with the SPF and DKIM
|
Upon receiving a mail, the server checks whether the "From:" field of the mail is consistent with the SPF and DKIM
|
||||||
records of the sender's domain.
|
records of the sender's domain.
|
||||||
|
@ -311,11 +311,11 @@ dmarc_introduction =
|
||||||
|
|
||||||
dmarc_policy :: forall w i. Array (HH.HTML w i)
|
dmarc_policy :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_policy =
|
dmarc_policy =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
DMARC record enables to tell receivers what to do with a non-conforming message,
|
DMARC record enables to tell receivers what to do with a non-conforming message,
|
||||||
i.e. a message that wasn't properly secured with SPF and DKIM.
|
i.e. a message that wasn't properly secured with SPF and DKIM.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
This message can either be accepted ("None") or rejected, or even quarantined, meaning to be considered as suspicious.
|
This message can either be accepted ("None") or rejected, or even quarantined, meaning to be considered as suspicious.
|
||||||
This can take different forms, such as being flagged, marked as spam or have a high "spam score", it's up to the receiver.
|
This can take different forms, such as being flagged, marked as spam or have a high "spam score", it's up to the receiver.
|
||||||
"""
|
"""
|
||||||
|
@ -323,34 +323,34 @@ dmarc_policy =
|
||||||
|
|
||||||
dmarc_sp_policy :: forall w i. Array (HH.HTML w i)
|
dmarc_sp_policy :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_sp_policy =
|
dmarc_sp_policy =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Same as the previous entry, but for sub-domains.
|
Same as the previous entry, but for sub-domains.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_adkim :: forall w i. Array (HH.HTML w i)
|
dmarc_adkim :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_adkim =
|
dmarc_adkim =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Consistency policy for DKIM. Tell what should be considered acceptable.
|
Consistency policy for DKIM. Tell what should be considered acceptable.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
This is about the relation between the email "From:" field and the domain field of the DKIM signature ("d:").
|
This is about the relation between the email "From:" field and the domain field of the DKIM signature ("d:").
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
The policy can be either strict (both should be identical) or relaxed (both in the same Organizational Domain).
|
The policy can be either strict (both should be identical) or relaxed (both in the same Organizational Domain).
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_aspf :: forall w i. Array (HH.HTML w i)
|
dmarc_aspf :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_aspf =
|
dmarc_aspf =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Consistency policy for SPF. Tell what should be considered acceptable.
|
Consistency policy for SPF. Tell what should be considered acceptable.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
First, SPF should produce a passing result.
|
First, SPF should produce a passing result.
|
||||||
Then, the "From:" and the "MailFrom:" fields of the received email are checked.
|
Then, the "From:" and the "MailFrom:" fields of the received email are checked.
|
||||||
"""
|
"""
|
||||||
, Bulma.p """
|
, Style.p """
|
||||||
In strict mode, both fields should be identical.
|
In strict mode, both fields should be identical.
|
||||||
In relaxed mode, they can be different, but in the same Organizational Domain.
|
In relaxed mode, they can be different, but in the same Organizational Domain.
|
||||||
"""
|
"""
|
||||||
|
@ -367,28 +367,28 @@ dmarc_aspf =
|
||||||
]
|
]
|
||||||
, HH.p_
|
, HH.p_
|
||||||
[ HH.text "See "
|
[ HH.text "See "
|
||||||
, Bulma.outside_link [] "https://publicsuffix.org/" "publicsuffix.org"
|
, Style.outside_link [] "https://publicsuffix.org/" "publicsuffix.org"
|
||||||
, HH.text " for a list of Organizational Domains."
|
, HH.text " for a list of Organizational Domains."
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_contact :: forall w i. Array (HH.HTML w i)
|
dmarc_contact :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_contact =
|
dmarc_contact =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
In case you want to receive error reports, enter email addresses that should receive either an aggregated report or a detailed report of the occurring errors.
|
In case you want to receive error reports, enter email addresses that should receive either an aggregated report or a detailed report of the occurring errors.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_ri :: forall w i. Array (HH.HTML w i)
|
dmarc_ri :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_ri =
|
dmarc_ri =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Requested report interval. Default is 86400.
|
Requested report interval. Default is 86400.
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
dmarc_pct :: forall w i. Array (HH.HTML w i)
|
dmarc_pct :: forall w i. Array (HH.HTML w i)
|
||||||
dmarc_pct =
|
dmarc_pct =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Sampling rate.
|
Sampling rate.
|
||||||
Percentage of messages subjected to the requested policy.
|
Percentage of messages subjected to the requested policy.
|
||||||
"""
|
"""
|
||||||
|
@ -397,7 +397,7 @@ dmarc_pct =
|
||||||
|
|
||||||
dkim_default_algorithms :: forall w i. Array (HH.HTML w i)
|
dkim_default_algorithms :: forall w i. Array (HH.HTML w i)
|
||||||
dkim_default_algorithms =
|
dkim_default_algorithms =
|
||||||
[ Bulma.p """
|
[ Style.p """
|
||||||
Default values should be fine (RSA + SHA256), change them only if you know what you are doing.
|
Default values should be fine (RSA + SHA256), change them only if you know what you are doing.
|
||||||
Just enter your public key.
|
Just enter your public key.
|
||||||
"""
|
"""
|
||||||
|
@ -435,7 +435,7 @@ spf_introduction =
|
||||||
|
|
||||||
spf_default_behavior :: forall w i. Array (HH.HTML w i)
|
spf_default_behavior :: forall w i. Array (HH.HTML w i)
|
||||||
spf_default_behavior = [
|
spf_default_behavior = [
|
||||||
Bulma.p """
|
Style.p """
|
||||||
What should someone do when receiving a mail from your email address but not from a listed domain or IP address?
|
What should someone do when receiving a mail from your email address but not from a listed domain or IP address?
|
||||||
"""
|
"""
|
||||||
, HH.p_ [ HH.text """
|
, HH.p_ [ HH.text """
|
||||||
|
@ -464,7 +464,7 @@ spf_default_behavior = [
|
||||||
|
|
||||||
srv_introduction :: forall w i. Array (HH.HTML w i)
|
srv_introduction :: forall w i. Array (HH.HTML w i)
|
||||||
srv_introduction =
|
srv_introduction =
|
||||||
[ Bulma.p "The SRV record is a DNS resource record for specifying the location of services."
|
[ Style.p "The SRV record is a DNS resource record for specifying the location of services."
|
||||||
, HH.p_ [ HH.text "Given a specific "
|
, HH.p_ [ HH.text "Given a specific "
|
||||||
, HH.u_ [HH.text "service name"]
|
, HH.u_ [HH.text "service name"]
|
||||||
, HH.text " (which may be arbitrary) and a "
|
, HH.text " (which may be arbitrary) and a "
|
||||||
|
@ -487,38 +487,38 @@ website_abuse_address = "abuse AT netlib.re" :: String
|
||||||
|
|
||||||
legal_notice :: forall w i. HH.HTML w i
|
legal_notice :: forall w i. HH.HTML w i
|
||||||
legal_notice = HH.div_
|
legal_notice = HH.div_
|
||||||
[ Bulma.h3 "Legal Notice"
|
[ Style.h3 "Legal Notice"
|
||||||
|
|
||||||
, Bulma.strong "Website Publisher"
|
, Style.strong "Website Publisher"
|
||||||
, expl [ HH.p_ [ HH.text "You can contact this website's owner and publisher at: "
|
, expl [ HH.p_ [ HH.text "You can contact this website's owner and publisher at: "
|
||||||
, Bulma.strong website_owner_address
|
, Style.strong website_owner_address
|
||||||
]
|
]
|
||||||
, HH.p_ [ HH.text "For legal matter: "
|
, HH.p_ [ HH.text "For legal matter: "
|
||||||
, Bulma.strong website_abuse_address
|
, Style.strong website_abuse_address
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.strong "Website Hosting"
|
, Style.strong "Website Hosting"
|
||||||
, expl [ HH.p_ [ HH.text "This website is hosted by "
|
, expl [ HH.p_ [ HH.text "This website is hosted by "
|
||||||
, Bulma.strong "Alsace Réseau Neutre"
|
, Style.strong "Alsace Réseau Neutre"
|
||||||
, HH.text "."
|
, HH.text "."
|
||||||
, HH.br_
|
, HH.br_
|
||||||
, HH.text "Website: "
|
, HH.text "Website: "
|
||||||
, Bulma.outside_link [] "https://arn-fai.net" "arn-fai.net"
|
, Style.outside_link [] "https://arn-fai.net" "arn-fai.net"
|
||||||
, HH.br_
|
, HH.br_
|
||||||
, HH.text "Address & contact: "
|
, HH.text "Address & contact: "
|
||||||
, Bulma.outside_link [] "https://arn-fai.net/fr/mentions" "Legal Notice of ARN"
|
, Style.outside_link [] "https://arn-fai.net/fr/mentions" "Legal Notice of ARN"
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.strong "Intellectual Property"
|
, Style.strong "Intellectual Property"
|
||||||
, expl' """
|
, expl' """
|
||||||
The code of this website is released under the ISC License. You
|
The code of this website is released under the ISC License. You
|
||||||
are free to copy, modify, and distribute the code, provided
|
are free to copy, modify, and distribute the code, provided
|
||||||
that you comply with the terms of the ISC License.
|
that you comply with the terms of the ISC License.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.strong "Personal Data Collection"
|
, Style.strong "Personal Data Collection"
|
||||||
, expl' """
|
, expl' """
|
||||||
This website collects only the personal data necessary for its proper functioning.
|
This website collects only the personal data necessary for its proper functioning.
|
||||||
This includes data such as: a login (arbitrary set of
|
This includes data such as: a login (arbitrary set of
|
||||||
|
@ -526,12 +526,12 @@ legal_notice = HH.div_
|
||||||
to contact the owner of the domain, domain names and zone data.
|
to contact the owner of the domain, domain names and zone data.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.strong "Data Sharing"
|
, Style.strong "Data Sharing"
|
||||||
, expl' """
|
, expl' """
|
||||||
None of the collected data will be shared to third parties.
|
None of the collected data will be shared to third parties.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.strong "Data Retention"
|
, Style.strong "Data Retention"
|
||||||
, expl' """
|
, expl' """
|
||||||
The personal data collected on this website will be retained
|
The personal data collected on this website will be retained
|
||||||
for as long as necessary to fulfill the purposes for which it
|
for as long as necessary to fulfill the purposes for which it
|
||||||
|
@ -549,16 +549,16 @@ legal_notice = HH.div_
|
||||||
After this period, all data will be securely deleted.
|
After this period, all data will be securely deleted.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.strong "Liability"
|
, Style.strong "Liability"
|
||||||
, expl
|
, expl
|
||||||
[ Bulma.p
|
[ Style.p
|
||||||
"""
|
"""
|
||||||
The publisher of this website makes every effort to ensure that
|
The publisher of this website makes every effort to ensure that
|
||||||
the website functions properly and that all data is protected
|
the website functions properly and that all data is protected
|
||||||
to the best of their ability.
|
to the best of their ability.
|
||||||
"""
|
"""
|
||||||
|
|
||||||
, Bulma.p
|
, Style.p
|
||||||
"""
|
"""
|
||||||
However, despite all reasonable precautions, the publisher
|
However, despite all reasonable precautions, the publisher
|
||||||
cannot guarantee that the website will always be free of errors,
|
cannot guarantee that the website will always be free of errors,
|
||||||
|
@ -576,7 +576,7 @@ legal_notice = HH.div_
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.p
|
, Style.p
|
||||||
"""
|
"""
|
||||||
By using this website, users acknowledge that they accept the
|
By using this website, users acknowledge that they accept the
|
||||||
inherent risks associated with the use of online services. The
|
inherent risks associated with the use of online services. The
|
||||||
|
@ -585,13 +585,13 @@ legal_notice = HH.div_
|
||||||
"""
|
"""
|
||||||
]
|
]
|
||||||
|
|
||||||
, Bulma.strong "GDPR compliance"
|
, Style.strong "GDPR compliance"
|
||||||
, expl [ HH.p_ [ HH.text """
|
, expl [ HH.p_ [ HH.text """
|
||||||
You have the right to access, correct and delete your personal
|
You have the right to access, correct and delete your personal
|
||||||
data at any time via this website or by contacting us at the
|
data at any time via this website or by contacting us at the
|
||||||
following email address:
|
following email address:
|
||||||
"""
|
"""
|
||||||
, Bulma.strong website_owner_address
|
, Style.strong website_owner_address
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
|
Loading…
Add table
Reference in a new issue