Validation: cannot expect exact public key input sizes.
This commit is contained in:
parent
a9c33df22d
commit
1adb688b9b
@ -1,9 +1,7 @@
|
|||||||
-- | This module provides functions to display errors in a fancy way.
|
-- | This module provides functions to display errors in a fancy way.
|
||||||
module App.DisplayErrors where
|
module App.DisplayErrors where
|
||||||
|
|
||||||
import Prelude (show, ($), (<>), map, (<<<), (*))
|
import Prelude (show, ($), (<>))
|
||||||
|
|
||||||
import Data.Array as A
|
|
||||||
|
|
||||||
-- import Data.Foldable as Foldable
|
-- import Data.Foldable as Foldable
|
||||||
import Data.Maybe (Maybe(..), maybe)
|
import Data.Maybe (Maybe(..), maybe)
|
||||||
@ -43,14 +41,14 @@ error_to_paragraph v = Bulma.error_message (Bulma.p $ show_error_title v)
|
|||||||
ValidationDNS.VESPFMechanismIPv6 err -> maybe default_error show_error_ip6 err.error
|
ValidationDNS.VESPFMechanismIPv6 err -> maybe default_error show_error_ip6 err.error
|
||||||
ValidationDNS.VESPFModifierName err -> maybe default_error show_error_domain err.error
|
ValidationDNS.VESPFModifierName err -> maybe default_error show_error_domain err.error
|
||||||
|
|
||||||
ValidationDNS.DKIMInvalidKeySize err -> show_error_key_sizes err
|
ValidationDNS.DKIMInvalidKeySize min max -> show_error_key_sizes min max
|
||||||
)
|
)
|
||||||
where default_error = Bulma.p ""
|
where default_error = Bulma.p ""
|
||||||
|
|
||||||
show_error_key_sizes :: forall w i. Array Int -> HH.HTML w i
|
show_error_key_sizes :: forall w i. Int -> Int -> HH.HTML w i
|
||||||
show_error_key_sizes arr
|
show_error_key_sizes min max
|
||||||
= Bulma.p $ "Chosen signature algorithm only accepts those key sizes (in bits): ["
|
= Bulma.p $ "Chosen signature algorithm only accepts public key input between "
|
||||||
<> (A.fold $ A.intersperse ", " $ map (show <<< (8*_)) arr) <> "]"
|
<> 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.
|
||||||
show_error_title :: ValidationDNS.Error -> String
|
show_error_title :: ValidationDNS.Error -> String
|
||||||
@ -76,7 +74,7 @@ show_error_title v = case v of
|
|||||||
ValidationDNS.VESPFMechanismIPv6 err -> "The IPv6 address in a SPF mechanism is wrong (position: " <> show err.position <> ")"
|
ValidationDNS.VESPFMechanismIPv6 err -> "The IPv6 address in a SPF mechanism is wrong (position: " <> show err.position <> ")"
|
||||||
|
|
||||||
ValidationDNS.VESPFModifierName err -> "The domain name in a SPF modifier (EXP or REDIRECT) is wrong (position: " <> show err.position <> ")"
|
ValidationDNS.VESPFModifierName err -> "The domain name in a SPF modifier (EXP or REDIRECT) is wrong (position: " <> show err.position <> ")"
|
||||||
ValidationDNS.DKIMInvalidKeySize _ -> "Public key has an invalid length."
|
ValidationDNS.DKIMInvalidKeySize _ _ -> "Public key has an invalid length."
|
||||||
|
|
||||||
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
|
||||||
|
@ -1,6 +1,6 @@
|
|||||||
module App.Validation.DNS where
|
module App.Validation.DNS where
|
||||||
|
|
||||||
import Prelude (apply, between, bind, map, pure, ($), (-), (<), (<>))
|
import Prelude (apply, between, bind, map, pure, ($), (-), (<), (<>), (==))
|
||||||
|
|
||||||
import Control.Alt ((<|>))
|
import Control.Alt ((<|>))
|
||||||
import Data.Array as A
|
import Data.Array as A
|
||||||
@ -59,7 +59,7 @@ data Error
|
|||||||
|
|
||||||
| VESPFModifierName (G.Error DomainParser.DomainError)
|
| VESPFModifierName (G.Error DomainParser.DomainError)
|
||||||
|
|
||||||
| DKIMInvalidKeySize (Array Int)
|
| DKIMInvalidKeySize Int Int
|
||||||
|
|
||||||
type AVErrors = Array Error
|
type AVErrors = Array Error
|
||||||
|
|
||||||
@ -267,21 +267,32 @@ validationSPF form = ado
|
|||||||
, v = form.v, mechanisms = Just mechanisms
|
, v = form.v, mechanisms = Just mechanisms
|
||||||
, modifiers = Just modifiers, q = form.q }
|
, modifiers = Just modifiers, q = form.q }
|
||||||
|
|
||||||
-- | Accepted RSA key sizes = 2048 or 4096 bits, meaning 256 or 512 characters.
|
-- | Accepted RSA key sizes = 2048 or 4096 bits, 256 bits for ED25519.
|
||||||
accepted_rsa_key_sizes = [256, 512] :: Array Int
|
-- |
|
||||||
accepted_ed25519_key_sizes = [32] :: Array Int
|
-- | Since the public key representation for the RSA algorithm is in PKCS format (RFC 5958)
|
||||||
|
-- | then converted in PEM (RFC 7468), and knowing this format allows some optional parameters,
|
||||||
|
-- | it is not possible to expect an exact size for the public key input.
|
||||||
|
-- | Consequently, we expect *at least* an input of 250 bytes for public key, loosely leading
|
||||||
|
-- | to accept key sizes of at least 2048 bits. Maximum allowed key size is also arbitrary.
|
||||||
|
rsa_min_key_size = 250 :: Int
|
||||||
|
rsa_max_key_size = 1000 :: Int
|
||||||
|
|
||||||
|
-- | Contrary to RSA, ED25519 doesn't use a PEM-converted PKCS representation to exchange
|
||||||
|
-- | public keys, and the key size is 256 bits (32 bytes).
|
||||||
|
-- | This key is converted directly in base64, leading to a simple 44-byte key representation.
|
||||||
|
ed25519_key_size = 44 :: Int
|
||||||
|
|
||||||
verify_public_key :: DKIM.SignatureAlgorithm -> DKIM.PublicKey -> V (Array Error) DKIM.PublicKey
|
verify_public_key :: DKIM.SignatureAlgorithm -> DKIM.PublicKey -> V (Array Error) DKIM.PublicKey
|
||||||
verify_public_key signalgo key = case signalgo of
|
verify_public_key signalgo key = case signalgo of
|
||||||
DKIM.RSA -> ado
|
DKIM.RSA -> ado
|
||||||
k <- if A.elem (S.length key) accepted_rsa_key_sizes
|
k <- if between rsa_min_key_size rsa_max_key_size (S.length key)
|
||||||
then pure key
|
then pure key
|
||||||
else invalid [DKIMInvalidKeySize accepted_rsa_key_sizes]
|
else invalid [DKIMInvalidKeySize rsa_min_key_size rsa_max_key_size]
|
||||||
in k
|
in k
|
||||||
DKIM.ED25519 -> ado
|
DKIM.ED25519 -> ado
|
||||||
k <- if A.elem (S.length key) accepted_ed25519_key_sizes
|
k <- if S.length key == ed25519_key_size
|
||||||
then pure key
|
then pure key
|
||||||
else invalid [DKIMInvalidKeySize accepted_ed25519_key_sizes]
|
else invalid [DKIMInvalidKeySize ed25519_key_size ed25519_key_size]
|
||||||
in k
|
in k
|
||||||
|
|
||||||
validationDKIM :: ResourceRecord -> V (Array Error) ResourceRecord
|
validationDKIM :: ResourceRecord -> V (Array Error) ResourceRecord
|
||||||
|
Loading…
Reference in New Issue
Block a user