predicate-typed-0.6.2.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 DateNip = ParseTimes Day DateFmts Id Source #

'ip' type for reading one of many date formats from DateFmts

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 DateTimeNip = ParseTimes UTCTime DateTimeFmts Id Source #

'ip' type for reading one of many date time formats from DateTimeFmts

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

'ip' type for reading in a date time

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

'fmt' type for formatting the date time compatible ith Dtip

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

type Ddmmyyyyop = GuardsDetail "%s %d is out of range" '['("day", Between 1 31 Id), '("month", Between 1 12 Id), '("year", Between 1990 2050 Id)] Source #

type Ddmmyyyyop' = Bools '['("day", Between 1 31 Id), '("month", Between 1 12 Id), '("year", Between 1990 2050 Id)] Source #

time checkers

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

'ip' type for reading in time

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

'op' type for validating the time using a guard

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

'op' type for validating the time using predicate

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

'fmt' type for formatting the time

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

regular expression for a time component

credit cards

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

'ip' type for converting a credit card number to a list of singleton digits

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

'op' type for validating a credit card number by check digit

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

'fmt' type for formatting a credit card using 'ns' as the format

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, Sum], Guard (PrintT "expected %d mod 10 = 0 but found %d" '(Id, Id `Mod` 10)) (Mod Id 10 == 0)]) Source #

type Luhnop' (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, Sum] >> Guard (PrintT "expected %d mod 10 = 0 but found %d" '(Id, Id `Mod` 10)) (Mod Id 10 == 0)) Source #

type Luhn'' (n :: Nat) = Luhnip >> Luhnop' n Source #

ssn

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

'ip' type for reading in a ssn

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

'op' type for validating a ssn

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

'fmt' type for formatting the ssn compatible with Ssnip

ipv4

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

'ip' type for reading in an ip4 address

type Ip4ip' = Map (ReadP Int Id) (Rescan Ip4RE Id >> Snd (OneP Id)) Source #

'ip' type for reading in an ip4 address using a regular expression

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

'op' type for validating an ip4 address using a guard

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

'op' type for validating an ip4 address using a predicate

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

'fmt' type for formatting an ip4 address

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

regular expression for an octet

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

regular expression for an ip4 address

type Ip4StrictRE = "^" <%> (IntersperseT "\\." (RepeatT 4 OctetRE) <%> "$") Source #

regular expression for an ip4 address

ipv6

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

'ip' type for reading in an ip6 address

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

'op' type for validating an ip6 address using predicates

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

'fmt' type for formatting an ip6 address