predicate-typed-0.5.0.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Examples.Common

Contents

Description

Common predicates for use with Refined, Refined2, and Refined3

Synopsis

date time checkers

type DateFmts = '["%Y-%m-%d", "%m/%d/%y", "%B %d %Y"] Source #

type DateTimeFmts = '["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"] Source #

type Dtip t = ParseTimeP t "%F %T" Id Source #

type Dtfmt = FormatTimeP "%F %T" Id Source #

type DdmmyyyyRE = "^(\\d{2})-(\\d{2})-(\\d{4})$" Source #

type Ddmmyyyyval = Guards '['(PrintT "guard(%d) day %d is out of range" Id, Between 1 31), '(PrintT "guard(%d) month %d is out of range" Id, Between 1 12), '(PrintT "guard(%d) year %d is out of range" Id, Between 1990 2050)] Source #

type Ddmmyyyyval' = GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31, Between 1 12, Between 1990 2050] Source #

time checkers

type Hmsip = Map (ReadP Int Id) (Resplit ":" Id) Source #

type Hmsop = GuardsDetail "%s invalid: found %d" '['("hours", Between 0 23), '("minutes", Between 0 59), '("seconds", Between 0 59)] Source #

type Hmsop' = Bools '['("hours", Between 0 23), '("minutes", Between 0 59), '("seconds", Between 0 59)] Source #

type Hmsfmt = PrintL 3 "%02d:%02d:%02d" Id Source #

type HmsRE = "^([0-1][0-9]|2[0-3]):([0-5][0-9]):([0-5][0-9])$" Source #

credit cards

type Ccip = Map (ReadP Int Id) (Ones (Remove "-" Id)) Source #

type Ccop (n :: Nat) = Guard (PrintT "expected %d digits but found %d" '(n, Len)) (Len == n) >> Luhn Id Source #

type Ccfmt (ns :: [Nat]) = ConcatMap (ShowP Id) Id >> (SplitAts ns Id >> Concat (Intercalate '["-"] Id)) Source #

type Luhnip = Map (ReadP Int Id) (Ones Id) Source #

uses builtin Luhn

type Luhnop (n :: Nat) = Msg "incorrect number of digits:" (Len == n) && Luhn Id Source #

type Luhn' (n :: Nat) = Msg "Luhn'" (Do '[Guard (PrintT "incorrect number of digits found %d but expected %d in [%s]" '(Len, n, Id)) (Len == n), Do '[Ones Id, Map (ReadP Int Id) Id, Reverse, Zip (Cycle n [1, 2]) Id, Map ((Fst Id * Snd Id) >> If (Id >= 10) (Id - 9) Id) Id, FoldMap (Sum Int) Id], Guard (PrintT "expected %d mod 10 = 0 but found %d" '(Id, Id `Mod` 10)) (Mod Id 10 == 0)]) Source #

type Luhn'' (n :: Nat) = Guard (PrintT "incorrect number of digits found %d but expected %d in [%s]" '(Len, n, ShowP Id)) (Len == n) >> (Do '[Reverse, Zip (Cycle n [1, 2]) Id, Map ((Fst Id * Snd Id) >> If (Id >= 10) (Id - 9) Id) Id, FoldMap (Sum Int) Id] >> Guard (PrintT "expected %d mod 10 = 0 but found %d" '(Id, Id `Mod` 10)) (Mod Id 10 == 0)) Source #

ssn

type Ssnip = Map (ReadP Int Id) (Rescan "^(\\d{3})-(\\d{2})-(\\d{4})$" Id >> Snd (OneP Id)) Source #

type Ssnop = BoolsQuick (PrintT "number for group %d invalid: found %d" Id) '[Between 1 899 && (Id /= 666), Between 1 99, Between 1 9999] Source #

type Ssnfmt = PrintL 3 "%03d-%02d-%04d" Id Source #

ipv4

type Ip4ip = Map (ReadP Int Id) (Resplit "\\." Id) Source #

type Ip4op = GuardsN (PrintT "octet %d out of range 0-255 found %d" Id) 4 (Between 0 255) Source #

type Ip4op' = BoolsN (PrintT "octet %d out of range 0-255 found %d" Id) 4 (Between 0 255) Source #

type Ip4fmt = PrintL 4 "%03d.%03d.%03d.%03d" Id Source #

type OctetRE = "(25[0-5]|2[0..4][0-9]|1[0-9][0-9]|[1-9][0-9]|[0-9])" Source #

type Ip4RE = "^(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" Source #

ipv6

type Ip6ip = Resplit ":" Id >> (Map (If (Id == "") "0" Id) Id >> (Map (ReadBaseInt 16 Id) Id >> PadL 8 0 Id)) Source #

type Ip6op = Msg "count is bad:" (Len == 8) && Msg "out of bounds:" (All (Between 0 65535) Id) Source #

type Ip6fmt = PrintL 8 "%04x:%04x:%04x:%04x:%04x:%04x:%04x:%04x" Id Source #