predicate-typed-0.7.4.4: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Examples.Common

Description

Common predicates for use with Refined, Refined2, and Refined3

Synopsis

datetime

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" Source #

ip type for reading in a date time

type Dtfmt = FormatTimeP "%F %T" 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)] >> 'True Source #

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

type JsonMicrosoftDateTime = Do '[Rescan "^Date\\(([-+])?(\\d*?)(\\d{0,3})([+-]\\d{4})\\)", Head, Snd, If ((Id !! 0) == "-") "-" "" <> (PadL 1 (C "0") (Id !! 1) <> ("." <> (PadL 3 (C "0") (Id !! 2) <> (Id !! 3)))), ParseTimeP ZonedTime "%s%Q%z"] Source #

convert json microsoft datetime to zonedtime

>>> pz @JsonMicrosoftDateTime "Date(1593460089052+0800)"
Val 2020-06-30 03:48:09.052 +0800
>>> pz @JsonMicrosoftDateTime "Date(0+0800)"
Val 1970-01-01 08:00:00 +0800
>>> pz @JsonMicrosoftDateTime "Date(12+0800)"
Val 1970-01-01 08:00:00.012 +0800
>>> pz @JsonMicrosoftDateTime "Date(123+0800)"
Val 1970-01-01 08:00:00.123 +0800
>>> pz @JsonMicrosoftDateTime "Date(+1234+0800)"
Val 1970-01-01 08:00:01.234 +0800
>>> pz @JsonMicrosoftDateTime "Date(-123456+0000)"
Val 1969-12-31 23:57:57.456 +0000

time

type Hmsip = Map' (ReadP Int Id) (Resplit ":") 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)] >> 'True 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 Luhnip = Map' (ReadP Int Id) (Remove "-" Id >> Ones) Source #

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

type Luhnop (n :: Nat) = GuardBool (PrintT "expected %d digits but found %d" '(n, Len)) (Len == n) && GuardBool "invalid checkdigit" IsLuhn Source #

op type for validating a credit card number by check digit

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

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

type Luhn' (n :: Nat) = Msg "Luhn'" (Do '[Guard (PrintT "incorrect length: found %d but expected %d in [%s]" '(Len, n, Id)) (Len == n), Do '[Ones, Map (ReadP Int Id), Reverse, ZipWith ((Fst * Snd) >> If (Id >= 10) (Id - 9) Id) (Cycle n [1, 2]) 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, ZipWith ((Fst * Snd) >> If (Id >= 10) (Id - 9) Id) (Cycle n [1, 2]) Id, Sum] >> 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})$" >> (OneP >> Snd)) 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 "\\.") Source #

ip type for reading in an ip4 address

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

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

type Ip4op = GuardsN 4 (PrintT "octet %d out of range 0-255 found %d" Id) (0 <..> 255) >> 'True 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 (0 <..> 255) 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 ":" >> (Map (If (Id == "") "0" Id) >> (Map (ReadBase Int 16) >> 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 (0 <..> 65535)) 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

isbn10

type Isbn10op = GuardSimple ((Fst >> All (0 <..> 9)) && Between 0 10 Snd) >> (ZipWith (Fst * Snd) ((1 ... 10) >> Reverse) (Fst +: Snd) >> (Sum >> GuardBool "mod 0 oops" ((Id `Mod` 11) == 0))) Source #

type Isbn10fmt = (ConcatMap (ShowP Id) Id *** If (Id == 10) "X" (ShowP Id)) >> (Fst <> ("-" <> Snd)) Source #

isbn13

type Isbn13op = ZipWith (Fst * Snd) (Cycle 13 [1, 3] >> Reverse) Id >> (Sum >> ('(Id, Id `Mod` 10) >> GuardBool (PrintT "sum=%d mod 10=%d" Id) (Snd == 0))) Source #