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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Condition

Contents

Description

promoted conditional functions

Synopsis

conditional expressions

data If p q r Source #

similar to an if statement: if 'p' then run 'q' else run 'r'

>>> pz @(If (Gt 4) "greater than 4" "less than or equal to 4") 10
PresentT "greater than 4"
>>> pz @(If (Gt 4) "greater than 4" "less than or equal to 4") 0
PresentT "less than or equal to 4"
>>> pz @(If (Snd Id == "a") '("xxx",Fst Id + 13) (If (Snd Id == "b") '("yyy",Fst Id + 7) (Failt _ "oops"))) (99,"b")
PresentT ("yyy",106)
>>> pl @(If (Len > 2) (Map (Succ Id) Id) (FailS "someval")) [12,15,16]
Present [13,16,17] (If (true cond))
PresentT [13,16,17]
>>> pl @(Map (If (Lt 3) 'True (Failt _ "err")) Id) [1..10]
Error err(8) (Map(i=2, a=3) excnt=8)
FailT "err(8)"
>>> pl @(Map (If (Lt 3) 'True (Failt _ "someval")) Id) [1..10]
Error someval(8) (Map(i=2, a=3) excnt=8)
FailT "someval(8)"
>>> pl @(Map (If (Lt 3) 'True 'False) Id) [1..5]
Present [True,True,False,False,False] (Map [True,True,False,False,False] | [1,2,3,4,5])
PresentT [True,True,False,False,False]
>>> pl @(If (Gt 4) (Fail (Hole _) (PrintF "failing with %d" Id)) ()) 45
Error failing with 45 (If [True])
FailT "failing with 45"
>>> pl @(If (Gt 4) (Fail (Hole _) (PrintF "failing with %d" Id)) (Id * 7)) 3
Present 21 (If (false cond) 21)
PresentT 21
>>> pl @(If (Gt 4) (Fail (Hole _) (PrintF "failing with %d" Id)) (Id * 7 >> ShowP Id >> Ones Id)) 3
Present ["2","1"] (If (false cond) ["2","1"])
PresentT ["2","1"]
>>> pl @(If (Gt 4) (Fail (Hole _) (PrintF "failing with %d" Id)) (ShowP (Id * 7) >> Ones Id)) 19
Error failing with 19 (If [True])
FailT "failing with 19"
Instances
(Show (PP r a), P p a, PP p a ~ Bool, P q a, P r a, PP q a ~ PP r a) => P (If p q r :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (If p q r) a :: Type Source #

Methods

eval :: MonadEval m => proxy (If p q r) -> POpts -> a -> m (TT (PP (If p q r) a)) Source #

type PP (If p q r :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (If p q r :: Type) a = PP q a

data Case (e :: k0) (ps :: [k]) (qs :: [k1]) (r :: k2) Source #

tries to match the value 'r' with a condition in 'ps' and if there is a match calls the associated 'qs' entry else run 'e'

>>> pl @(Case (Snd Id >> Failp "xx") '[Gt 3, Lt 2, Same 3] '["gt3","lt2","eq3"] Id) 15
Present "gt3" (Case(0 of 3) "gt3" | 15)
PresentT "gt3"
>>> pl @(Case (Snd Id >> Failp "xx") '[Gt 3, Lt 2, Same 3] '["gt3","lt2","eq3"] Id) 1
Present "lt2" (Case(0) "lt2" | 1)
PresentT "lt2"
>>> pl @(Case (Snd Id >> Failp "xx") '[Gt 3, Lt 2, Same 3] '["gt3","lt2","eq3"] Id) 3
Present "eq3" (Case(0) "eq3" | 3)
PresentT "eq3"
>>> pl @(Case (Snd Id >> Failp "no match") '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Error no match (Case(0) failed rhs)
FailT "no match"
>>> pl @(Case (Fail (Snd Id >> Unproxy) (PrintF "no match for %03d" (Fst Id))) '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Error no match for 015 (Case(0) failed rhs)
FailT "no match for 015"
>>> pl @(Case "other" '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Present "other" (Case(0) "other" | 15)
PresentT "other"
>>> pl @(Case (ShowP (Fst Id) >> Id <> Id <> Id) '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Present "151515" (Case(0) "151515" | 15)
PresentT "151515"
Instances
(FailUnlessT (LenT ps == LenT qs) (((Text "lengths are not the same " :<>: ShowType (LenT ps)) :<>: Text " vs ") :<>: ShowType (LenT qs)), P (CaseImplT e ps qs r) x) => P (Case e ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Case e ps qs r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Case e ps qs r) -> POpts -> x -> m (TT (PP (Case e ps qs r) x)) Source #

type PP (Case e ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Case e ps qs r :: Type) x

data Case' (ps :: [k]) (qs :: [k1]) (r :: k2) Source #

like Case but uses a generic error message (skips the 'e' parameter)

>>> pl @(Case' '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Error Case:no match (Case(0) failed rhs)
FailT "Case:no match"
Instances
P (CaseT' ps qs r) x => P (Case' ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Case' ps qs r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Case' ps qs r) -> POpts -> x -> m (TT (PP (Case' ps qs r) x)) Source #

type PP (Case' ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Case' ps qs r :: Type) x

data Case'' s (ps :: [k]) (qs :: [k1]) (r :: k2) Source #

like Case but allows you to use the value in the error message

>>> pl @(Case'' (PrintF "no match for %03d" Id) '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Error no match for 015 (Case(0) failed rhs)
FailT "no match for 015"
>>> pl @(Case'' (PrintF "no match for %03d" Id) '[Same 1, Same 2, Same 3] '["eq1","eq2","eq3"] Id) 15
Error no match for 015 (Case(0) failed rhs)
FailT "no match for 015"
>>> pl @(Case'' (PrintF "no match for %04d" Id) '[Between 0 5 Id, Same 6, Between 7 10 Id] '[ 'LT, 'EQ, 'GT] Id) (-12)
Error no match for -012 (Case(0) failed rhs)
FailT "no match for -012"
Instances
P (CaseT'' s ps qs r) x => P (Case'' s ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Case'' s ps qs r) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Case'' s ps qs r) -> POpts -> x -> m (TT (PP (Case'' s ps qs r) x)) Source #

type PP (Case'' s ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Case'' s ps qs r :: Type) x

data Guards (ps :: [(k, k1)]) Source #

Guards contain a type level list of tuples the action to run on failure of the predicate and the predicate itself Each tuple validating against the corresponding value in a value list

'prt' receives (Int,a) as input which is the position and value if there is a failure

>>> pz @(Guards '[ '("arg1 failed",Gt 4), '("arg2 failed", Same 4)]) [17,4]
PresentT [17,4]
>>> pz @(Guards '[ '("arg1 failed",Gt 4), '("arg2 failed", Same 5)]) [17,4]
FailT "arg2 failed"
>>> pz @(Guards '[ '("arg1 failed",Gt 99), '("arg2 failed", Same 4)]) [17,4]
FailT "arg1 failed"
>>> pz @(Guards '[ '(PrintT "arg %d failed with value %d" Id,Gt 4), '(PrintT "%d %d" Id, Same 4)]) [17,3]
FailT "1 3"
>>> pz @(Msg "isbn10" (Resplit "-" Id) >> Concat Id >> 'Just Unsnoc >> Map (ReadP Int (Singleton Id)) Id *** If (Singleton Id ==~ "X") 10 (ReadP Int (Singleton Id)) >> Zip (1...10 >> Reverse) (Fst Id +: Snd Id) >> Map (Fst Id * Snd Id) Id >> Sum >> Guard ("mod 0 oops") (Id `Mod` 11 == 0)) "0-306-40614-X"
FailT "mod 0 oops"
>>> pz @(Resplit "-" Id >> Concat Id >> 'Just Unsnoc >> Map (ReadP Int (Singleton Id)) Id *** If (Singleton Id ==~ "X") 10 (ReadP Int (Singleton Id)) >> Zip (1...10 >> Reverse) (Fst Id +: Snd Id) >> Map (Fst Id * Snd Id) Id >> Sum >> Guard ("mod 0 oops") (Id `Mod` 11 == 0)) "0-306-40611-X"
PresentT 132
>>> pz @(Msg "isbn13" (Resplit "-" Id) >> Concat Id >> Map (ReadP Int (Singleton Id)) Id >> Zip (Cycle 13 [1,3] >> Reverse) Id >> Map (Fst Id * Snd Id) Id >> Sum >> '(Id,Id `Mod` 10) >> Guard (PrintT "sum=%d mod 10=%d" Id) (Snd Id == 0)) "978-0-306-40615-7"
PresentT (100,0)
>>> pz @(Resplit "-" Id >> Concat Id >> Map (ReadP Int (Singleton Id)) Id >> Zip (Cycle 13 [1,3] >> Reverse) Id >> Map (Fst Id * Snd Id) Id >> Sum >> '(Id,Id `Mod` 10) >> Guard (PrintT "sum=%d mod 10=%d" Id) (Snd Id == 0)) "978-0-306-40615-8"
FailT "sum=101 mod 10=1"
>>> pz @(Do '[Resplit "-" Id, Concat Id, Zip (Cycle 13 [1,3]) (Map (ReadP Int (Singleton Id)) Id), Map (Fst Id * Snd Id) Id, Sum, Guard (PrintF "%d is not evenly divisible by 10" Id) (Id `Mod` 10 == 0)]) "978-0-7167-0344-9"
FailT "109 is not evenly divisible by 10"
>>> pz @(Do '[Resplit "-" Id, Concat Id, Zip (Cycle 13 [1,3]) (Map (ReadP Int (Singleton Id)) Id), Map (Fst Id * Snd Id) Id, Sum, Guard (PrintF "%d is not evenly divisible by 10" Id) (Id `Mod` 10 == 0)]) "978-0-7167-0344-0"
PresentT 100
Instances
([a] ~ x, GetLen ps, P (GuardsImpl (LenT ps) ps) x) => P (Guards ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Guards ps) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Guards ps) -> POpts -> x -> m (TT (PP (Guards ps) x)) Source #

type PP (Guards ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Guards ps :: Type) x

data GuardsQuick (prt :: k) (ps :: [k1]) Source #

GuardsQuick contain a type level list of conditions and one of matching values: on no match will fail using the first parameter

>>> pz @(GuardsQuick (PrintT "arg %d failed with value %d" Id) '[Gt 4, Ge 3, Same 4]) [17,3,5]
FailT "arg 2 failed with value 5"
>>> pz @(GuardsQuick (PrintT "arg %d failed with value %d" Id) '[Gt 4, Ge 3, Same 4]) [17,3,5,99]
FailT "Guards:invalid length(4) expected 3"
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 0 11 Id, Between 1 4 Id,Between 3 5 Id]) [10::Int,2,5]
Present [10,2,5] (Guards)
PresentT [10,2,5]
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31 Id, Between 1 12 Id, Between 1990 2050 Id]) [31,11,1999::Int]
Present [31,11,1999] (Guards)
PresentT [31,11,1999]
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31 Id, Between 1 12 Id, Between 1990 2050 Id]) [31,11::Int]
Error Guards:invalid length(2) expected 3
FailT "Guards:invalid length(2) expected 3"
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31 Id, Between 1 12 Id, Between 1990 2050 Id]) [31,13,1999::Int]
Error guard(1) 13 is out of range (Guard(0) ok | rhs failed)
FailT "guard(1) 13 is out of range"
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31 Id, Between 1 12 Id, Between 1990 2050 Id]) [0,44,1999::Int]
Error guard(0) 0 is out of range (Guard(0) failed [guard(0) 0 is out of range] 0)
FailT "guard(0) 0 is out of range"
>>> pl @(GuardsQuick (PrintT "guard(%d) %d is out of range" Id) '[Between 1 31 Id, Between 1 12 Id, Between 1990 2050 Id]) [31,11,2000,1,2::Int]
Error Guards:invalid length(5) expected 3
FailT "Guards:invalid length(5) expected 3"
>>> pl @(GuardsQuick (PrintT "guard(%d) err %03d" Id) '[W 'True, Ge 12, W 'False, Lt 2]) [1,2,-99,-999]
Error guard(1) err 002 (Guard(0) ok | rhs failed)
FailT "guard(1) err 002"
>>> pl @(GuardsQuick (PrintT "guard(%d) err %03d" Id) '[W 'True, Ge 12, W 'False, Lt 2]) [1,2,-99]
Error Guards:invalid length(3) expected 4
FailT "Guards:invalid length(3) expected 4"
>>> pl @(GuardsQuick (PrintT "guard(%d) err %03d" Id) '[W 'True, Ge 12, W 'True, Lt 2]) [1,22,-99,-999,1,1,2]
Error Guards:invalid length(7) expected 4
FailT "Guards:invalid length(7) expected 4"
Instances
P (GuardsQuickT prt ps) x => P (GuardsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardsQuick prt ps) x :: Type Source #

Methods

eval :: MonadEval m => proxy (GuardsQuick prt ps) -> POpts -> x -> m (TT (PP (GuardsQuick prt ps) x)) Source #

type PP (GuardsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (GuardsQuick prt ps :: Type) x

data Guard prt p Source #

'p' is the predicate and on failure of the predicate runs 'prt'

>>> pz @(Guard "expected > 3" (Gt 3)) 17
PresentT 17
>>> pz @(Guard "expected > 3" (Gt 3)) 1
FailT "expected > 3"
>>> pz @(Guard (PrintF "%d not > 3" Id) (Gt 3)) (-99)
FailT "-99 not > 3"
>>> pl @(Map (Guard "someval" (Lt 3) >> 'True) Id) [1::Int ..10]
Error someval(8) (Map(i=2, a=3) excnt=8)
FailT "someval(8)"
>>> pl @(Guard "someval" (Len == 2) >> (ShowP Id &&& Id)) ([] :: [Int])
Error someval ((>>) lhs failed)
FailT "someval"
>>> pl @(Guard "someval" (Len == 2) >> (Id &&& ShowP Id)) [2,3]
Present ([2,3],"[2,3]") ((>>) ([2,3],"[2,3]") | {W '([2,3],"[2,3]")})
PresentT ([2,3],"[2,3]")
>>> pl @(Guard "someval" (Len == 2) >> (ShowP Id &&& Id)) [2,3,4]
Error someval ((>>) lhs failed)
FailT "someval"
>>> pl @(Map (Guard "someval" (Lt 3) >> 'True) Id) [1::Int ..10]
Error someval(8) (Map(i=2, a=3) excnt=8)
FailT "someval(8)"
>>> pl @(Guard "oops" (Len > 2) >> Map (Succ Id) Id) [12,15,16]
Present [13,16,17] ((>>) [13,16,17] | {Map [13,16,17] | [12,15,16]})
PresentT [13,16,17]
>>> pl @(Guard "err" (Len > 2) >> Map (Succ Id) Id) [12]
Error err ((>>) lhs failed)
FailT "err"
>>> pl @(Guard (PrintF "err found len=%d" Len) (Len > 5) >> Map (Succ Id) Id) [12,15,16]
Error err found len=3 ((>>) lhs failed)
FailT "err found len=3"
Instances
(Show a, P prt a, PP prt a ~ String, P p a, PP p a ~ Bool) => P (Guard prt p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Guard prt p) a :: Type Source #

Methods

eval :: MonadEval m => proxy (Guard prt p) -> POpts -> a -> m (TT (PP (Guard prt p) a)) Source #

type PP (Guard prt p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Guard prt p :: Type) a = a

data ExitWhen prt p Source #

uses Guard but negates 'p'

>>> pl @(HeadFail "failedn" Id &&& (Len == 1 >> ExitWhen "ExitWhen" Id) >> Fst Id) [3]
Error ExitWhen ((>>) lhs failed)
FailT "ExitWhen"
>>> pl @(Head Id &&& (Len == 1 >> Not Id >> ExitWhen "ExitWhen" Id) >> Fst Id) [3]
Present 3 ((>>) 3 | {Fst 3 | (3,False)})
PresentT 3
>>> pl @(Head Id &&& (Len == 1 >> ExitWhen "ExitWhen" (Not Id)) >> Fst Id) [3]
Present 3 ((>>) 3 | {Fst 3 | (3,True)})
PresentT 3
>>> pl @(ExitWhen "ExitWhen" (Len /= 1) >> Head Id) [3,1]
Error ExitWhen ((>>) lhs failed)
FailT "ExitWhen"
>>> pl @(ExitWhen "ExitWhen" (Len /= 1) >> Head Id) [3]
Present 3 ((>>) 3 | {Head 3 | [3]})
PresentT 3
>>> pl @(ExitWhen "ExitWhen" (Len /= 1) >> Head Id >> Gt (20 -% 1)) [3]
True ((>>) True | {3 % 1 > (-20) % 1})
TrueT
>>> pl @(ExitWhen "ExitWhen" (Len /= 1) >> Head Id >> Gt (20 -% 1)) [-23]
False ((>>) False | {(-23) % 1 > (-20) % 1})
FalseT
>>> pl @(Map (ExitWhen "ExitWhen" (Gt 10) >> Gt 2) Id) [1..5]
Present [False,False,True,True,True] (Map [False,False,True,True,True] | [1,2,3,4,5])
PresentT [False,False,True,True,True]
>>> pl @(ExitWhen "err" (Len > 2) >> Map (Succ Id) Id) [12,15,16]
Error err ((>>) lhs failed)
FailT "err"
>>> pl @(ExitWhen "err" (Len > 2) >> Map (Succ Id) Id) [12]
Present [13] ((>>) [13] | {Map [13] | [12]})
PresentT [13]
Instances
P (ExitWhenT prt p) x => P (ExitWhen prt p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (ExitWhen prt p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ExitWhen prt p) -> POpts -> x -> m (TT (PP (ExitWhen prt p) x)) Source #

type PP (ExitWhen prt p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (ExitWhen prt p :: Type) x

data GuardSimple p Source #

similar to Guard but uses the root message of the False predicate case as the failure message

most uses of GuardSimple can be replaced by a boolean predicate unless you require a failure message instead of true/false

>>> pz @(GuardSimple (Luhn Id)) [1..4]
FailT "(Luhn map=[4,6,2,2] sum=14 ret=4 | [1,2,3,4])"
>>> pl @(Luhn Id) [1..4]
False (Luhn map=[4,6,2,2] sum=14 ret=4 | [1,2,3,4])
FalseT
>>> pz @(GuardSimple (Luhn Id)) [1,2,3,0]
PresentT [1,2,3,0]
>>> pz @(GuardSimple (Len > 30)) [1,2,3,0]
FailT "(4 > 30)"
>>> pl @(Map (GuardSimple (Lt 3) >> 'True) Id) [1::Int .. 10]
Error (3 < 3) | (4 < 3) | (5 < 3) | (6 < 3) | (7 < 3) | (8 < 3) | (9 < 3) | (10 < 3) (Map(i=2, a=3) excnt=8)
FailT "(3 < 3) | (4 < 3) | (5 < 3) | (6 < 3) | (7 < 3) | (8 < 3) | (9 < 3) | (10 < 3)"
>>> pl @(Map (GuardSimple (Ge 1) >> 'True) Id) [1::Int .. 10]
Present [True,True,True,True,True,True,True,True,True,True] (Map [True,True,True,True,True,True,True,True,True,True] | [1,2,3,4,5,6,7,8,9,10])
PresentT [True,True,True,True,True,True,True,True,True,True]
>>> pl @(Map (GuardSimple (Lt 3) >> 'True) Id) [1::Int .. 10]
Error (3 < 3) | (4 < 3) | (5 < 3) | (6 < 3) | (7 < 3) | (8 < 3) | (9 < 3) | (10 < 3) (Map(i=2, a=3) excnt=8)
FailT "(3 < 3) | (4 < 3) | (5 < 3) | (6 < 3) | (7 < 3) | (8 < 3) | (9 < 3) | (10 < 3)"
>>> pl @(Map (GuardSimple (Ge 1) >> 'True) Id) [1::Int .. 10]
Present [True,True,True,True,True,True,True,True,True,True] (Map [True,True,True,True,True,True,True,True,True,True] | [1,2,3,4,5,6,7,8,9,10])
PresentT [True,True,True,True,True,True,True,True,True,True]
Instances
(Show a, P p a, PP p a ~ Bool) => P (GuardSimple p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardSimple p) a :: Type Source #

Methods

eval :: MonadEval m => proxy (GuardSimple p) -> POpts -> a -> m (TT (PP (GuardSimple p) a)) Source #

type PP (GuardSimple p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (GuardSimple p :: Type) a = a

data GuardsN prt (n :: Nat) p Source #

leverages RepeatT for repeating predicates (passthrough method)

>>> pz @(GuardsN (PrintT "id=%d must be between 0 and 255, found %d" Id) 4 (Between 0 255 Id)) [121,33,7,256]
FailT "id=3 must be between 0 and 255, found 256"
>>> pz @(GuardsN (PrintT "id=%d must be between 0 and 255, found %d" Id) 4 (Between 0 255 Id)) [121,33,7,44]
PresentT [121,33,7,44]
>>> pl @(GuardsN (PrintT "guard(%d) %d is out of range" Id) 4 (Between 0 255 Id)) [1,2,3,4::Int]
Present [1,2,3,4] (Guards)
PresentT [1,2,3,4]
>>> pl @(GuardsN (PrintT "guard(%d) %d is out of range" Id) 4 (Between 0 255 Id)) [1,2,3,4,5::Int]
Error Guards:invalid length(5) expected 4
FailT "Guards:invalid length(5) expected 4"
>>> pl @(GuardsN (PrintT "guard(%d) %d is out of range" Id) 4 (Between 0 255 Id)) [1,2,3::Int]
Error Guards:invalid length(3) expected 4
FailT "Guards:invalid length(3) expected 4"
Instances
(x ~ [a], P (GuardsNT prt n p) x) => P (GuardsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardsN prt n p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (GuardsN prt n p) -> POpts -> x -> m (TT (PP (GuardsN prt n p) x)) Source #

type PP (GuardsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (GuardsN prt n p :: Type) x

data GuardsDetail prt (ps :: [(k0, k1)]) Source #

Instances
P (GuardsDetailT prt ps) x => P (GuardsDetail prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardsDetail prt ps) x :: Type Source #

Methods

eval :: MonadEval m => proxy (GuardsDetail prt ps) -> POpts -> x -> m (TT (PP (GuardsDetail prt ps) x)) Source #

type PP (GuardsDetail prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (GuardsDetail prt ps :: Type) x

data Bools (ps :: [(k, k1)]) Source #

boolean guard which checks a given a list of predicates against the list of values

>>> pl @(Bools '[ '(W "hh",Between 0 23 Id), '(W "mm",Between 0 59 Id), '(PrintT "<<<%d %d>>>" Id,Between 0 59 Id) ]) [12,93,14]
False (Bool(1) [mm] (93 <= 59))
FalseT
>>> pl @(Bools '[ '(W "hh",Between 0 23 Id), '(W "mm",Between 0 59 Id), '(PrintT "<<<%d %d>>>" Id,Between 0 59 Id) ]) [12,13,94]
False (Bool(2) [<<<2 94>>>] (94 <= 59))
FalseT
>>> pl @(Bools '[ '(W "hh",Between 0 23 Id), '(W "mm",Between 0 59 Id), '(PrintT "<<<%d %d>>>" Id,Between 0 59 Id) ]) [12,13,14]
True (Bools)
TrueT
>>> pl @(BoolsQuick "abc" '[Between 0 23 Id, Between 0 59 Id, Between 0 59 Id]) [12,13,14]
True (Bools)
TrueT
>>> pl @(BoolsQuick (PrintT "id=%d val=%d" Id) '[Between 0 23 Id, Between 0 59 Id, Between 0 59 Id]) [12,13,14]
True (Bools)
TrueT
>>> pl @(BoolsQuick (PrintT "id=%d val=%d" Id) '[Between 0 23 Id, Between 0 59 Id, Between 0 59 Id]) [12,13,99]
False (Bool(2) [id=2 val=99] (99 <= 59))
FalseT
>>> pl @(Bools '[ '("hours",Between 0 23 Id), '("minutes",Between 0 59 Id), '("seconds",Between 0 59 Id)]) [12,13,14]
True (Bools)
TrueT
>>> pl @(Bools '[ '("hours",Between 0 23 Id), '("minutes",Between 0 59 Id), '("seconds",Between 0 59 Id)]) [12,60,14]
False (Bool(1) [minutes] (60 <= 59))
FalseT
>>> pl @(Bools '[ '("hours",Between 0 23 Id), '("minutes",Between 0 59 Id), '("seconds",Between 0 59 Id)]) [12,60,14,20]
False (Bools:invalid length(4) expected 3)
FalseT
Instances
([a] ~ x, GetLen ps, P (BoolsImpl (LenT ps) ps) x, PP (BoolsImpl (LenT ps) ps) x ~ Bool) => P (Bools ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (Bools ps) x :: Type Source #

Methods

eval :: MonadEval m => proxy (Bools ps) -> POpts -> x -> m (TT (PP (Bools ps) x)) Source #

type PP (Bools ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (Bools ps :: Type) x = Bool

data BoolsQuick (prt :: k) (ps :: [k1]) Source #

Instances
(PP (Bools (ToGuardsT prt ps)) x ~ Bool, P (BoolsQuickT prt ps) x) => P (BoolsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (BoolsQuick prt ps) x :: Type Source #

Methods

eval :: MonadEval m => proxy (BoolsQuick prt ps) -> POpts -> x -> m (TT (PP (BoolsQuick prt ps) x)) Source #

type PP (BoolsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (BoolsQuick prt ps :: Type) x

data BoolsN prt (n :: Nat) (p :: k1) Source #

leverages RepeatT for repeating predicates (passthrough method)

>>> pl @(BoolsN (PrintT "id=%d must be between 0 and 255, found %d" Id) 4 (Between 0 255 Id)) [121,33,7,256]
False (Bool(3) [id=3 must be between 0 and 255, found 256] (256 <= 255))
FalseT
>>> pl @(BoolsN (PrintT "id=%d must be between 0 and 255, found %d" Id) 4 (Between 0 255 Id)) [121,33,7,44]
True (Bools)
TrueT
Instances
(x ~ [a], P (BoolsNT prt n p) x) => P (BoolsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (BoolsN prt n p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (BoolsN prt n p) -> POpts -> x -> m (TT (PP (BoolsN prt n p) x)) Source #

type PP (BoolsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

type PP (BoolsN prt n p :: Type) x