Remove confusing typing.

beta
Philippe Pittoli 2024-02-15 20:40:28 +01:00
parent 6cda323c9f
commit 5a38838f88
1 changed files with 12 additions and 12 deletions

View File

@ -1,6 +1,6 @@
module App.Validation.DNS where
import Prelude (apply, between, bind, map, pure, ($), (-), (<))
import Prelude (apply, between, bind, map, pure, ($), (-), (<), (<<<))
import Control.Alt ((<|>))
import Data.Array as A
@ -13,7 +13,7 @@ import App.ResourceRecord (ResourceRecord)
import GenericParser.SomeParsers as SomeParsers
import GenericParser.Parser as G
import GenericParser.DomainParser.Common (DomainError) as DomainParser
import GenericParser.DomainParser (sub_eof) as DomainParser
import GenericParser.DomainParser (label, sub_eof) as DomainParser
import GenericParser.IPAddress as IPAddress
import GenericParser.RFC5234 as RFC5234
@ -161,19 +161,19 @@ txt_parser = do pos <- G.current_position
-- | `parse` allows to run any parser based on `GenericParser` and provide a validation error.
-- | The actual validation error contains the parser's error including the position.
parse :: forall e v. G.Parser e v -> String -> ((G.Error e) -> Error) -> V AVErrors v
parse :: forall e v. G.Parser e v -> String -> ((G.Error e) -> Error) -> V (Array Error) v
parse (G.Parser p) str c = case p { string: str, position: 0 } of
Left x -> invalid $ [c x]
Right x -> pure x.result
validationA :: ResourceRecord -> V AVErrors ResourceRecord
validationA :: ResourceRecord -> V (Array Error) ResourceRecord
validationA form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
target <- parse IPAddress.ipv4 form.target VEIPv4
in toRR_basic form.rrid form.readonly "A" name ttl target
validationAAAA :: ResourceRecord -> V AVErrors ResourceRecord
validationAAAA :: ResourceRecord -> V (Array Error) ResourceRecord
validationAAAA form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
@ -181,21 +181,21 @@ validationAAAA form = ado
target <- parse (G.read_input IPAddress.ipv6) form.target VEIPv6
in toRR_basic form.rrid form.readonly "AAAA" name ttl target
validationTXT :: ResourceRecord -> V AVErrors ResourceRecord
validationTXT :: ResourceRecord -> V (Array Error) ResourceRecord
validationTXT form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
target <- parse txt_parser form.target VETXT
in toRR_basic form.rrid form.readonly "TXT" name ttl target
validationCNAME :: ResourceRecord -> V AVErrors ResourceRecord
validationCNAME :: ResourceRecord -> V (Array Error) ResourceRecord
validationCNAME form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
target <- parse DomainParser.sub_eof form.target VECNAME
in toRR_basic form.rrid form.readonly "CNAME" name ttl target
validationNS :: ResourceRecord -> V AVErrors ResourceRecord
validationNS :: ResourceRecord -> V (Array Error) ResourceRecord
validationNS form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
@ -210,12 +210,12 @@ protocol_parser = do
pos <- G.current_position
G.string "tcp" <|> G.string "udp" <|> G.Parser \_ -> G.failureError pos (Just InvalidProtocol)
is_between :: Int -> Int -> Int -> (Int -> Int -> Int -> Error) -> V AVErrors Int
is_between :: Int -> Int -> Int -> (Int -> Int -> Int -> Error) -> V (Array Error) Int
is_between min max n ve = if between min max n
then pure n
else invalid [ve min max n]
validationMX :: ResourceRecord -> V AVErrors ResourceRecord
validationMX :: ResourceRecord -> V (Array Error) ResourceRecord
validationMX form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
@ -223,7 +223,7 @@ validationMX form = ado
priority <- is_between min_priority max_priority (maybe 0 id form.priority) VEPriority
in toRR_mx form.rrid form.readonly "MX" name ttl target priority
validationSRV :: ResourceRecord -> V AVErrors ResourceRecord
validationSRV :: ResourceRecord -> V (Array Error) ResourceRecord
validationSRV form = ado
name <- parse DomainParser.sub_eof form.name VEName
ttl <- is_between min_ttl max_ttl form.ttl VETTL
@ -234,7 +234,7 @@ validationSRV form = ado
weight <- is_between min_weight max_weight (maybe 0 id form.weight) VEWeight
in toRR_srv form.rrid form.readonly "SRV" name ttl target priority port protocol weight
validation :: ResourceRecord -> Either AVErrors ResourceRecord
validation :: ResourceRecord -> Either (Array Error) ResourceRecord
validation entry = case entry.rrtype of
"A" -> toEither $ validationA entry
"AAAA" -> toEither $ validationAAAA entry