This commit is contained in:
Philippe Pittoli 2023-07-14 00:35:50 +02:00
parent 5fdbcc6058
commit 15eb7d9acb

View File

@ -3,15 +3,20 @@ module App.Validation where
import Prelude import Prelude
import Data.Validation.Semigroup import Data.Validation.Semigroup
import Data.Array import Data.Array as A
import Data.Maybe import Data.Maybe
import Data.Either
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.String.Regex import Data.String.Regex as R
import Data.String.Regex.Flags as RF
import Data.String as S
import Data.Int (fromString) import Data.Int (fromString)
import App.RR import App.RR
import App.ResourceRecord (ResourceRecord) import App.ResourceRecord (ResourceRecord)
infixl 8 andThen as !>
data Attribute data Attribute
= Name = Name
| TTL | TTL
@ -40,16 +45,17 @@ name_format = "[a-zA-Z]+"
lengthIsBetween :: Attribute -> Int -> Int -> String -> V Errors String lengthIsBetween :: Attribute -> Int -> Int -> String -> V Errors String
lengthIsBetween field minlen maxlen value lengthIsBetween field minlen maxlen value
| valid_condition = invalid [ Tuple field error_message ] = if valid_condition
| otherwise = pure value then pure value
else invalid [ Tuple field error_message ]
where where
actual_len = A.length value actual_len = S.length value
valid_condition = actual_len >= minlen && actual_len <= maxlen valid_condition = actual_len >= minlen && actual_len <= maxlen
error_message = "acceptable length [" <> show minlen <> "-" <> show maxlen <> "]" error_message = "acceptable length [" <> show minlen <> "-" <> show maxlen <> "]"
matches :: Attribute -> Regex -> String -> V Errors String matches :: Attribute -> R.Regex -> String -> V Errors String
matches field regex value matches field regex value
| test regex value = pure value | R.test regex value = pure value
| otherwise = invalid [Tuple field "unacceptable format"] | otherwise = invalid [Tuple field "unacceptable format"]
intBetween :: Attribute -> Int -> Int -> Int -> V Errors Int intBetween :: Attribute -> Int -> Int -> Int -> V Errors Int
@ -60,30 +66,34 @@ intBetween field min max value
error_message = "acceptable value [" <> show min <> "-" <> show max <> "]" error_message = "acceptable value [" <> show min <> "-" <> show max <> "]"
validate_integer :: Attribute -> String -> V Errors Int validate_integer :: Attribute -> String -> V Errors Int
validate_integer field value validate_integer field string
= case fromString form.ttl of = case fromString string of
Nothing -> invalid [Tuple field "not an integer"] Nothing -> invalid [Tuple field "not an integer"]
Just i -> pure i Just i -> pure i
xx :: forall y a. y -> Array a -> y
xx f _ = f
-- Field-related validations. -- Field-related validations.
validate_name :: String -> V Errors String validate_name :: String -> V Errors String
validate_name name = ado validate_name name
_ <- lengthIsBetween Name name_min_len name_max_len name = case R.regex name_format RF.unicode of
_ <- matches Name name_format name Left error_string -> invalid [Tuple NotAnAttribute $ "error in name regex: " <> error_string]
in pure name Right regex -> verify_length !> (matches Name regex)
where
verify_length = lengthIsBetween Name name_min_len name_max_len name
validate_ttl :: String -> V Errors Int validate_ttl :: String -> V Errors Int
validate_ttl str_ttl = ado validate_ttl str_ttl
ttl <- validate_integer TTL str_ttl = is_int str_ttl !> (intBetween TTL min_ttl max_ttl) !> pure
in ado where
value <- intBetween TTL min_ttl max_ttl ttl is_int = validate_integer TTL
in pure value
validate_target :: String -> V Errors String validate_target :: String -> V Errors String
validate_target target = ado validate_target target = verify_length target !> pure
target <- lengthIsBetween Target target_min_len target_max_len target where
in pure target verify_length = lengthIsBetween Target target_min_len target_max_len
-- Resource-related validations. -- Resource-related validations.
@ -92,7 +102,7 @@ validateA form = ado
name <- validate_name form.name name <- validate_name form.name
ttl <- validate_ttl form.ttl ttl <- validate_ttl form.ttl
target <- validate_target form.target target <- validate_target form.target
in pure $ toRR_basic form.readonly form.rrid "A" name ttl target in pure $ toRR_basic form.rrid form.readonly "A" name ttl target
validateAAAA :: forall l. SimpleRR (|l) -> V Errors ResourceRecord validateAAAA :: forall l. SimpleRR (|l) -> V Errors ResourceRecord
validateAAAA _ = invalid [Tuple NotAnAttribute "validation not implemented"] validateAAAA _ = invalid [Tuple NotAnAttribute "validation not implemented"]
@ -144,6 +154,7 @@ type RRRetry = Maybe Int
type RRExpire = Maybe Int type RRExpire = Maybe Int
type RRMinttl = Maybe Int type RRMinttl = Maybe Int
toRR :: Int -> Boolean -> String -> String -> Int -> String toRR :: Int -> Boolean -> String -> String -> Int -> String
-> RRPriority -> RRPriority
-> RRPort -> RRPort
@ -187,19 +198,19 @@ toRR rrid readonly rrtype rrname ttl target
toRR_basic :: Int -> Boolean -> String -> String -> Int -> String -> ResourceRecord toRR_basic :: Int -> Boolean -> String -> String -> Int -> String -> ResourceRecord
toRR_basic rrid readonly rrtype rrname ttl target toRR_basic rrid readonly rrtype rrname ttl target
= toRR rrid readonly rrtype rrname ttl target = toRR rrid readonly rrtype rrname ttl target
Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing
-- last + priority -- last + priority
toRR_mx :: Int -> Boolean -> String -> String -> Int -> String -> Int -> ResourceRecord toRR_mx :: Int -> Boolean -> String -> String -> Int -> String -> Int -> ResourceRecord
toRR_mx rrid readonly rrtype rrname ttl target priority toRR_mx rrid readonly rrtype rrname ttl target priority
= toRR rrid readonly rrtype rrname ttl target (Just priority) = toRR rrid readonly rrtype rrname ttl target (Just priority)
Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing
-- last + port + protocol + weight -- last + port + protocol + weight
toRR_srv :: Int -> Boolean -> String -> String -> Int -> String -> Int -> Int -> String -> Int -> ResourceRecord toRR_srv :: Int -> Boolean -> String -> String -> Int -> String -> Int -> Int -> String -> Int -> ResourceRecord
toRR_srv rrid readonly rrtype rrname ttl target priority port protocol weight toRR_srv rrid readonly rrtype rrname ttl target priority port protocol weight
= toRR rrid readonly rrtype rrname ttl target (Just priority) (Just port) (Just protocol) (Just weight) = toRR rrid readonly rrtype rrname ttl target (Just priority) (Just port) (Just protocol) (Just weight)
Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing Nothing
fromLocalSimpleRRRepresentationToResourceRecord :: forall l. SimpleRR (|l) -> ResourceRecord fromLocalSimpleRRRepresentationToResourceRecord :: forall l. SimpleRR (|l) -> ResourceRecord
fromLocalSimpleRRRepresentationToResourceRecord form fromLocalSimpleRRRepresentationToResourceRecord form