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

Safe HaskellNone
LanguageHaskell2010

Predicate.Prelude

Contents

Description

Dsl for evaluating and displaying type level expressions

Contains instances of the class P for evaluating expressions at the type level.

Synopsis

boolean expressions

data p && q infixr 3 Source #

similar to &&

>>> pz @(Fst Id && Snd Id) (True, True)
True
TrueT
>>> pz @(Id > 15 && Id < 17) 16
True
TrueT
>>> pz @(Id > 15 && Id < 17) 30
False
FalseT
>>> pz @(Fst Id && (Length (Snd Id) >= 4)) (True,[11,12,13,14])
True
TrueT
>>> pz @(Fst Id && (Length (Snd Id) == 4)) (True,[12,11,12,13,14])
False
FalseT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p && q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p && q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p && q) -> POpts -> a -> m (TT (PP (p && q) a)) Source #

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

Defined in Predicate.Prelude

type PP (p && q :: Type) a = Bool

data p || q infixr 2 Source #

similar to ||

>>> pz @(Fst Id || (Length (Snd Id) >= 4)) (False,[11,12,13,14])
True
TrueT
>>> pz @(Not (Fst Id) || (Length (Snd Id) == 4)) (True,[12,11,12,13,14])
False
FalseT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p || q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p || q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p || q) -> POpts -> a -> m (TT (PP (p || q) a)) Source #

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

Defined in Predicate.Prelude

type PP (p || q :: Type) a = Bool

data p ~> q infixr 1 Source #

implication

>>> pz @(Fst Id ~> (Length (Snd Id) >= 4)) (True,[11,12,13,14])
True
TrueT
>>> pz @(Fst Id ~> (Length (Snd Id) == 4)) (True,[12,11,12,13,14])
False
FalseT
>>> pz @(Fst Id ~> (Length (Snd Id) == 4)) (False,[12,11,12,13,14])
True
TrueT
>>> pz @(Fst Id ~> (Length (Snd Id) >= 4)) (False,[11,12,13,14])
True
TrueT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p ~> q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p ~> q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ~> q) -> POpts -> a -> m (TT (PP (p ~> q) a)) Source #

type PP (p ~> q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (p ~> q :: Type) a = Bool

data Not p Source #

not function

>>> pz @(Not Id) False
True
TrueT
>>> pz @(Not Id) True
False
FalseT
>>> pz @(Not (Fst Id)) (True,22)
False
FalseT
>>> pl @(Not (Lt 3)) 13
True (Not (13 < 3))
TrueT
Instances
(PP p x ~ Bool, P p x) => P (Not p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Not p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Not p) -> POpts -> x -> m (TT (PP (Not p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Not p :: Type) x = Bool

data Ands p Source #

ands

>>> pz @(Ands Id) [True,True,True]
True
TrueT
>>> pl @(Ands Id) [True,True,True,False]
False (Ands(4) i=3 | [True,True,True,False])
FalseT
>>> pz @(Ands Id) []
True
TrueT
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ands p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ands p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ands p) -> POpts -> x -> m (TT (PP (Ands p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Ands p :: Type) x = Bool

data Ors p Source #

ors

>>> pz @(Ors Id) [False,False,False]
False
FalseT
>>> pl @(Ors Id) [True,True,True,False]
True (Ors(4) i=0 | [True,True,True,False])
TrueT
>>> pl @(Ors Id) []
False (Ors(0) | [])
FalseT
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ors p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ors p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ors p) -> POpts -> x -> m (TT (PP (Ors p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Ors p :: Type) x = Bool

type Asc = All (Fst Id <= Snd Id) Pairs Source #

a type level predicate for a monotonic increasing list

>>> pl @Asc "aaacdef"
True (All(6))
TrueT
>>> pz @Asc [1,2,3,4,5,5,7]
True
TrueT
>>> pz @Asc' [1,2,3,4,5,5,7]
False
FalseT
>>> pz @Asc "axacdef"
False
FalseT

a type level predicate for a monotonic increasing list

type Asc' = All (Fst Id < Snd Id) Pairs Source #

a type level predicate for a strictly increasing list

type Desc = All (Fst Id >= Snd Id) Pairs Source #

a type level predicate for a monotonic decreasing list

type Desc' = All (Fst Id > Snd Id) Pairs Source #

a type level predicate for a strictly decreasing list

type Between p q = Between' p q Id Source #

type (<..>) p q = Between p q infix 4 Source #

data Between' p q r Source #

A predicate that determines if the value is between 'p' and 'q'

>>> pz @(Between' 5 8 Len) [1,2,3,4,5,5,7]
True
TrueT
>>> pz @(Between 5 8) 6
True
TrueT
>>> pz @(Between 5 8) 9
False
FalseT
>>> pz @(10 % 4 <..> 40 % 5) 4
True
TrueT
>>> pz @(10 % 4 <..> 40 % 5) 33
False
FalseT
Instances
(Ord (PP p x), Show (PP p x), PP r x ~ PP p x, PP r x ~ PP q x, P p x, P q x, P r x) => P (Between' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Between' p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Between' p q r) -> POpts -> x -> m (TT (PP (Between' p q r) x)) Source #

type PP (Between' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Between' p q r :: Type) x = Bool

data All p q Source #

similar to all

>>> pl @(All Even Id) [1,5,11,5,3]
False (All i=0 (1 == 0) 5 false)
FalseT
>>> pz @(All Odd Id) [1,5,11,5,3]
True
TrueT
>>> pz @(All Odd Id) []
True
TrueT
>>> pe @(All Even Id) [1,5,11,5,3]
False All i=0 (1 == 0) 5 false
|
+- P Id [1,5,11,5,3]
|
+- False i=0:1 == 0
|  |
|  +- P 1 `mod` 2 = 1
|  |  |
|  |  +- P I
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=1:1 == 0
|  |
|  +- P 5 `mod` 2 = 1
|  |  |
|  |  +- P I
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=2:1 == 0
|  |
|  +- P 11 `mod` 2 = 1
|  |  |
|  |  +- P I
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=3:1 == 0
|  |
|  +- P 5 `mod` 2 = 1
|  |  |
|  |  +- P I
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
`- False i=4:1 == 0
   |
   +- P 3 `mod` 2 = 1
   |  |
   |  +- P I
   |  |
   |  `- P '2
   |
   `- P '0
FalseT
Instances
(P p a, PP p a ~ Bool, PP q x ~ f a, P q x, Show a, Foldable f) => P (All p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (All p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (All p q) -> POpts -> x -> m (TT (PP (All p q) x)) Source #

type PP (All p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (All p q :: Type) x = Bool

data Any p q Source #

similar to any

>>> pz @(Any Even Id) [1,5,11,5,3]
False
FalseT
>>> pz @(Any Even Id) [1,5,112,5,3]
True
TrueT
>>> pz @(Any Even Id) []
False
FalseT
Instances
(P p a, PP p a ~ Bool, PP q x ~ f a, P q x, Show a, Foldable f) => P (Any p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Any p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Any p q) -> POpts -> x -> m (TT (PP (Any p q) x)) Source #

type PP (Any p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Any p q :: Type) x = Bool

type AllPositive = All Positive Id Source #

a type level predicate for all positive elements in a list

>>> pz @AllPositive [1,5,10,2,3]
True
TrueT
>>> pz @AllPositive [0,1,5,10,2,3]
False
FalseT
>>> pz @AllPositive [3,1,-5,10,2,3]
False
FalseT
>>> pz @AllNegative [-1,-5,-10,-2,-3]
True
TrueT

type Positive = Gt 0 Source #

type AllNegative = All Negative Id Source #

a type level predicate for all negative elements in a list

type Negative = Lt 0 Source #

regex expressions

type Re p q = Re' '[] p q Source #

data Re' (rs :: [ROpt]) p q Source #

represents a predicate using a Symbol as a regular expression evaluates Re and returns True if there is a match

>>> pz @(Re "^\\d{2}:\\d{2}:\\d{2}$" Id) "13:05:25"
True
TrueT
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Re' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Re' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Re' rs p q) -> POpts -> x -> m (TT (PP (Re' rs p q) x)) Source #

type PP (Re' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Re' rs p q :: Type) x = Bool

type Rescan p q = Rescan' '[] p q Source #

data Rescan' (rs :: [ROpt]) p q Source #

runs a regex matcher returning the original values and optionally any groups

>>> pz @(Rescan "^(\\d{2}):(\\d{2}):(\\d{2})$" Id) "13:05:25"
Present [("13:05:25",["13","05","25"])]
PresentT [("13:05:25",["13","05","25"])]
>>> pz @(Rescan (Snd Id) "13:05:25") ('a',"^(\\d{2}):(\\d{2}):(\\d{2})$")
Present [("13:05:25",["13","05","25"])]
PresentT [("13:05:25",["13","05","25"])]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Rescan' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Rescan' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Rescan' rs p q) -> POpts -> x -> m (TT (PP (Rescan' rs p q) x)) Source #

type PP (Rescan' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Rescan' rs p q :: Type) x = [(String, [String])]

type RescanRanges p q = RescanRanges' '[] p q Source #

data RescanRanges' (rs :: [ROpt]) p q Source #

similar to Rescan but gives the column start and ending positions instead of values

>>> pz @(RescanRanges "^(\\d{2}):(\\d{2}):(\\d{2})$" Id) "13:05:25"
Present [((0,8),[(0,2),(3,5),(6,8)])]
PresentT [((0,8),[(0,2),(3,5),(6,8)])]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (RescanRanges' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (RescanRanges' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (RescanRanges' rs p q) -> POpts -> x -> m (TT (PP (RescanRanges' rs p q) x)) Source #

type PP (RescanRanges' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (RescanRanges' rs p q :: Type) x = [((Int, Int), [(Int, Int)])]

type Resplit p q = Resplit' '[] p q Source #

data Resplit' (rs :: [ROpt]) p q Source #

splits a string on a regex delimiter

>>> pz @(Resplit "\\." Id) "141.201.1.22"
Present ["141","201","1","22"]
PresentT ["141","201","1","22"]
>>> pz @(Resplit (Singleton (Fst Id)) (Snd Id)) (':', "12:13:1")
Present ["12","13","1"]
PresentT ["12","13","1"]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Resplit' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Resplit' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Resplit' rs p q) -> POpts -> x -> m (TT (PP (Resplit' rs p q) x)) Source #

type PP (Resplit' rs p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Resplit' rs p q :: Type) x = [String]

type ReplaceAll p q r = ReplaceAll' '[] p q r Source #

type ReplaceAll' (rs :: [ROpt]) p q r = ReplaceImpl True rs p q r Source #

type ReplaceOne p q r = ReplaceOne' '[] p q r Source #

type ReplaceOne' (rs :: [ROpt]) p q r = ReplaceImpl False rs p q r Source #

type ReplaceAllString' (rs :: [ROpt]) p q r = ReplaceAll' rs p (MakeRR q) r Source #

type ReplaceOneString' (rs :: [ROpt]) p q r = ReplaceOne' rs p (MakeRR q) r Source #

data MakeRR p Source #

Simple replacement string: see ReplaceAllString and ReplaceOneString

Instances
(PP p x ~ String, P p x) => P (MakeRR p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MakeRR p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR p) -> POpts -> x -> m (TT (PP (MakeRR p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MakeRR p :: Type) x = RR

data MakeRR1 p Source #

A replacement function (String -> [String] -> String) which returns the whole match and the groups Used by sub and gsub

Requires Text.Show.Functions

Instances
(PP p x ~ (String -> [String] -> String), P p x) => P (MakeRR1 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MakeRR1 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR1 p) -> POpts -> x -> m (TT (PP (MakeRR1 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MakeRR1 p :: Type) x = RR

data MakeRR2 p Source #

A replacement function (String -> String) that yields the whole match Used by sub and gsub

Requires Text.Show.Functions

>>> :m + Text.Show.Functions
>>> pz @(ReplaceAll "\\." (MakeRR2 (Fst Id)) (Snd Id)) (\x -> x <> ":" <> x, "141.201.1.22")
Present "141.:.201.:.1.:.22"
PresentT "141.:.201.:.1.:.22"
Instances
(PP p x ~ (String -> String), P p x) => P (MakeRR2 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MakeRR2 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR2 p) -> POpts -> x -> m (TT (PP (MakeRR2 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MakeRR2 p :: Type) x = RR

data MakeRR3 p Source #

A replacement function ([String] -> String) which yields the groups Used by sub and gsub

Requires Text.Show.Functions

>>> :m + Text.Show.Functions
>>> pz @(ReplaceAll "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" (MakeRR3 (Fst Id)) (Snd Id)) (\ys -> intercalate  " | " $ map (show . succ . read @Int) ys, "141.201.1.22")
Present "142 | 202 | 2 | 23"
PresentT "142 | 202 | 2 | 23"
Instances
(PP p x ~ ([String] -> String), P p x) => P (MakeRR3 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MakeRR3 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR3 p) -> POpts -> x -> m (TT (PP (MakeRR3 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MakeRR3 p :: Type) x = RR

tuple expressions

data Fst p Source #

similar to fst

>>> pz @(Fst Id) (10,"Abc")
Present 10
PresentT 10
>>> pz @(Fst Id) (10,"Abc",'x')
Present 10
PresentT 10
>>> pz @(Fst Id) (10,"Abc",'x',False)
Present 10
PresentT 10
Instances
(Show (ExtractL1T (PP p x)), ExtractL1C (PP p x), P p x, Show (PP p x)) => P (Fst p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Fst p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Fst p) -> POpts -> x -> m (TT (PP (Fst p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Fst p :: Type) x

data Snd p Source #

similar to snd

>>> pz @(Snd Id) (10,"Abc")
Present "Abc"
PresentT "Abc"
>>> pz @(Snd Id) (10,"Abc",True)
Present "Abc"
PresentT "Abc"
Instances
(Show (ExtractL2T (PP p x)), ExtractL2C (PP p x), P p x, Show (PP p x)) => P (Snd p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Snd p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Snd p) -> POpts -> x -> m (TT (PP (Snd p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Snd p :: Type) x

data Thd p Source #

similar to 3rd element in a n-tuple

>>> pz @(Thd Id) (10,"Abc",133)
Present 133
PresentT 133
>>> pz @(Thd Id) (10,"Abc",133,True)
Present 133
PresentT 133
Instances
(Show (ExtractL3T (PP p x)), ExtractL3C (PP p x), P p x, Show (PP p x)) => P (Thd p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Thd p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Thd p) -> POpts -> x -> m (TT (PP (Thd p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Thd p :: Type) x

type L1 p = Fst p Source #

type L2 p = Snd p Source #

type L3 p = Thd p Source #

data L4 p Source #

similar to 4th element in a n-tuple

>>> pz @(L4 Id) (10,"Abc",'x',True)
Present True
PresentT True
>>> pz @(L4 (Fst (Snd Id))) ('x',((10,"Abc",'x',999),"aa",1),9)
Present 999
PresentT 999
Instances
(Show (ExtractL4T (PP p x)), ExtractL4C (PP p x), P p x, Show (PP p x)) => P (L4 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (L4 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L4 p) -> POpts -> x -> m (TT (PP (L4 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (L4 p :: Type) x

data L5 p Source #

similar to 5th element in a n-tuple

>>> pz @(L5 Id) (10,"Abc",'x',True,1)
Present 1
PresentT 1
Instances
(Show (ExtractL5T (PP p x)), ExtractL5C (PP p x), P p x, Show (PP p x)) => P (L5 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (L5 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L5 p) -> POpts -> x -> m (TT (PP (L5 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (L5 p :: Type) x

data L6 p Source #

similar to 6th element in a n-tuple

>>> pz @(L6 Id) (10,"Abc",'x',True,1,99)
Present 99
PresentT 99
Instances
(Show (ExtractL6T (PP p x)), ExtractL6C (PP p x), P p x, Show (PP p x)) => P (L6 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (L6 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L6 p) -> POpts -> x -> m (TT (PP (L6 p) x)) Source #

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

Defined in Predicate.Prelude

type PP (L6 p :: Type) x

type Dup = '(Id, Id) Source #

data Swap Source #

swaps using swap

>>> pz @Swap (Left 123)
Present Right 123
PresentT (Right 123)
>>> pz @Swap (Right 123)
Present Left 123
PresentT (Left 123)
>>> pz @Swap (These 'x' 123)
Present These 123 'x'
PresentT (These 123 'x')
>>> pz @Swap (This 'x')
Present That 'x'
PresentT (That 'x')
>>> pz @Swap (That 123)
Present This 123
PresentT (This 123)
>>> pz @Swap (123,'x')
Present ('x',123)
PresentT ('x',123)
>>> pz @Swap (Left "abc")
Present Right "abc"
PresentT (Right "abc")
>>> pz @Swap (Right 123)
Present Left 123
PresentT (Left 123)
Instances
(Show (p a b), Swap p, Show (p b a)) => P Swap (p a b) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Swap (p a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy Swap -> POpts -> p a b -> m (TT (PP Swap (p a b))) Source #

type PP Swap (p a b) Source # 
Instance details

Defined in Predicate.Prelude

type PP Swap (p a b) = p b a

data Assoc Source #

assoc using assoc

>>> pz @Assoc (This (These 123 'x'))
Present These 123 (This 'x')
PresentT (These 123 (This 'x'))
>>> pz @Assoc ((99,'a'),True)
Present (99,('a',True))
PresentT (99,('a',True))
>>> pz @Assoc ((99,'a'),True)
Present (99,('a',True))
PresentT (99,('a',True))
>>> pz @Assoc (Right "Abc" :: Either (Either () ()) String)
Present Right (Right "Abc")
PresentT (Right (Right "Abc"))
>>> pz @Assoc (Left (Left 'x'))
Present Left 'x'
PresentT (Left 'x')
Instances
(Show (p (p a b) c), Show (p a (p b c)), Assoc p) => P Assoc (p (p a b) c) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Assoc (p (p a b) c) :: Type Source #

Methods

eval :: MonadEval m => Proxy Assoc -> POpts -> p (p a b) c -> m (TT (PP Assoc (p (p a b) c))) Source #

type PP Assoc (p (p a b) c) Source # 
Instance details

Defined in Predicate.Prelude

type PP Assoc (p (p a b) c) = p a (p b c)

data Unassoc Source #

unassoc using unassoc

>>> pz @Unassoc (These 123 (This 'x'))
Present This (These 123 'x')
PresentT (This (These 123 'x'))
>>> pz @Unassoc (99,('a',True))
Present ((99,'a'),True)
PresentT ((99,'a'),True)
>>> pz @Unassoc (This 10 :: These Int (These Bool ()))
Present This (This 10)
PresentT (This (This 10))
>>> pz @Unassoc (Right (Right 123))
Present Right 123
PresentT (Right 123)
>>> pz @Unassoc (Left 'x' :: Either Char (Either Bool Double))
Present Left (Left 'x')
PresentT (Left (Left 'x'))
Instances
(Show (p (p a b) c), Show (p a (p b c)), Assoc p) => P Unassoc (p a (p b c)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Unassoc (p a (p b c)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Unassoc -> POpts -> p a (p b c) -> m (TT (PP Unassoc (p a (p b c)))) Source #

type PP Unassoc (p a (p b c)) Source # 
Instance details

Defined in Predicate.Prelude

type PP Unassoc (p a (p b c)) = p (p a b) c

data Pairs Source #

creates a list of overlapping pairs of elements. requires two or more elements

>>> pz @Pairs [1,2,3,4]
Present [(1,2),(2,3),(3,4)]
PresentT [(1,2),(2,3),(3,4)]
>>> pz @Pairs []
Error Pairs no data found
FailT "Pairs no data found"
>>> pz @Pairs [1]
Error Pairs only one element found
FailT "Pairs only one element found"
Instances
Show a => P Pairs [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Pairs [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Pairs -> POpts -> [a] -> m (TT (PP Pairs [a])) Source #

type PP Pairs [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Pairs [a] = [(a, a)]

character expressions

type IsLower = IsCharSet CLower Source #

predicate for determining if a string is all lowercase

>>> pz @IsLower "abcdef213"
False
FalseT
>>> pz @IsLower "abcdef"
True
TrueT
>>> pz @IsLower ""
True
TrueT
>>> pz @IsLower "abcdefG"
False
FalseT

type IsUpper = IsCharSet CUpper Source #

type IsNumber = IsCharSet CNumber Source #

predicate for determining if the string is all digits

>>> pz @IsNumber "213G"
False
FalseT
>>> pz @IsNumber "929"
True
TrueT

type IsSpace = IsCharSet CSpace Source #

type IsPunctuation = IsCharSet CPunctuation Source #

type IsControl = IsCharSet CControl Source #

type IsHexDigit = IsCharSet CHexDigit Source #

type IsOctDigit = IsCharSet COctDigit Source #

type IsSeparator = IsCharSet CSeparator Source #

type IsLatin1 = IsCharSet CLatin1 Source #

datetime expressions

data FormatTimeP p q Source #

type level expression representing a formatted time similar to formatTime using a type level Symbol to get the formatting string

>>> pz @(FormatTimeP "%F %T" Id) (read "2019-05-24 05:19:59" :: LocalTime)
Present "2019-05-24 05:19:59"
PresentT "2019-05-24 05:19:59"
>>> pz @(FormatTimeP (Fst Id) (Snd Id)) ("the date is %d/%m/%Y", read "2019-05-24" :: Day)
Present "the date is 24/05/2019"
PresentT "the date is 24/05/2019"
Instances
(PP p x ~ String, FormatTime (PP q x), P p x, Show (PP q x), P q x) => P (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FormatTimeP p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (FormatTimeP p q) -> POpts -> x -> m (TT (PP (FormatTimeP p q) x)) Source #

type PP (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (FormatTimeP p q :: Type) x = String

type ParseTimeP (t :: Type) p q = ParseTimeP' (Hole t) p q Source #

data ParseTimeP' t p q Source #

similar to parseTimeM where 't' is the ParseTime type, 'p' is the datetime format and 'q' points to the content to parse

>>> pz @(ParseTimeP LocalTime "%F %T" Id) "2019-05-24 05:19:59"
Present 2019-05-24 05:19:59
PresentT 2019-05-24 05:19:59
>>> pz @(ParseTimeP LocalTime "%F %T" "2019-05-24 05:19:59") (Right "never used")
Present 2019-05-24 05:19:59
PresentT 2019-05-24 05:19:59

keeping 'q' as we might want to extract from a tuple

Instances
(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ String, PP q a ~ String) => P (ParseTimeP' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ParseTimeP' t p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParseTimeP' t p q) -> POpts -> a -> m (TT (PP (ParseTimeP' t p q) a)) Source #

type PP (ParseTimeP' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (ParseTimeP' t p q :: Type) a = PP t a

type ParseTimes (t :: Type) p q = ParseTimes' (Hole t) p q Source #

data ParseTimes' t p q Source #

A convenience method to match against many different datetime formats to find a match

>>> pz @(ParseTimes LocalTime '["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"] "03/11/19 01:22:33") ()
Present 2019-03-11 01:22:33
PresentT 2019-03-11 01:22:33
>>> pz @(ParseTimes LocalTime (Fst Id) (Snd Id)) (["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"], "03/11/19 01:22:33")
Present 2019-03-11 01:22:33
PresentT 2019-03-11 01:22:33
Instances
(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ [String], PP q a ~ String) => P (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ParseTimes' t p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParseTimes' t p q) -> POpts -> a -> m (TT (PP (ParseTimes' t p q) a)) Source #

type PP (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (ParseTimes' t p q :: Type) a = PP t a

type MkDay = MkDay' (Fst Id) (Snd Id) (Thd Id) Source #

data MkDay' p q r Source #

create a Day from three int values passed in as year month and day

>>> pz @MkDay (2019,12,30)
Present Just (2019-12-30,1,1)
PresentT (Just (2019-12-30,1,1))
>>> pz @(MkDay' (Fst Id) (Snd Id) (Thd Id)) (2019,99,99999)
Present Nothing
PresentT Nothing
>>> pz @MkDay (1999,3,13)
Present Just (1999-03-13,10,6)
PresentT (Just (1999-03-13,10,6))
Instances
(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Int) => P (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkDay' p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkDay' p q r) -> POpts -> x -> m (TT (PP (MkDay' p q r) x)) Source #

type PP (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkDay' p q r :: Type) x = Maybe (Day, Int, Int)

data UnMkDay p Source #

uncreate a Day returning year month and day

>>> pz @(UnMkDay Id) (read "2019-12-30")
Present (2019,12,30)
PresentT (2019,12,30)
Instances
(PP p x ~ Day, P p x) => P (UnMkDay p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (UnMkDay p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (UnMkDay p) -> POpts -> x -> m (TT (PP (UnMkDay p) x)) Source #

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

Defined in Predicate.Prelude

type PP (UnMkDay p :: Type) x = (Int, Int, Int)

numeric expressions

type (+) p q = Add p q infixl 6 Source #

type (-) p q = Sub p q infixl 6 Source #

type * p q = Mult p q infixl 7 Source #

data p / q infixl 7 Source #

fractional division

>>> pz @(Fst Id / Snd Id) (13,2)
Present 6.5
PresentT 6.5
>>> pz @(ToRational 13 / Id) 0
Error (/) zero denominator
FailT "(/) zero denominator"
>>> pz @(12 % 7 / 14 % 5 + Id) 12.4
Present 3188 % 245
PresentT (3188 % 245)
Instances
(PP p a ~ PP q a, Eq (PP q a), P p a, P q a, Show (PP p a), Fractional (PP p a)) => P (p / q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p / q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p / q) -> POpts -> a -> m (TT (PP (p / q) a)) Source #

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

Defined in Predicate.Prelude

type PP (p / q :: Type) a = PP p a

data Negate p Source #

similar to negate

>>> pz @(Negate Id) 14
Present -14
PresentT (-14)
>>> pz @(Negate (Fst Id * Snd Id)) (14,3)
Present -42
PresentT (-42)
>>> pz @(Negate (15 %- 4)) "abc"
Present 15 % 4
PresentT (15 % 4)
>>> pz @(Negate (15 % 3)) ()
Present (-5) % 1
PresentT ((-5) % 1)
>>> pz @(Negate (Fst Id % Snd Id)) (14,3)
Present (-14) % 3
PresentT ((-14) % 3)
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Negate p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Negate p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Negate p) -> POpts -> x -> m (TT (PP (Negate p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Negate p :: Type) x = PP p x

data Abs p Source #

similar to abs

>>> pz @(Abs Id) (-14)
Present 14
PresentT 14
>>> pz @(Abs (Snd Id)) ("xx",14)
Present 14
PresentT 14
>>> pz @(Abs Id) 0
Present 0
PresentT 0
>>> pz @(Abs (Negate 44)) "aaa"
Present 44
PresentT 44
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Abs p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Abs p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Abs p) -> POpts -> x -> m (TT (PP (Abs p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Abs p :: Type) x = PP p x

data Signum p Source #

similar to signum

>>> pz @(Signum Id) (-14)
Present -1
PresentT (-1)
>>> pz @(Signum Id) 14
Present 1
PresentT 1
>>> pz @(Signum Id) 0
Present 0
PresentT 0
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Signum p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Signum p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Signum p) -> POpts -> x -> m (TT (PP (Signum p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Signum p :: Type) x = PP p x

type FromInteger (t :: Type) p = FromInteger' (Hole t) p Source #

data FromInteger' t n Source #

fromInteger function where you need to provide the type 't' of the result

>>> pz @(FromInteger (SG.Sum _) Id) 23
Present Sum {getSum = 23}
PresentT (Sum {getSum = 23})
>>> pz @(FromInteger Rational 44) 12
Present 44 % 1
PresentT (44 % 1)
>>> pz @(FromInteger Rational Id) 12
Present 12 % 1
PresentT (12 % 1)
Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a)) => P (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromInteger' t n) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromInteger' t n) -> POpts -> a -> m (TT (PP (FromInteger' t n) a)) Source #

type PP (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromInteger' t n :: Type) a = PP t a

type FromIntegral (t :: Type) p = FromIntegral' (Hole t) p Source #

data FromIntegral' t n Source #

fromIntegral function where you need to provide the type 't' of the result

>>> pz @(FromIntegral (SG.Sum _) Id) 23
Present Sum {getSum = 23}
PresentT (Sum {getSum = 23})
Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a), Show (PP n a)) => P (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromIntegral' t n) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromIntegral' t n) -> POpts -> a -> m (TT (PP (FromIntegral' t n) a)) Source #

type PP (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromIntegral' t n :: Type) a = PP t a

type Truncate (t :: Type) p = Truncate' (Hole t) p Source #

data Truncate' t p Source #

truncate function where you need to provide the type 't' of the result

>>> pz @(Truncate Int Id) (23 % 5)
Present 4
PresentT 4
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Truncate' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Truncate' t p) -> POpts -> x -> m (TT (PP (Truncate' t p) x)) Source #

type PP (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Truncate' t p :: Type) x = PP t x

type Ceiling (t :: Type) p = Ceiling' (Hole t) p Source #

data Ceiling' t p Source #

ceiling function where you need to provide the type 't' of the result

>>> pz @(Ceiling Int Id) (23 % 5)
Present 5
PresentT 5
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ceiling' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ceiling' t p) -> POpts -> x -> m (TT (PP (Ceiling' t p) x)) Source #

type PP (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Ceiling' t p :: Type) x = PP t x

type Floor (t :: Type) p = Floor' (Hole t) p Source #

data Floor' t p Source #

floor function where you need to provide the type 't' of the result

>>> pz @(Floor Int Id) (23 % 5)
Present 4
PresentT 4
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Floor' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Floor' t p) -> POpts -> x -> m (TT (PP (Floor' t p) x)) Source #

type PP (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Floor' t p :: Type) x = PP t x

type Even = Mod I 2 == 0 Source #

similar to even

>>> pz @(Map Even Id) [9,-4,12,1,2,3]
Present [False,True,True,False,True,False]
PresentT [False,True,True,False,True,False]
>>> pz @(Map '(Even,Odd) Id) [9,-4,12,1,2,3]
Present [(False,True),(True,False),(True,False),(False,True),(True,False),(False,True)]
PresentT [(False,True),(True,False),(True,False),(False,True),(True,False),(False,True)]

type Odd = Mod I 2 == 1 Source #

data Div p q Source #

similar to div

>>> pz @(Div (Fst Id) (Snd Id)) (10,4)
Present 2
PresentT 2
>>> pz @(Div (Fst Id) (Snd Id)) (10,0)
Error Div zero denominator
FailT "Div zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Div p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Div p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Div p q) -> POpts -> a -> m (TT (PP (Div p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Div p q :: Type) a = PP p a

data Mod p q Source #

similar to mod

>>> pz @(Mod (Fst Id) (Snd Id)) (10,3)
Present 1
PresentT 1
>>> pz @(Mod (Fst Id) (Snd Id)) (10,0)
Error Mod zero denominator
FailT "Mod zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Mod p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Mod p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Mod p q) -> POpts -> a -> m (TT (PP (Mod p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Mod p q :: Type) a = PP p a

data DivMod p q Source #

similar to divMod

>>> pz @(DivMod (Fst Id) (Snd Id)) (10,3)
Present (3,1)
PresentT (3,1)
>>> pz @(DivMod (Fst Id) (Snd Id)) (10,-3)
Present (-4,-2)
PresentT (-4,-2)
>>> pz @(DivMod (Fst Id) (Snd Id)) (-10,3)
Present (-4,2)
PresentT (-4,2)
>>> pz @(DivMod (Fst Id) (Snd Id)) (-10,-3)
Present (3,-1)
PresentT (3,-1)
>>> pz @(DivMod (Fst Id) (Snd Id)) (10,0)
Error DivMod zero denominator
FailT "DivMod zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (DivMod p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (DivMod p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (DivMod p q) -> POpts -> a -> m (TT (PP (DivMod p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (DivMod p q :: Type) a = (PP p a, PP p a)

data QuotRem p q Source #

similar to quotRem

>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,3)
Present (3,1)
PresentT (3,1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,-3)
Present (-3,1)
PresentT (-3,1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (-10,-3)
Present (3,-1)
PresentT (3,-1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (-10,3)
Present (-3,-1)
PresentT (-3,-1)
>>> pz @(QuotRem (Fst Id) (Snd Id)) (10,0)
Error QuotRem zero denominator
FailT "QuotRem zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (QuotRem p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (QuotRem p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (QuotRem p q) -> POpts -> a -> m (TT (PP (QuotRem p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (QuotRem p q :: Type) a = (PP p a, PP p a)

type Quot p q = Fst (QuotRem p q) Source #

type Rem p q = Snd (QuotRem p q) Source #

rational numbers

data p % q infixl 8 Source #

creates a Rational value

>>> pz @(Id < 21 % 5) (-3.1)
True
TrueT
>>> pz @(Id < 21 % 5) 4.5
False
FalseT
>>> pz @(Fst Id % Snd Id) (13,2)
Present 13 % 2
PresentT (13 % 2)
>>> pz @(13 % Id) 0
Error MkRatio zero denominator
FailT "MkRatio zero denominator"
>>> pz @(4 % 3 + 5 % 7) "asfd"
Present 43 % 21
PresentT (43 % 21)
>>> pz @(4 %- 7 * 5 %- 3) "asfd"
Present 20 % 21
PresentT (20 % 21)
>>> pz @(Negate (14 % 3)) ()
Present (-14) % 3
PresentT ((-14) % 3)
>>> pz @(14 % 3) ()
Present 14 % 3
PresentT (14 % 3)
>>> pz @(Negate (14 % 3) ==! FromIntegral _ (Negate 5)) ()
Present GT
PresentT GT
>>> pz @(14 -% 3 ==! 5 %- 1) "aa"
Present GT
PresentT GT
>>> pz @(Negate (14 % 3) ==! Negate 5 % 2) ()
Present LT
PresentT LT
>>> pz @(14 -% 3 * 5 -% 1) ()
Present 70 % 3
PresentT (70 % 3)
>>> pz @(14 % 3 ==! 5 % 1) ()
Present LT
PresentT LT
>>> pz @(15 % 3 / 4 % 2) ()
Present 5 % 2
PresentT (5 % 2)
Instances
(Integral (PP p x), Integral (PP q x), Eq (PP q x), P p x, P q x, Show (PP p x), Show (PP q x)) => P (p % q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p % q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p % q) -> POpts -> x -> m (TT (PP (p % q) x)) Source #

type PP (p % q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p % q :: Type) x = Rational

type (%-) p q = Negate (p % q) infixl 8 Source #

type (-%) p q = Negate (p % q) infixl 8 Source #

data ToRational p Source #

toRational function

>>> pz @(ToRational Id) 23.5
Present 47 % 2
PresentT (47 % 2)
Instances
(a ~ PP p x, Show a, Real a, P p x) => P (ToRational p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToRational p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToRational p) -> POpts -> x -> m (TT (PP (ToRational p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ToRational p :: Type) x = Rational

type FromRational (t :: Type) p = FromRational' (Hole t) p Source #

data FromRational' t r Source #

fromRational function where you need to provide the type 't' of the result

>>> pz @(FromRational Rational Id) 23.5
Present 47 % 2
PresentT (47 % 2)
Instances
(P r a, PP r a ~ Rational, Show (PP t a), Fractional (PP t a)) => P (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromRational' t r) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromRational' t r) -> POpts -> a -> m (TT (PP (FromRational' t r) a)) Source #

type PP (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromRational' t r :: Type) a = PP t a

proxy expressions

data MkProxy Source #

converts a value to a Proxy: the same as '\'Proxy'

>>> pz @MkProxy 'x'
Present Proxy
PresentT Proxy
Instances
Show a => P MkProxy a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP MkProxy a :: Type Source #

Methods

eval :: MonadEval m => Proxy MkProxy -> POpts -> a -> m (TT (PP MkProxy a)) Source #

type PP MkProxy a Source # 
Instance details

Defined in Predicate.Prelude

type PP MkProxy a = Proxy a

type ProxyT (t :: Type) = ProxyT' (Hole t) Source #

data ProxyT' t Source #

Instances
Typeable t => P (ProxyT' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ProxyT' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ProxyT' t) -> POpts -> a -> m (TT (PP (ProxyT' t) a)) Source #

type PP (ProxyT' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (ProxyT' t :: Type) a = Proxy (PP t a)

data Unproxy Source #

Instances
Typeable a => P Unproxy (Proxy a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Unproxy (Proxy a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Unproxy -> POpts -> Proxy a -> m (TT (PP Unproxy (Proxy a))) Source #

type PP Unproxy (Proxy a) Source # 
Instance details

Defined in Predicate.Prelude

type PP Unproxy (Proxy a) = a

read / show expressions

data ShowP p Source #

similar to show

>>> pz @(ShowP Id) [4,8,3,9]
Present "[4,8,3,9]"
PresentT "[4,8,3,9]"
>>> pz @(ShowP Id) 'x'
Present "'x'"
PresentT "'x'"
>>> pz @(ShowP (42 %- 10)) 'x'
Present "(-21) % 5"
PresentT "(-21) % 5"
Instances
(Show (PP p x), P p x) => P (ShowP p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ShowP p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ShowP p) -> POpts -> x -> m (TT (PP (ShowP p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ShowP p :: Type) x = String

type ReadP (t :: Type) p = ReadP' (Hole t) p Source #

data ReadP' t p Source #

uses the Read of the given type 't' and 'p' which points to the content to read

>>> pz @(ReadP Rational Id) "4 % 5"
Present 4 % 5
PresentT (4 % 5)
>>> pz @(ReadP Day Id >> Between (ReadP Day "2017-04-11") (ReadP Day "2018-12-30")) "2018-10-12"
True
TrueT
>>> pz @(ReadP Day Id >> Between (ReadP Day "2017-04-11") (ReadP Day "2018-12-30")) "2016-10-12"
False
FalseT
Instances
(P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), Read (PP t x)) => P (ReadP' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadP' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadP' t p) -> POpts -> x -> m (TT (PP (ReadP' t p) x)) Source #

type PP (ReadP' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ReadP' t p :: Type) x = PP t x

type ReadQ (t :: Type) p = ReadQ' (Hole t) p Source #

type ReadQ' t p = ReadMaybe' t p >> MaybeIn (Failp "read failed") (Guard "oops" (Snd Id >> Null) >> Fst Id) Source #

emulates ReadP

type ReadMaybe (t :: Type) p = ReadMaybe' (Hole t) p Source #

data ReadMaybe' t p Source #

Read but returns the Maybe of the value and any remaining unparsed string

>>> pz @(ReadMaybe Int Id) "123x"
Present Just (123,"x")
PresentT (Just (123,"x"))
>>> pz @(ReadMaybe Int Id) "123"
Present Just (123,"")
PresentT (Just (123,""))
>>> pz @(ReadMaybe Int Id) "x123"
Present Nothing
PresentT Nothing
Instances
(P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), Read (PP t x)) => P (ReadMaybe' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadMaybe' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadMaybe' t p) -> POpts -> x -> m (TT (PP (ReadMaybe' t p) x)) Source #

type PP (ReadMaybe' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ReadMaybe' t p :: Type) x = Maybe (PP t x, String)

type ReadBase (t :: Type) (n :: Nat) p = ReadBase' (Hole t) n p Source #

data ReadBase' t (n :: Nat) p Source #

Read a number using base 2 through a maximum of 36

>>> pz @(ReadBase Int 16 Id) "00feD"
Present 4077
PresentT 4077
>>> pz @(ReadBase Int 16 Id) "-ff"
Present -255
PresentT (-255)
>>> pz @(ReadBase Int 2 Id) "10010011"
Present 147
PresentT 147
>>> pz @(ReadBase Int 8 Id) "Abff"
Error invalid base 8
FailT "invalid base 8"

supports negative numbers unlike readInt

Instances
(Typeable (PP t x), BetweenT 2 36 n, Show (PP t x), Num (PP t x), KnownNat n, PP p x ~ String, P p x) => P (ReadBase' t n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadBase' t n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadBase' t n p) -> POpts -> x -> m (TT (PP (ReadBase' t n p) x)) Source #

type PP (ReadBase' t n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ReadBase' t n p :: Type) x = PP t x

type ReadBaseInt (n :: Nat) p = ReadBase' (Hole Int) n p Source #

data ShowBase (n :: Nat) p Source #

Display a number at base 2 to 36, similar to showIntAtBase but supports signed numbers

>>> pz @(ShowBase 16 Id) 4077
Present "fed"
PresentT "fed"
>>> pz @(ShowBase 16 Id) (-255)
Present "-ff"
PresentT "-ff"
>>> pz @(ShowBase 2 Id) 147
Present "10010011"
PresentT "10010011"
>>> pz @(ShowBase 2 (Negate 147)) "whatever"
Present "-10010011"
PresentT "-10010011"
Instances
(PP p x ~ a, P p x, Show a, 2 <= n, n <= 36, KnownNat n, Integral a) => P (ShowBase n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ShowBase n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ShowBase n p) -> POpts -> x -> m (TT (PP (ShowBase n p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ShowBase n p :: Type) x = String

arrow expressions

type (&&&) p q = W '(p, q) infixr 3 Source #

similar to &&&

data p *** q infixr 3 Source #

similar to ***

>>> pz @(Pred Id *** ShowP Id) (13, True)
Present (12,"True")
PresentT (12,"True")
Instances
(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p *** q :: Type) (a, b) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p *** q) (a, b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p *** q) -> POpts -> (a, b) -> m (TT (PP (p *** q) (a, b))) Source #

type PP (p *** q :: Type) (a, b) Source # 
Instance details

Defined in Predicate.Prelude

type PP (p *** q :: Type) (a, b) = (PP p a, PP q b)

type First p = p *** I Source #

type Second q = I *** q Source #

data p ||| q infixr 2 Source #

similar |||

>>> pz @(Pred Id ||| Id) (Left 13)
Present 12
PresentT 12
>>> pz @(ShowP Id ||| Id) (Right "hello")
Present "hello"
PresentT "hello"
Instances
(Show (PP p a), P p a, P q b, PP p a ~ PP q b, Show a, Show b) => P (p ||| q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p ||| q) (Either a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ||| q) -> POpts -> Either a b -> m (TT (PP (p ||| q) (Either a b))) Source #

type PP (p ||| q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate.Prelude

type PP (p ||| q :: Type) (Either a b) = PP p a

data p +++ q infixr 2 Source #

similar +++

>>> pz @(Pred Id +++ Id) (Left 13)
Present Left 12
PresentT (Left 12)
>>> pz @(ShowP Id +++ Reverse) (Right "hello")
Present Right "olleh"
PresentT (Right "olleh")
Instances
(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p +++ q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p +++ q) (Either a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p +++ q) -> POpts -> Either a b -> m (TT (PP (p +++ q) (Either a b))) Source #

type PP (p +++ q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate.Prelude

type PP (p +++ q :: Type) (Either a b) = Either (PP p a) (PP q b)

compare expressions

type (>) p q = Cmp Cgt p q infix 4 Source #

type (>=) p q = Cmp Cge p q infix 4 Source #

type (==) p q = Cmp Ceq p q infix 4 Source #

type (/=) p q = Cmp Cne p q infix 4 Source #

type (<=) p q = Cmp Cle p q infix 4 Source #

type (<) p q = Cmp Clt p q infix 4 Source #

type (>~) p q = CmpI Cgt p q infix 4 Source #

type (>=~) p q = CmpI Cge p q infix 4 Source #

type (==~) p q = CmpI Ceq p q infix 4 Source #

type (/=~) p q = CmpI Cne p q infix 4 Source #

type (<=~) p q = CmpI Cle p q infix 4 Source #

type (<~) p q = CmpI Clt p q infix 4 Source #

type Gt n = Cmp Cgt I n Source #

type Ge n = Cmp Cge I n Source #

type Same n = Cmp Ceq I n Source #

type Le n = Cmp Cle I n Source #

type Lt n = Cmp Clt I n Source #

type Ne n = Cmp Cne I n Source #

data OrdP p q Source #

Instances
(Ord (PP p a), PP p a ~ PP q a, P p a, Show (PP q a), P q a) => P (OrdP p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (OrdP p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (OrdP p q) -> POpts -> a -> m (TT (PP (OrdP p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (OrdP p q :: Type) a = Ordering

type (==!) p q = OrdP p q infix 4 Source #

type OrdA' p q = OrdP (Fst Id >> p) (Snd Id >> q) Source #

similar to compare

>>> pz @(Fst Id ==! Snd Id) (10,9)
Present GT
PresentT GT
>>> pz @(14 % 3 ==! Fst Id %- Snd Id) (-10,7)
Present GT
PresentT GT
>>> pz @(Fst Id ==! Snd Id) (10,11)
Present LT
PresentT LT
>>> pz @(Snd Id ==! (Fst Id >> Snd Id >> Head Id)) (('x',[10,12,13]),10)
Present EQ
PresentT EQ
>>> pz @(Snd Id ==! Head (Snd (Fst Id))) (('x',[10,12,13]),10)
Present EQ
PresentT EQ

type OrdA p = OrdA' p p Source #

data OrdI p q Source #

compare two strings ignoring case

>>> pz @(Fst Id ===~ Snd Id) ("abC","aBc")
Present EQ
PresentT EQ
>>> pz @(Fst Id ===~ Snd Id) ("abC","DaBc")
Present LT
PresentT LT
Instances
(PP p a ~ String, PP p a ~ PP q a, P p a, P q a) => P (OrdI p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (OrdI p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (OrdI p q) -> POpts -> a -> m (TT (PP (OrdI p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (OrdI p q :: Type) a = Ordering

type (===~) p q = OrdI p q infix 4 Source #

data Cmp (o :: OrderingP) p q Source #

compare two values using the given ordering 'o'

Instances
(GetOrd o, Ord (PP p a), Show (PP p a), PP p a ~ PP q a, P p a, P q a) => P (Cmp o p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Cmp o p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Cmp o p q) -> POpts -> a -> m (TT (PP (Cmp o p q) a)) Source #

type PP (Cmp o p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Cmp o p q :: Type) a = Bool

data CmpI (o :: OrderingP) p q Source #

compare two strings ignoring case using the given ordering 'o'

Instances
(PP p a ~ String, GetOrd o, PP p a ~ PP q a, P p a, P q a) => P (CmpI o p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (CmpI o p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (CmpI o p q) -> POpts -> a -> m (TT (PP (CmpI o p q) a)) Source #

type PP (CmpI o p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (CmpI o p q :: Type) a = Bool

enum expressions

data Succ p Source #

unbounded succ function

>>> pz @(Succ Id) 13
Present 14
PresentT 14
>>> pz @(Succ Id) LT
Present EQ
PresentT EQ
>>> pz @(Succ Id) GT
Error Succ IO e=Prelude.Enum.Ordering.succ: bad argument
FailT "Succ IO e=Prelude.Enum.Ordering.succ: bad argument"
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (Succ p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Succ p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Succ p) -> POpts -> x -> m (TT (PP (Succ p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Succ p :: Type) x = PP p x

data Pred p Source #

unbounded pred function

>>> pz @(Pred Id) 13
Present 12
PresentT 12
>>> pz @(Pred Id) LT
Error Pred IO e=Prelude.Enum.Ordering.pred: bad argument
FailT "Pred IO e=Prelude.Enum.Ordering.pred: bad argument"
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (Pred p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Pred p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pred p) -> POpts -> x -> m (TT (PP (Pred p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Pred p :: Type) x = PP p x

data FromEnum p Source #

fromEnum function

>>> pz @(FromEnum Id) 'x'
Present 120
PresentT 120
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (FromEnum p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromEnum p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromEnum p) -> POpts -> x -> m (TT (PP (FromEnum p) x)) Source #

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

Defined in Predicate.Prelude

type PP (FromEnum p :: Type) x = Int

type ToEnum (t :: Type) p = ToEnum' (Hole t) p Source #

data ToEnum' t p Source #

unsafe toEnum function

>>> pz @(ToEnum Char Id) 120
Present 'x'
PresentT 'x'
Instances
(PP p x ~ a, P p x, Show a, Enum (PP t x), Show (PP t x), Integral a) => P (ToEnum' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToEnum' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToEnum' t p) -> POpts -> x -> m (TT (PP (ToEnum' t p) x)) Source #

type PP (ToEnum' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ToEnum' t p :: Type) x = PP t x

data EnumFromTo p q Source #

similar to enumFromTo

>>> pz @(EnumFromTo 2 5) ()
Present [2,3,4,5]
PresentT [2,3,4,5]
>>> pz @(EnumFromTo 'LT 'GT) ()
Present [LT,EQ,GT]
PresentT [LT,EQ,GT]
>>> pz @(EnumFromTo 'GT 'LT) ()
Present []
PresentT []
>>> pz @(EnumFromTo (Pred Id) (Succ Id)) (SG.Max 10)
Present [Max {getMax = 9},Max {getMax = 10},Max {getMax = 11}]
PresentT [Max {getMax = 9},Max {getMax = 10},Max {getMax = 11}]
Instances
(P p x, P q x, PP p x ~ a, Show a, PP q x ~ a, Enum a) => P (EnumFromTo p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (EnumFromTo p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EnumFromTo p q) -> POpts -> x -> m (TT (PP (EnumFromTo p q) x)) Source #

type PP (EnumFromTo p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (EnumFromTo p q :: Type) x = [PP p x]

bounded enum expressions

data SuccB p q Source #

bounded succ function

>>> pz @(SuccB' Id) (13 :: Int)
Present 14
PresentT 14
>>> pz @(SuccB' Id) LT
Present EQ
PresentT EQ
>>> pz @(SuccB 'LT Id) GT
Present LT
PresentT LT
>>> pz @(SuccB' Id) GT
Error Succ bounded failed
FailT "Succ bounded failed"
Instances
(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (SuccB p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (SuccB p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SuccB p q) -> POpts -> x -> m (TT (PP (SuccB p q) x)) Source #

type PP (SuccB p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (SuccB p q :: Type) x = PP q x

type SuccB' q = SuccB (Failp "Succ bounded failed") q Source #

data PredB p q Source #

bounded pred function

>>> pz @(PredB' Id) (13 :: Int)
Present 12
PresentT 12
>>> pz @(PredB' Id) LT
Error Pred bounded failed
FailT "Pred bounded failed"
Instances
(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (PredB p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PredB p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (PredB p q) -> POpts -> x -> m (TT (PP (PredB p q) x)) Source #

type PP (PredB p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (PredB p q :: Type) x = PP q x

type PredB' q = PredB (Failp "Pred bounded failed") q Source #

type ToEnumBDef (t :: Type) def = ToEnumBDef' (Hole t) def Source #

data ToEnumBDef' t def Source #

bounded toEnum function

>>> pz @(ToEnumBDef Ordering LT) 2
Present GT
PresentT GT
>>> pz @(ToEnumBDef Ordering LT) 6
Present LT
PresentT LT
>>> pz @(ToEnumBFail Ordering) 6
Error ToEnum bounded failed
FailT "ToEnum bounded failed"
Instances
(P def (Proxy (PP t a)), PP def (Proxy (PP t a)) ~ PP t a, Show a, Show (PP t a), Bounded (PP t a), Enum (PP t a), Integral a) => P (ToEnumBDef' t def :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToEnumBDef' t def) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToEnumBDef' t def) -> POpts -> a -> m (TT (PP (ToEnumBDef' t def) a)) Source #

type PP (ToEnumBDef' t def :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (ToEnumBDef' t def :: Type) a = PP t a

type ToEnumBFail (t :: Type) = ToEnumBDef' (Hole t) (Failp "ToEnum bounded failed") Source #

wrap / unwrap expressions

data Unwrap p Source #

unwraps a value (see _Wrapped')

>>> pz @(Unwrap Id) (SG.Sum (-13))
Present -13
PresentT (-13)
Instances
(PP p x ~ s, P p x, Show s, Show (Unwrapped s), Wrapped s) => P (Unwrap p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Unwrap p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Unwrap p) -> POpts -> x -> m (TT (PP (Unwrap p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Unwrap p :: Type) x = Unwrapped (PP p x)

type Wrap (t :: Type) p = Wrap' (Hole t) p Source #

data Wrap' t p Source #

wraps a value (see _Wrapped' and _Unwrapped')

>>> :m + Data.List.NonEmpty
>>> pz @(Wrap (SG.Sum _) Id) (-13)
Present Sum {getSum = -13}
PresentT (Sum {getSum = -13})
>>> pz @(Wrap SG.Any (Ge 4)) 13
Present Any {getAny = True}
PresentT (Any {getAny = True})
>>> pz @(Wrap (NonEmpty _) (Uncons >> 'Just Id)) "abcd"
Present 'a' :| "bcd"
PresentT ('a' :| "bcd")
Instances
(Show (PP p x), P p x, Unwrapped (PP s x) ~ PP p x, Wrapped (PP s x), Show (PP s x)) => P (Wrap' s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Wrap' s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Wrap' s p) -> POpts -> x -> m (TT (PP (Wrap' s p) x)) Source #

type PP (Wrap' s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Wrap' s p :: Type) x = PP s x

data Coerce (t :: k) Source #

similar to coerce

>>> pz @(Coerce (SG.Sum Integer)) (Identity (-13))
Present Sum {getSum = -13}
PresentT (Sum {getSum = -13})
Instances
(Show a, Show t, Coercible t a) => P (Coerce t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Coerce t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Coerce t) -> POpts -> a -> m (TT (PP (Coerce t) a)) Source #

type PP (Coerce t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Coerce t :: Type) a = t

data Coerce2 (t :: k) Source #

see Coerce: coerce over a functor

>>> pz @(Coerce2 (SG.Sum Integer)) [Identity (-13), Identity 4, Identity 99]
Present [Sum {getSum = -13},Sum {getSum = 4},Sum {getSum = 99}]
PresentT [Sum {getSum = -13},Sum {getSum = 4},Sum {getSum = 99}]
>>> pz @(Coerce2 (SG.Sum Integer)) (Just (Identity (-13)))
Present Just (Sum {getSum = -13})
PresentT (Just (Sum {getSum = -13}))
>>> pz @(Coerce2 (SG.Sum Int)) (Nothing @(Identity Int))
Present Nothing
PresentT Nothing
Instances
(Show (f a), Show (f t), Coercible t a, Functor f) => P (Coerce2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Coerce2 t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Coerce2 t) -> POpts -> f a -> m (TT (PP (Coerce2 t) (f a))) Source #

type PP (Coerce2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

type PP (Coerce2 t :: Type) (f a) = f t

list / foldable expressions

data Map p q Source #

similar to map

>>> pz @(Map (Pred Id) Id) [1..5]
Present [0,1,2,3,4]
PresentT [0,1,2,3,4]
Instances
(Show (PP p a), P p a, PP q x ~ f a, P q x, Show a, Show (f a), Foldable f) => P (Map p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Map p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Map p q) -> POpts -> x -> m (TT (PP (Map p q) x)) Source #

type PP (Map p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Map p q :: Type) x

data Concat p Source #

similar to concat

>>> pz @(Concat Id) ["abc","D","eF","","G"]
Present "abcDeFG"
PresentT "abcDeFG"
>>> pz @(Concat (Snd Id)) ('x',["abc","D","eF","","G"])
Present "abcDeFG"
PresentT "abcDeFG"
Instances
(Show a, Show (t [a]), PP p x ~ t [a], P p x, Foldable t) => P (Concat p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Concat p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Concat p) -> POpts -> x -> m (TT (PP (Concat p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Concat p :: Type) x

type ConcatMap p q = Concat (Map p q) Source #

data Partition p q Source #

similar to partition

>>> pz @(Partition (Ge 3) Id) [10,4,1,7,3,1,3,5]
Present ([10,4,7,3,3,5],[1,1])
PresentT ([10,4,7,3,3,5],[1,1])
>>> pz @(Partition (Prime Id) Id) [10,4,1,7,3,1,3,5]
Present ([7,3,3,5],[10,4,1,1])
PresentT ([7,3,3,5],[10,4,1,1])
>>> pz @(Partition (Ge 300) Id) [10,4,1,7,3,1,3,5]
Present ([],[10,4,1,7,3,1,3,5])
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pz @(Partition (Id < 300) Id) [10,4,1,7,3,1,3,5]
Present ([10,4,1,7,3,1,3,5],[])
PresentT ([10,4,1,7,3,1,3,5],[])
Instances
(P p x, Show x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Partition p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Partition p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Partition p q) -> POpts -> a -> m (TT (PP (Partition p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Partition p q :: Type) a = (PP q a, PP q a)

type Filter p q = Partition p q >> Fst Id Source #

data Break p q Source #

similar to break

>>> pz @(Break (Ge 3) Id) [10,4,1,7,3,1,3,5]
Present ([],[10,4,1,7,3,1,3,5])
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pz @(Break (Lt 3) Id) [10,4,1,7,3,1,3,5]
Present ([10,4],[1,7,3,1,3,5])
PresentT ([10,4],[1,7,3,1,3,5])
Instances
(P p x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Break p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Break p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Break p q) -> POpts -> a -> m (TT (PP (Break p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Break p q :: Type) a = (PP q a, PP q a)

type Span p q = Break (Not p) q Source #

data Intercalate p q Source #

intercalate two lists

>>> pz @(Intercalate '["aB"] '["xxxx","yz","z","www","xyz"]) ()
Present ["xxxx","aB","yz","aB","z","aB","www","aB","xyz"]
PresentT ["xxxx","aB","yz","aB","z","aB","www","aB","xyz"]
>>> pz @(Intercalate '[W 99,Negate 98] Id) [1..5]
Present [1,99,-98,2,99,-98,3,99,-98,4,99,-98,5]
PresentT [1,99,-98,2,99,-98,3,99,-98,4,99,-98,5]
>>> pz @(Intercalate '[99,100] Id) [1..5]
Present [1,99,100,2,99,100,3,99,100,4,99,100,5]
PresentT [1,99,100,2,99,100,3,99,100,4,99,100,5]
Instances
(PP p x ~ [a], PP q x ~ PP p x, P p x, P q x, Show a) => P (Intercalate p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Intercalate p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Intercalate p q) -> POpts -> x -> m (TT (PP (Intercalate p q) x)) Source #

type PP (Intercalate p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Intercalate p q :: Type) x = PP p x

data Elem p q Source #

elem function

>>> pz @(Elem (Fst Id) (Snd Id)) ('x',"abcdxy")
True
TrueT
>>> pz @(Elem (Fst Id) (Snd Id)) ('z',"abcdxy")
False
FalseT
Instances
([PP p a] ~ PP q a, P p a, P q a, Show (PP p a), Eq (PP p a)) => P (Elem p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Elem p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Elem p q) -> POpts -> a -> m (TT (PP (Elem p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Elem p q :: Type) a = Bool

data Inits Source #

similar to inits

>>> pz @Inits [4,8,3,9]
Present [[],[4],[4,8],[4,8,3],[4,8,3,9]]
PresentT [[],[4],[4,8],[4,8,3],[4,8,3,9]]
>>> pz @Inits []
Present [[]]
PresentT [[]]
Instances
Show a => P Inits [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Inits [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Inits -> POpts -> [a] -> m (TT (PP Inits [a])) Source #

type PP Inits [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Inits [a] = [[a]]

data Tails Source #

similar to tails

>>> pz @Tails [4,8,3,9]
Present [[4,8,3,9],[8,3,9],[3,9],[9],[]]
PresentT [[4,8,3,9],[8,3,9],[3,9],[9],[]]
>>> pz @Tails []
Present [[]]
PresentT [[]]
Instances
Show a => P Tails [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Tails [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Tails -> POpts -> [a] -> m (TT (PP Tails [a])) Source #

type PP Tails [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Tails [a] = [[a]]

data Ones p Source #

split a list into single values

>>> pz @(Ones Id) [4,8,3,9]
Present [[4],[8],[3],[9]]
PresentT [[4],[8],[3],[9]]
>>> pz @(Ones Id) []
Present []
PresentT []
Instances
(PP p x ~ [a], P p x, Show a) => P (Ones p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ones p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ones p) -> POpts -> x -> m (TT (PP (Ones p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Ones p :: Type) x = [PP p x]

type OneP = Guard (PrintF "expected list of length 1 but found length=%d" Len) (Len == 1) >> Head Id Source #

data Len Source #

similar to length

>>> pz @Len [10,4,5,12,3,4]
Present 6
PresentT 6
>>> pz @Len []
Present 0
PresentT 0
Instances
(Show a, as ~ [a]) => P Len as Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Len as :: Type Source #

Methods

eval :: MonadEval m => Proxy Len -> POpts -> as -> m (TT (PP Len as)) Source #

type PP Len as Source # 
Instance details

Defined in Predicate.Prelude

type PP Len as = Int

data Length p Source #

similar to length for Foldable instances

>>> pz @(Length Id) (Left "aa")
Present 0
PresentT 0
>>> pz @(Length Id) (Right "aa")
Present 1
PresentT 1
>>> pz @(Length (Right' Id)) (Right "abcd")
Present 4
PresentT 4
>>> pz @(Length (Thd (Snd Id))) (True,(23,'x',[10,9,1,3,4,2]))
Present 6
PresentT 6
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t) => P (Length p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Length p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Length p) -> POpts -> x -> m (TT (PP (Length p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Length p :: Type) x = Int

type PadL n p q = Pad True n p q Source #

type PadR n p q = Pad False n p q Source #

data Cycle n p Source #

similar to cycle but for a fixed number 'n'

>>> pz @(Cycle 5 Id) [1,2]
Present [1,2,1,2,1]
PresentT [1,2,1,2,1]
Instances
(Show a, Show (t a), PP p x ~ t a, P p x, Integral (PP n x), P n x, Foldable t) => P (Cycle n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Cycle n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Cycle n p) -> POpts -> x -> m (TT (PP (Cycle n p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Cycle n p :: Type) x

data SplitAts ns p Source #

split a list 'p' into parts using the lengths in the type level list 'ns'

>>> pz @(SplitAts '[2,3,1,1] Id) "hello world"
Present ["he","llo"," ","w","orld"]
PresentT ["he","llo"," ","w","orld"]
>>> pz @(SplitAts '[2] Id) "hello world"
Present ["he","llo world"]
PresentT ["he","llo world"]
>>> pz @(SplitAts '[10,1,1,5] Id) "hello world"
Present ["hello worl","d","",""]
PresentT ["hello worl","d","",""]
Instances
(P ns x, P p x, PP p x ~ [a], Show n, Show a, PP ns x ~ [n], Integral n) => P (SplitAts ns p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (SplitAts ns p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SplitAts ns p) -> POpts -> x -> m (TT (PP (SplitAts ns p) x)) Source #

type PP (SplitAts ns p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (SplitAts ns p :: Type) x = [PP p x]

data SplitAt n p Source #

similar to splitAt

>>> pz @(SplitAt 4 Id) "hello world"
Present ("hell","o world")
PresentT ("hell","o world")
>>> pz @(SplitAt 20 Id) "hello world"
Present ("hello world","")
PresentT ("hello world","")
>>> pz @(SplitAt 0 Id) "hello world"
Present ("","hello world")
PresentT ("","hello world")
>>> pz @(SplitAt (Snd Id) (Fst Id)) ("hello world",4)
Present ("hell","o world")
PresentT ("hell","o world")
Instances
(PP p a ~ [b], P n a, P p a, Show b, Integral (PP n a)) => P (SplitAt n p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (SplitAt n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (SplitAt n p) -> POpts -> a -> m (TT (PP (SplitAt n p) a)) Source #

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

Defined in Predicate.Prelude

type PP (SplitAt n p :: Type) a = (PP p a, PP p a)

type Take n p = Fst (SplitAt n p) Source #

type Drop n p = Snd (SplitAt n p) Source #

data Min Source #

similar to minimum

>>> pz @Min [10,4,5,12,3,4]
Present 3
PresentT 3
>>> pz @Min []
Error empty list
FailT "empty list"
Instances
(Ord a, Show a) => P Min [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Min [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Min -> POpts -> [a] -> m (TT (PP Min [a])) Source #

type PP Min [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Min [a] = a

data Max Source #

similar to maximum

>>> pz @Max [10,4,5,12,3,4]
Present 12
PresentT 12
>>> pz @Max []
Error empty list
FailT "empty list"
Instances
(Ord a, Show a) => P Max [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Max [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Max -> POpts -> [a] -> m (TT (PP Max [a])) Source #

type PP Max [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Max [a] = a

data Sum Source #

similar to sum

>>> pz @Sum [10,4,5,12,3,4]
Present 38
PresentT 38
>>> pz @Sum []
Present 0
PresentT 0
Instances
(Num a, Show a) => P Sum [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Sum [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Sum -> POpts -> [a] -> m (TT (PP Sum [a])) Source #

type PP Sum [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP Sum [a] = a

data IsEmpty Source #

similar to null using AsEmpty

>>> pz @IsEmpty [1,2,3,4]
False
FalseT
>>> pz @IsEmpty []
True
TrueT
>>> pz @IsEmpty LT
False
FalseT
>>> pz @IsEmpty EQ
True
TrueT
Instances
(Show as, AsEmpty as) => P IsEmpty as Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsEmpty as :: Type Source #

Methods

eval :: MonadEval m => Proxy IsEmpty -> POpts -> as -> m (TT (PP IsEmpty as)) Source #

type PP IsEmpty as Source # 
Instance details

Defined in Predicate.Prelude

type PP IsEmpty as = Bool

data Null Source #

similar to null using Foldable

>>> pz @Null [1,2,3,4]
False
FalseT
>>> pz @Null []
True
TrueT
>>> pz @Null Nothing
True
TrueT
Instances
(Show (t a), Foldable t, t a ~ as) => P Null as Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Null as :: Type Source #

Methods

eval :: MonadEval m => Proxy Null -> POpts -> as -> m (TT (PP Null as)) Source #

type PP Null as Source # 
Instance details

Defined in Predicate.Prelude

type PP Null as = Bool

data ToList Source #

similar to toList

>>> pz @ToList ("aBc" :: String)
Present "aBc"
PresentT "aBc"
>>> pz @ToList (Just 14)
Present [14]
PresentT [14]
>>> pz @ToList Nothing
Present []
PresentT []
>>> pz @ToList (Left "xx")
Present []
PresentT []
>>> pz @ToList (These 12 "xx")
Present ["xx"]
PresentT ["xx"]
Instances
(Show (t a), Foldable t, Show a) => P ToList (t a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ToList (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy ToList -> POpts -> t a -> m (TT (PP ToList (t a))) Source #

type PP ToList (t a) Source # 
Instance details

Defined in Predicate.Prelude

type PP ToList (t a) = [a]

data ToList' p Source #

similar to toList

>>> pz @(ToList' Id) ("aBc" :: String)
Present "aBc"
PresentT "aBc"
>>> pz @(ToList' Id) (Just 14)
Present [14]
PresentT [14]
>>> pz @(ToList' Id) Nothing
Present []
PresentT []
>>> pz @(ToList' Id) (Left "xx")
Present []
PresentT []
>>> pz @(ToList' Id) (These 12 "xx")
Present ["xx"]
PresentT ["xx"]
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, Show a) => P (ToList' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToList' p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToList' p) -> POpts -> x -> m (TT (PP (ToList' p) x)) Source #

type PP (ToList' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ToList' p :: Type) x

type IToList (t :: Type) = IToList' (Hole t) Id Source #

data IToList' t p Source #

similar to itoList

>>> pz @(IToList _) ("aBc" :: String)
Present [(0,'a'),(1,'B'),(2,'c')]
PresentT [(0,'a'),(1,'B'),(2,'c')]
Instances
(Show x, P p x, Typeable (PP t (PP p x)), Show (PP t (PP p x)), FoldableWithIndex (PP t (PP p x)) f, PP p x ~ f a, Show a) => P (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IToList' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (IToList' t p) -> POpts -> x -> m (TT (PP (IToList' t p) x)) Source #

type PP (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (IToList' t p :: Type) x

data FromList (t :: Type) Source #

Instances
(a ~ Item t, Show t, IsList t) => P (FromList t :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromList t) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromList t) -> POpts -> [a] -> m (TT (PP (FromList t) [a])) Source #

type PP (FromList t :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromList t :: Type) [a] = t

type EmptyList (t :: Type) = EmptyList' (Hole t) Source #

data EmptyList' t Source #

creates an empty list of the given type

>>> pz @(Id :+ EmptyList _) 99
Present [99]
PresentT [99]
Instances
P (EmptyList' t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (EmptyList' t) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EmptyList' t) -> POpts -> x -> m (TT (PP (EmptyList' t) x)) Source #

type PP (EmptyList' t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (EmptyList' t :: Type) x = [PP t x]

type Singleton p = p :+ EmptyT [] p Source #

creates a singleton from a value

>>> pz @(Singleton (Char1 "aBc")) ()
Present "a"
PresentT "a"
>>> pz @(Singleton Id) False
Present [False]
PresentT [False]
>>> pz @(Singleton (Snd Id)) (False,"hello")
Present ["hello"]
PresentT ["hello"]

data Reverse Source #

similar to reverse

>>> pz @Reverse [1,2,4]
Present [4,2,1]
PresentT [4,2,1]
>>> pz @Reverse "AbcDeF"
Present "FeDcbA"
PresentT "FeDcbA"
Instances
(Show a, as ~ [a]) => P Reverse as Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Reverse as :: Type Source #

Methods

eval :: MonadEval m => Proxy Reverse -> POpts -> as -> m (TT (PP Reverse as)) Source #

type PP Reverse as Source # 
Instance details

Defined in Predicate.Prelude

type PP Reverse as = as

data ReverseL Source #

reverses using reversing

>>> pz @ReverseL (T.pack "AbcDeF")
Present "FeDcbA"
PresentT "FeDcbA"
>>> pz @ReverseL ("AbcDeF" :: String)
Present "FeDcbA"
PresentT "FeDcbA"
Instances
(Show t, Reversing t) => P ReverseL t Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ReverseL t :: Type Source #

Methods

eval :: MonadEval m => Proxy ReverseL -> POpts -> t -> m (TT (PP ReverseL t)) Source #

type PP ReverseL t Source # 
Instance details

Defined in Predicate.Prelude

type PP ReverseL t = t

data SortBy p q Source #

sort a list

>>> pz @(SortOn (Fst Id) Id) [(10,"abc"), (3,"def"), (4,"gg"), (10,"xyz"), (1,"z")]
Present [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
PresentT [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
>>> pz @(SortBy (OrdP (Snd Id) (Fst Id)) Id) [(10,"ab"),(4,"x"),(20,"bbb")]
Present [(20,"bbb"),(10,"ab"),(4,"x")]
PresentT [(20,"bbb"),(10,"ab"),(4,"x")]
>>> pz @(SortBy 'LT Id) [1,5,2,4,7,0]
Present [1,5,2,4,7,0]
PresentT [1,5,2,4,7,0]
>>> pz @(SortBy 'GT Id) [1,5,2,4,7,0]
Present [0,7,4,2,5,1]
PresentT [0,7,4,2,5,1]
>>> pz @(SortBy ((Fst (Fst Id) ==! Fst (Snd Id)) <> (Snd (Fst Id) ==! Snd (Snd Id))) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
Present [(4,"a"),(4,"x"),(4,"y"),(10,"ab"),(20,"bbb")]
PresentT [(4,"a"),(4,"x"),(4,"y"),(10,"ab"),(20,"bbb")]
>>> pz @(SortBy ((Fst (Fst Id) ==! Fst (Snd Id)) <> (Snd (Snd Id) ==! Snd (Fst Id))) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
Present [(4,"y"),(4,"x"),(4,"a"),(10,"ab"),(20,"bbb")]
PresentT [(4,"y"),(4,"x"),(4,"a"),(10,"ab"),(20,"bbb")]
Instances
(P p (a, a), P q x, Show a, PP q x ~ [a], PP p (a, a) ~ Ordering) => P (SortBy p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (SortBy p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SortBy p q) -> POpts -> x -> m (TT (PP (SortBy p q) x)) Source #

type PP (SortBy p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (SortBy p q :: Type) x = PP q x

type SortOn p q = SortBy (OrdA p) q Source #

type SortOnDesc p q = SortBy (Swap >> OrdA p) q Source #

type Remove p q = KeepImpl False p q Source #

type Keep p q = KeepImpl True p q Source #

overloaded list expressions

data ToListExt Source #

invokes toList

>>> pz @ToListExt (M.fromList [(1,'x'),(4,'y')])
Present [(1,'x'),(4,'y')]
PresentT [(1,'x'),(4,'y')]
>>> pz @ToListExt (T.pack "abc")
Present "abc"
PresentT "abc"
Instances
(Show l, IsList l, Show (Item l)) => P ToListExt l Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ToListExt l :: Type Source #

Methods

eval :: MonadEval m => Proxy ToListExt -> POpts -> l -> m (TT (PP ToListExt l)) Source #

type PP ToListExt l Source # 
Instance details

Defined in Predicate.Prelude

type PP ToListExt l = [Item l]

data FromListExt (t :: Type) Source #

invokes fromList

requires the OverloadedLists extension

>>> :set -XOverloadedLists
>>> pz @(FromListExt (M.Map _ _)) [(4,"x"),(5,"dd")]
Present fromList [(4,"x"),(5,"dd")]
PresentT (fromList [(4,"x"),(5,"dd")])
Instances
(Show l, IsList l, l ~ l') => P (FromListExt l' :: Type) l Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromListExt l') l :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromListExt l') -> POpts -> l -> m (TT (PP (FromListExt l') l)) Source #

type PP (FromListExt l' :: Type) l Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromListExt l' :: Type) l = l'

maybe expressions

type MkNothing (t :: Type) = MkNothing' (Hole t) Source #

data MkNothing' t Source #

Instances
P (MkNothing' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkNothing' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkNothing' t) -> POpts -> a -> m (TT (PP (MkNothing' t) a)) Source #

type PP (MkNothing' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkNothing' t :: Type) a = Maybe (PP t a)

data MkJust p Source #

Just constructor

>>> pz @(MkJust Id) 44
Present Just 44
PresentT (Just 44)
Instances
(PP p x ~ a, P p x, Show a) => P (MkJust p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkJust p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkJust p) -> POpts -> x -> m (TT (PP (MkJust p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MkJust p :: Type) x = Maybe (PP p x)

data Just p Source #

tries to extract a from Maybe a otherwise it fails

>>> pz @(Just Id) (Just "abc")
Present "abc"
PresentT "abc"
>>> pz @(Just Id) Nothing
Error Just(empty)
FailT "Just(empty)"
Instances
(Show a, PP p x ~ Maybe a, P p x) => P (Just p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Just p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Just p) -> POpts -> x -> m (TT (PP (Just p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Just p :: Type) x

data JustDef p q Source #

extract the value from a Maybe otherwise use the default value

>>> pz @(JustDef (1 % 4) Id) (Just 20.4)
Present 102 % 5
PresentT (102 % 5)
>>> pz @(JustDef (1 % 4) Id) Nothing
Present 1 % 4
PresentT (1 % 4)
>>> pz @(JustDef (MEmptyT _) Id) (Just "xy")
Present "xy"
PresentT "xy"
>>> pz @(JustDef (MEmptyT _) Id) Nothing
Present ()
PresentT ()
>>> pz @(JustDef (MEmptyT (SG.Sum _)) Id) Nothing
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
Instances
(PP p x ~ a, PP q x ~ Maybe a, P p x, P q x) => P (JustDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (JustDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (JustDef p q) -> POpts -> x -> m (TT (PP (JustDef p q) x)) Source #

type PP (JustDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (JustDef p q :: Type) x

data JustFail p q Source #

extract the value from a Maybe or fail

>>> pz @(JustFail "nope" Id) (Just 99)
Present 99
PresentT 99
>>> pz @(JustFail "nope" Id) Nothing
Error nope
FailT "nope"
>>> pz @(JustFail (PrintF "oops=%d" (Snd Id)) (Fst Id)) (Nothing, 123)
Error oops=123
FailT "oops=123"
>>> pz @(JustFail (PrintF "oops=%d" (Snd Id)) (Fst Id)) (Just 'x', 123)
Present 'x'
PresentT 'x'
Instances
(PP p x ~ String, PP q x ~ Maybe a, P p x, P q x) => P (JustFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (JustFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (JustFail p q) -> POpts -> x -> m (TT (PP (JustFail p q) x)) Source #

type PP (JustFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (JustFail p q :: Type) x

data MaybeIn p q Source #

similar to maybe

provides a Proxy to the result of 'q' but does not provide the surrounding context

>>> pz @(MaybeIn "foundnothing" (ShowP (Pred Id))) (Just 20)
Present "19"
PresentT "19"
>>> pz @(MaybeIn "found nothing" (ShowP (Pred Id))) Nothing
Present "found nothing"
PresentT "found nothing"
Instances
(P q a, Show a, Show (PP q a), PP p (Proxy (PP q a)) ~ PP q a, P p (Proxy (PP q a))) => P (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MaybeIn p q) (Maybe a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (MaybeIn p q) -> POpts -> Maybe a -> m (TT (PP (MaybeIn p q) (Maybe a))) Source #

type PP (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate.Prelude

type PP (MaybeIn p q :: Type) (Maybe a) = PP q a

data MaybeBool b p Source #

Convenient method to convert a value 'p' to a Maybe based on a predicate '\b\' if '\b\' then Just 'p' else Nothing

>>> pz @(MaybeBool (Id > 4) Id) 24
Present Just 24
PresentT (Just 24)
>>> pz @(MaybeBool (Id > 4) Id) (-5)
Present Nothing
PresentT Nothing
Instances
(Show (PP p a), P b a, P p a, PP b a ~ Bool) => P (MaybeBool b p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MaybeBool b p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MaybeBool b p) -> POpts -> a -> m (TT (PP (MaybeBool b p) a)) Source #

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

Defined in Predicate.Prelude

type PP (MaybeBool b p :: Type) a = Maybe (PP p a)

either expressions

data PartitionEithers Source #

similar to partitionEithers

>>> pz @PartitionEithers [Left 'a',Right 2,Left 'c',Right 4,Right 99]
Present ("ac",[2,4,99])
PresentT ("ac",[2,4,99])
>>> pz @PartitionEithers [Right 2,Right 4,Right 99]
Present ([],[2,4,99])
PresentT ([],[2,4,99])
>>> pz @PartitionEithers [Left 'a',Left 'c']
Present ("ac",[])
PresentT ("ac",[])
>>> pz @PartitionEithers ([] @(Either _ _))
Present ([],[])
PresentT ([],[])
Instances
(Show a, Show b) => P PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP PartitionEithers [Either a b] :: Type Source #

Methods

eval :: MonadEval m => Proxy PartitionEithers -> POpts -> [Either a b] -> m (TT (PP PartitionEithers [Either a b])) Source #

type PP PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate.Prelude

type PP PartitionEithers [Either a b] = ([a], [b])

type MkLeft (t :: Type) p = MkLeft' (Hole t) p Source #

data MkLeft' t p Source #

Left constructor

>>> pz @(MkLeft _ Id) 44
Present Left 44
PresentT (Left 44)
Instances
(Show (PP p x), P p x) => P (MkLeft' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkLeft' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkLeft' t p) -> POpts -> x -> m (TT (PP (MkLeft' t p) x)) Source #

type PP (MkLeft' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkLeft' t p :: Type) x = Either (PP p x) (PP t x)

type MkRight (t :: Type) p = MkRight' (Hole t) p Source #

data MkRight' t p Source #

Right constructor

>>> pz @(MkRight _ Id) 44
Present Right 44
PresentT (Right 44)
Instances
(Show (PP p x), P p x) => P (MkRight' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkRight' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkRight' t p) -> POpts -> x -> m (TT (PP (MkRight' t p) x)) Source #

type PP (MkRight' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkRight' t p :: Type) x = Either (PP t x) (PP p x)

type Left' p = LeftFail "expected Left" p Source #

type Right' p = RightFail "expected Right" p Source #

data LeftDef p q Source #

extract the Left value from an Either otherwise use the default value

if there is no Left value then p is passed the Right value and the whole context

>>> pz @(LeftDef (1 % 4) Id) (Left 20.4)
Present 102 % 5
PresentT (102 % 5)
>>> pz @(LeftDef (1 % 4) Id) (Right "aa")
Present 1 % 4
PresentT (1 % 4)
>>> pz @(LeftDef (PrintT "found right=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Right "xy")
Present "found right=xy fst=123"
PresentT "found right=xy fst=123"
>>> pz @(LeftDef (MEmptyT _) Id) (Right 222)
Present ()
PresentT ()
>>> pz @(LeftDef (MEmptyT (SG.Sum _)) Id) (Right 222)
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
Instances
(PP q x ~ Either a b, PP p (b, x) ~ a, P q x, P p (b, x)) => P (LeftDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LeftDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (LeftDef p q) -> POpts -> x -> m (TT (PP (LeftDef p q) x)) Source #

type PP (LeftDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (LeftDef p q :: Type) x

data LeftFail p q Source #

extract the Left value from an Either otherwise fail with an error message

if there is no Left value then p is passed the Right value and the whole context

>>> pz @(LeftFail "oops" Id) (Left 20.4)
Present 20.4
PresentT 20.4
>>> pz @(LeftFail "oops" Id) (Right "aa")
Error oops
FailT "oops"
>>> pz @(LeftFail (PrintT "found right=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Right "xy")
Error found right=xy fst=123
FailT "found right=xy fst=123"
>>> pz @(LeftFail (MEmptyT _) Id) (Right 222)
Error
FailT ""
Instances
(PP p (b, x) ~ String, PP q x ~ Either a b, P p (b, x), P q x) => P (LeftFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LeftFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (LeftFail p q) -> POpts -> x -> m (TT (PP (LeftFail p q) x)) Source #

type PP (LeftFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (LeftFail p q :: Type) x

data RightDef p q Source #

extract the Right value from an Either

if there is no Right value then p is passed the Left value and the whole context

>>> pz @(RightDef (1 % 4) Id) (Right 20.4)
Present 102 % 5
PresentT (102 % 5)
>>> pz @(RightDef (1 % 4) Id) (Left "aa")
Present 1 % 4
PresentT (1 % 4)
>>> pz @(RightDef (PrintT "found left=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Left "xy")
Present "found left=xy fst=123"
PresentT "found left=xy fst=123"
>>> pz @(RightDef (MEmptyT _) Id) (Left 222)
Present ()
PresentT ()
>>> pz @(RightDef (MEmptyT (SG.Sum _)) Id) (Left 222)
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
Instances
(PP q x ~ Either a b, PP p (a, x) ~ b, P q x, P p (a, x)) => P (RightDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (RightDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (RightDef p q) -> POpts -> x -> m (TT (PP (RightDef p q) x)) Source #

type PP (RightDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (RightDef p q :: Type) x

data RightFail p q Source #

extract the Right value from an Either otherwise fail with an error message

if there is no Right value then p is passed the Left value and the whole context

>>> pz @(RightFail "oops" Id) (Right 20.4)
Present 20.4
PresentT 20.4
>>> pz @(RightFail "oops" Id) (Left "aa")
Error oops
FailT "oops"
>>> pz @(RightFail (PrintT "found left=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Left "xy")
Error found left=xy fst=123
FailT "found left=xy fst=123"
>>> pz @(RightFail (MEmptyT _) Id) (Left 222)
Error
FailT ""
Instances
(PP p (a, x) ~ String, PP q x ~ Either a b, P p (a, x), P q x) => P (RightFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (RightFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (RightFail p q) -> POpts -> x -> m (TT (PP (RightFail p q) x)) Source #

type PP (RightFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (RightFail p q :: Type) x

data EitherBool b p q Source #

Convenient method to convert a 'p' or '\q' to a Either based on a predicate '\b\' if 'b' then Right 'p' else Left '\q\'

>>> pz @(EitherBool (Fst Id > 4) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (24,(-1,999))
Present Right 999
PresentT (Right 999)
>>> pz @(EitherBool (Fst Id > 4) (Fst (Snd Id)) (Snd (Snd Id))) (1,(-1,999))
Present Left (-1)
PresentT (Left (-1))
Instances
(Show (PP p a), P p a, Show (PP q a), P q a, P b a, PP b a ~ Bool) => P (EitherBool b p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (EitherBool b p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (EitherBool b p q) -> POpts -> a -> m (TT (PP (EitherBool b p q) a)) Source #

type PP (EitherBool b p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (EitherBool b p q :: Type) a = Either (PP p a) (PP q a)

type MkRightAlt t p = Pure (Either t) p Source #

type EitherIn p q = p ||| q Source #

semigroup / monoid expressions

data p <> q infixr 6 Source #

similar to <>

>>> pz @(Fst Id <> Snd Id) ("abc","def")
Present "abcdef"
PresentT "abcdef"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
Present "abcdefghi"
PresentT "abcdefghi"
>>> pz @("abcd" <> "ef" <> Id) "ghi"
Present "abcdefghi"
PresentT "abcdefghi"
>>> pz @(Wrap (SG.Sum _) Id <> FromInteger _ 10) 13
Present Sum {getSum = 23}
PresentT (Sum {getSum = 23})
>>> pz @(Wrap (SG.Product _) Id <> FromInteger _ 10) 13
Present Product {getProduct = 130}
PresentT (Product {getProduct = 130})
>>> pz @('(FromInteger _ 10,"def") <> Id) (SG.Sum 12, "_XYZ")
Present (Sum {getSum = 22},"def_XYZ")
PresentT (Sum {getSum = 22},"def_XYZ")
>>> pz @(Sapa' (SG.Max _)) (10,12)
Present Max {getMax = 12}
PresentT (Max {getMax = 12})
>>> pz @(Sapa' (SG.Sum _)) (10,12)
Present Sum {getSum = 22}
PresentT (Sum {getSum = 22})
Instances
(Semigroup (PP p x), PP p x ~ PP q x, P p x, Show (PP q x), P q x) => P (p <> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p <> q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <> q) -> POpts -> x -> m (TT (PP (p <> q) x)) Source #

type PP (p <> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p <> q :: Type) x = PP p x

data MConcat p Source #

similar to mconcat

>>> pz @(MConcat Id) [SG.Sum 44, SG.Sum 12, SG.Sum 3]
Present Sum {getSum = 59}
PresentT (Sum {getSum = 59})
Instances
(PP p x ~ [a], P p x, Show a, Monoid a) => P (MConcat p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MConcat p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MConcat p) -> POpts -> x -> m (TT (PP (MConcat p) x)) Source #

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

Defined in Predicate.Prelude

type PP (MConcat p :: Type) x

data STimes n p Source #

similar to stimes

>>> pz @(STimes 4 Id) (SG.Sum 3)
Present Sum {getSum = 12}
PresentT (Sum {getSum = 12})
>>> pz @(STimes 4 Id) "ab"
Present "abababab"
PresentT "abababab"
Instances
(P n a, Integral (PP n a), Semigroup (PP p a), P p a, Show (PP p a)) => P (STimes n p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (STimes n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (STimes n p) -> POpts -> a -> m (TT (PP (STimes n p) a)) Source #

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

Defined in Predicate.Prelude

type PP (STimes n p :: Type) a = PP p a

type Sapa' (t :: Type) = Wrap t (Fst Id) <> Wrap t (Snd Id) Source #

type MEmptyT (t :: Type) = MEmptyT' (Hole t) Source #

data MEmptyT' t Source #

similar to mempty

>>> pz @(MEmptyT (SG.Sum Int)) ()
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})

no Monoid for Maybe a unless a is also a monoid but can use empty!

Instances
(Show (PP t a), Monoid (PP t a)) => P (MEmptyT' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MEmptyT' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MEmptyT' t) -> POpts -> a -> m (TT (PP (MEmptyT' t) a)) Source #

type PP (MEmptyT' t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (MEmptyT' t :: Type) a = PP t a

data MEmptyT2' t Source #

lift mempty over a Functor

>>> pz @(MEmptyT2 (SG.Product Int)) [Identity (-13), Identity 4, Identity 99]
Present [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
PresentT [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
Instances
(Show (f a), Show (f (PP t (f a))), Functor f, Monoid (PP t (f a))) => P (MEmptyT2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MEmptyT2' t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (MEmptyT2' t) -> POpts -> f a -> m (TT (PP (MEmptyT2' t) (f a))) Source #

type PP (MEmptyT2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

type PP (MEmptyT2' t :: Type) (f a) = f (PP t (f a))

indexing expressions

data Ix (n :: Nat) def Source #

similar to !!

>>> pz @(Ix 4 "not found") ["abc","D","eF","","G"]
Present "G"
PresentT "G"
>>> pz @(Ix 40 "not found") ["abc","D","eF","","G"]
Present "not found"
PresentT "not found"
Instances
(P def (Proxy a), PP def (Proxy a) ~ a, KnownNat n, Show a) => P (Ix n def :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ix n def) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ix n def) -> POpts -> [a] -> m (TT (PP (Ix n def) [a])) Source #

type PP (Ix n def :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (Ix n def :: Type) [a] = a

type Ix' (n :: Nat) = Ix n (Failp "Ix index not found") Source #

data IxL p q def Source #

similar to !! leveraging Ixed

>>> import qualified Data.Map.Strict as M
>>> pz @(Id !! 2) ["abc","D","eF","","G"]
Present "eF"
PresentT "eF"
>>> pz @(Id !! 20) ["abc","D","eF","","G"]
Error (!!) index not found
FailT "(!!) index not found"
>>> pz @(Id !! "eF") (M.fromList (flip zip [0..] ["abc","D","eF","","G"]))
Present 2
PresentT 2
Instances
(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a)), P r (Proxy (IxValue (PP p a))), PP r (Proxy (IxValue (PP p a))) ~ IxValue (PP p a)) => P (IxL p q r :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

type PP (IxL p q r :: Type) a = IxValue (PP p a)

type (!!) p q = IxL p q (Failp "(!!) index not found") Source #

data Lookup p q Source #

lookup leveraging Ixed

>>> pz @(Lookup Id 2) ["abc","D","eF","","G"]
Present Just "eF"
PresentT (Just "eF")
>>> pz @(Lookup Id 20) ["abc","D","eF","","G"]
Present Nothing
PresentT Nothing
Instances
(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a))) => P (Lookup p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Lookup p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Lookup p q) -> POpts -> a -> m (TT (PP (Lookup p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Lookup p q :: Type) a = Maybe (IxValue (PP p a))

type LookupDef x y p = LookupDef' x y p I Source #

type LookupDef' x y p q = JustDef p (q >> Lookup x y) Source #

type LookupFail msg x y = LookupFail' msg x y I Source #

type LookupFail' msg x y q = JustFail msg (q >> Lookup x y) Source #

data p :+ q infixr 5 Source #

similar to cons

>>> pz @(Fst Id :+ Snd Id) (99,[1,2,3,4])
Present [99,1,2,3,4]
PresentT [99,1,2,3,4]
>>> pz @(Snd Id :+ Fst Id) ([],5)
Present [5]
PresentT [5]
>>> pz @(123 :+ EmptyList _) "somestuff"
Present [123]
PresentT [123]
Instances
(P p x, P q x, Show (PP p x), Show (PP q x), Cons (PP q x) (PP q x) (PP p x) (PP p x)) => P (p :+ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p :+ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p :+ q) -> POpts -> x -> m (TT (PP (p :+ q) x)) Source #

type PP (p :+ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p :+ q :: Type) x = PP q x

data p +: q infixl 5 Source #

similar to snoc

>>> pz @(Snd Id +: Fst Id) (99,[1,2,3,4])
Present [1,2,3,4,99]
PresentT [1,2,3,4,99]
>>> pz @(Fst Id +: Snd Id) ([],5)
Present [5]
PresentT [5]
>>> pz @(EmptyT [] Id +: 5) 5
Present [5]
PresentT [5]
Instances
(P p x, P q x, Show (PP q x), Show (PP p x), Snoc (PP p x) (PP p x) (PP q x) (PP q x)) => P (p +: q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p +: q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p +: q) -> POpts -> x -> m (TT (PP (p +: q) x)) Source #

type PP (p +: q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p +: q :: Type) x = PP p x

data Uncons Source #

uncons

>>> pz @Uncons [1,2,3,4]
Present Just (1,[2,3,4])
PresentT (Just (1,[2,3,4]))
>>> pz @Uncons []
Present Nothing
PresentT Nothing
>>> pz @Uncons (Seq.fromList "abc")
Present Just ('a',fromList "bc")
PresentT (Just ('a',fromList "bc"))
>>> pz @Uncons ("xyz" :: T.Text)
Present Just ('x',"yz")
PresentT (Just ('x',"yz"))
Instances
(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s)) => P Uncons s Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Uncons s :: Type Source #

Methods

eval :: MonadEval m => Proxy Uncons -> POpts -> s -> m (TT (PP Uncons s)) Source #

type PP Uncons s Source # 
Instance details

Defined in Predicate.Prelude

type PP Uncons s = Maybe (ConsT s, s)

data Unsnoc Source #

unsnoc

>>> pz @Unsnoc [1,2,3,4]
Present Just ([1,2,3],4)
PresentT (Just ([1,2,3],4))
>>> pz @Unsnoc []
Present Nothing
PresentT Nothing
>>> pz @Unsnoc ("xyz" :: T.Text)
Present Just ("xy",'z')
PresentT (Just ("xy",'z'))
Instances
(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s)) => P Unsnoc s Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Unsnoc s :: Type Source #

Methods

eval :: MonadEval m => Proxy Unsnoc -> POpts -> s -> m (TT (PP Unsnoc s)) Source #

type PP Unsnoc s Source # 
Instance details

Defined in Predicate.Prelude

type PP Unsnoc s = Maybe (s, ConsT s)

data Head p Source #

takes the head of a list like container

>>> pz @(Head Id) "abcd"
Present 'a'
PresentT 'a'
>>> pz @(Head Id) []
Error Head(empty)
FailT "Head(empty)"
Instances
(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Head p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Head p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Head p) -> POpts -> x -> m (TT (PP (Head p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Head p :: Type) x = ConsT (PP p x)

data Tail p Source #

takes the tail of a list like container

>>> pz @(Tail Id) "abcd"
Present "bcd"
PresentT "bcd"
>>> pz @(Tail Id) []
Error Tail(empty)
FailT "Tail(empty)"
Instances
(Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Tail p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Tail p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Tail p) -> POpts -> x -> m (TT (PP (Tail p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Tail p :: Type) x = PP p x

data Init p Source #

takes the init of a list like container

>>> pz @(Init Id) "abcd"
Present "abc"
PresentT "abc"
>>> pz @(Init Id) (T.pack "abcd")
Present "abc"
PresentT "abc"
>>> pz @(Init Id) []
Error Init(empty)
FailT "Init(empty)"
Instances
(Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Init p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Init p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Init p) -> POpts -> x -> m (TT (PP (Init p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Init p :: Type) x = PP p x

data Last p Source #

takes the last of a list like container

>>> pz @(Last Id) "abcd"
Present 'd'
PresentT 'd'
>>> pz @(Last Id) []
Error Last(empty)
FailT "Last(empty)"
Instances
(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Last p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Last p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Last p) -> POpts -> x -> m (TT (PP (Last p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Last p :: Type) x = ConsT (PP p x)

type HeadDef p q = JustDef p (q >> (Uncons >> FMapFst)) Source #

takes the head or default of a list-like object

see ConsT for other supported types eg Seq

>>> pz @(HeadDef 444 Id) []
Present 444
PresentT 444
>>> pz @(HeadDef 444 Id) [1..5]
Present 1
PresentT 1
>>> pz @(HeadDef 444 Id) [1..5]
Present 1
PresentT 1
>>> pz @(HeadDef (Char1 "w") Id) (Seq.fromList "abcdef")
Present 'a'
PresentT 'a'
>>> pz @(HeadDef (Char1 "w") Id) Seq.empty
Present 'w'
PresentT 'w'
>>> pz @(HeadDef (MEmptyT _) Id) ([] @(SG.Sum _))
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
>>> pz @(HeadDef (MEmptyT _) '[ "abc","def","asdfadf" ]) ()
Present "abc"
PresentT "abc"
>>> pz @(HeadDef (MEmptyT _) (Snd Id)) (123,[ "abc","def","asdfadf" ])
Present "abc"
PresentT "abc"
>>> pz @(HeadDef (MEmptyT _) (Snd Id)) (123,[])
Present ()
PresentT ()

type HeadFail msg q = JustFail msg (q >> (Uncons >> FMapFst)) Source #

takes the head of a list or fail

see ConsT for other supported types eg Seq

>>> pz @(HeadFail "dude" Id) [ "abc","def","asdfadf" ]
Present "abc"
PresentT "abc"
>>> pz @(HeadFail "empty list" Id) []
Error empty list
FailT "empty list"

type TailDef p q = JustDef p (q >> (Uncons >> FMapSnd)) Source #

type TailFail msg q = JustFail msg (q >> (Uncons >> FMapSnd)) Source #

type LastDef p q = JustDef p (q >> (Unsnoc >> FMapSnd)) Source #

type LastFail msg q = JustFail msg (q >> (Unsnoc >> FMapSnd)) Source #

type InitDef p q = JustDef p (q >> (Unsnoc >> FMapFst)) Source #

type InitFail msg q = JustFail msg (q >> (Unsnoc >> FMapFst)) Source #

these expressions

data PartitionThese Source #

similar to partitionThese. returns a 3-tuple with the results so use Fst Snd Thd to extract

>>> pz @PartitionThese [This 'a', That 2, This 'c', These 'z' 1, That 4, These 'a' 2, That 99]
Present ("ac",[2,4,99],[('z',1),('a',2)])
PresentT ("ac",[2,4,99],[('z',1),('a',2)])
Instances
(Show a, Show b) => P PartitionThese [These a b] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP PartitionThese [These a b] :: Type Source #

Methods

eval :: MonadEval m => Proxy PartitionThese -> POpts -> [These a b] -> m (TT (PP PartitionThese [These a b])) Source #

type PP PartitionThese [These a b] Source # 
Instance details

Defined in Predicate.Prelude

type PP PartitionThese [These a b] = ([a], [b], [(a, b)])

type This' p = ThisFail "expected This" p Source #

type That' p = ThatFail "expected That" p Source #

type These' p = TheseFail "expected These" p Source #

type IsThis p = IsTh (This ()) p Source #

type IsThat p = IsTh (That ()) p Source #

type IsThese p = IsTh (These () ()) p Source #

type MkThis (t :: Type) p = MkThis' (Hole t) p Source #

data MkThis' t p Source #

This constructor

>>> pz @(MkThis _ Id) 44
Present This 44
PresentT (This 44)
>>> pz @(Proxy Int >> MkThis' Unproxy 10) []
Present This 10
PresentT (This 10)
Instances
(Show (PP p x), P p x) => P (MkThis' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkThis' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThis' t p) -> POpts -> x -> m (TT (PP (MkThis' t p) x)) Source #

type PP (MkThis' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkThis' t p :: Type) x = These (PP p x) (PP t x)

type MkThat (t :: Type) p = MkThat' (Hole t) p Source #

data MkThat' t p Source #

That constructor

>>> pz @(MkThat _ Id) 44
Present That 44
PresentT (That 44)
Instances
(Show (PP p x), P p x) => P (MkThat' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkThat' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThat' t p) -> POpts -> x -> m (TT (PP (MkThat' t p) x)) Source #

type PP (MkThat' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (MkThat' t p :: Type) x = These (PP t x) (PP p x)

data MkThese p q Source #

These constructor

>>> pz @(MkThese (Fst Id) (Snd Id)) (44,'x')
Present These 44 'x'
PresentT (These 44 'x')
Instances
(P p a, P q a, Show (PP p a), Show (PP q a)) => P (MkThese p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkThese p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThese p q) -> POpts -> a -> m (TT (PP (MkThese p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (MkThese p q :: Type) a = These (PP p a) (PP q a)

data ThisDef p q Source #

extract the This value from an These otherwise use the default value

if there is no This value then p is passed the whole context only

>>> pz @(ThisDef (1 % 4) Id) (This 20.4)
Present 102 % 5
PresentT (102 % 5)
>>> pz @(ThisDef (1 % 4) Id) (That "aa")
Present 1 % 4
PresentT (1 % 4)
>>> pz @(ThisDef (1 % 4) Id) (These 2.3 "aa")
Present 1 % 4
PresentT (1 % 4)
>>> pz @(ThisDef (PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id)) (Snd Id)) (123,That "xy")
Present "found That \"xy\" fst=123"
PresentT "found That \"xy\" fst=123"
>>> pz @(ThisDef (MEmptyT _) Id) (That 222)
Present ()
PresentT ()
>>> pz @(ThisDef (MEmptyT (SG.Sum _)) Id) (These 222 'x')
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
Instances
(PP q x ~ These a b, PP p x ~ a, P q x, P p x) => P (ThisDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ThisDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ThisDef p q) -> POpts -> x -> m (TT (PP (ThisDef p q) x)) Source #

type PP (ThisDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ThisDef p q :: Type) x

data ThisFail p q Source #

extract the This value from a These otherwise fail with an error message

if there is no This value then p is passed the whole context only

>>> pz @(ThisFail "oops" Id) (This 20.4)
Present 20.4
PresentT 20.4
>>> pz @(ThisFail "oops" Id) (That "aa")
Error oops
FailT "oops"
>>> pz @(ThisFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,That "xy")
Error found That "xy" fst=123
FailT "found That \"xy\" fst=123"
>>> pz @(ThisFail (MEmptyT _) Id) (That 222)
Error
FailT ""
Instances
(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (ThisFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ThisFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ThisFail p q) -> POpts -> x -> m (TT (PP (ThisFail p q) x)) Source #

type PP (ThisFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ThisFail p q :: Type) x

data ThatDef p q Source #

extract the That value from an These otherwise use the default value

if there is no That value then p is passed the whole context only

>>> pz @(ThatDef (1 % 4) Id) (That 20.4)
Present 102 % 5
PresentT (102 % 5)
>>> pz @(ThatDef (1 % 4) Id) (This "aa")
Present 1 % 4
PresentT (1 % 4)
>>> pz @(ThatDef (1 % 4) Id) (These "aa" 2.3)
Present 1 % 4
PresentT (1 % 4)
>>> pz @(ThatDef (PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id)) (Snd Id)) (123,This "xy")
Present "found This \"xy\" fst=123"
PresentT "found This \"xy\" fst=123"
>>> pz @(ThatDef (MEmptyT _) Id) (This 222)
Present ()
PresentT ()
>>> pz @(ThatDef (MEmptyT (SG.Sum _)) Id) (These 'x' 1120)
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})
Instances
(PP q x ~ These a b, PP p x ~ b, P q x, P p x) => P (ThatDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ThatDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ThatDef p q) -> POpts -> x -> m (TT (PP (ThatDef p q) x)) Source #

type PP (ThatDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ThatDef p q :: Type) x

data ThatFail p q Source #

extract the That value from a These otherwise fail with an error message

if there is no That value then p is passed the whole context only

>>> pz @(ThatFail "oops" Id) (That 20.4)
Present 20.4
PresentT 20.4
>>> pz @(ThatFail "oops" Id) (This "aa")
Error oops
FailT "oops"
>>> pz @(ThatFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,This "xy")
Error found This "xy" fst=123
FailT "found This \"xy\" fst=123"
>>> pz @(ThatFail (MEmptyT _) Id) (This 222)
Error
FailT ""
Instances
(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (ThatFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ThatFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ThatFail p q) -> POpts -> x -> m (TT (PP (ThatFail p q) x)) Source #

type PP (ThatFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (ThatFail p q :: Type) x

data TheseDef p q Source #

extract the These value from an These otherwise use the default value

if there is no These value then p is passed the whole context only

>>> pz @(TheseDef '(1 % 4,"zz") Id) (These 20.4 "x")
Present (102 % 5,"x")
PresentT (102 % 5,"x")
>>> pz @(TheseDef '(1 % 4,"zz") Id) (This 20.4)
Present (1 % 4,"zz")
PresentT (1 % 4,"zz")
>>> pz @(TheseDef '(1 % 4,"zz") Id) (That "x")
Present (1 % 4,"zz")
PresentT (1 % 4,"zz")
>>> pz @(TheseDef '(PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id),999) (Snd Id)) (123,This "xy")
Present ("found This \"xy\" fst=123",999)
PresentT ("found This \"xy\" fst=123",999)
>>> pz @(TheseDef (MEmptyT (SG.Sum _, String)) Id) (This 222)
Present (Sum {getSum = 0},"")
PresentT (Sum {getSum = 0},"")
>>> pz @(TheseDef (MEmptyT _) Id) (These (222 :: SG.Sum Int) "aa")
Present (Sum {getSum = 222},"aa")
PresentT (Sum {getSum = 222},"aa")
Instances
(PP q x ~ These a b, PP p x ~ (a, b), P q x, P p x) => P (TheseDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (TheseDef p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseDef p q) -> POpts -> x -> m (TT (PP (TheseDef p q) x)) Source #

type PP (TheseDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (TheseDef p q :: Type) x

data TheseFail p q Source #

extract the These value from a These otherwise fail with an error message

if there is no These value then p is passed the whole context only

>>> pz @(TheseFail "oops" Id) (These "abc" 20.4)
Present ("abc",20.4)
PresentT ("abc",20.4)
>>> pz @(TheseFail "oops" Id) (That "aa")
Error oops
FailT "oops"
>>> pz @(TheseFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,That "xy")
Error found That "xy" fst=123
FailT "found That \"xy\" fst=123"
>>> pz @(TheseFail (MEmptyT _) Id) (That 222)
Error
FailT ""
Instances
(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (TheseFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (TheseFail p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseFail p q) -> POpts -> x -> m (TT (PP (TheseFail p q) x)) Source #

type PP (TheseFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (TheseFail p q :: Type) x

data TheseIn p q r Source #

similar to these

>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (This 13)
Present 13
PresentT 13
>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (That "this is a long string")
Present 21
PresentT 21
>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (These 20 "somedata")
Present 28
PresentT 28
>>> pz @(TheseIn (MkLeftAlt _ Id) (MkRightAlt _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (That "this is a long string")
Present Right "this is a long string"
PresentT (Right "this is a long string")
>>> pz @(TheseIn (MkLeftAlt _ Id) (MkRightAlt _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 1 "this is a long string")
Present Right "this is a long string"
PresentT (Right "this is a long string")
>>> pz @(TheseIn (MkLeftAlt _ Id) (MkRightAlt _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 100 "this is a long string")
Present Left 100
PresentT (Left 100)
Instances
(Show a, Show b, Show (PP p a), P p a, P q b, P r (a, b), PP p a ~ PP q b, PP p a ~ PP r (a, b), PP q b ~ PP r (a, b)) => P (TheseIn p q r :: Type) (These a b) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (TheseIn p q r) (These a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseIn p q r) -> POpts -> These a b -> m (TT (PP (TheseIn p q r) (These a b))) Source #

type PP (TheseIn p q r :: Type) (These a b) Source # 
Instance details

Defined in Predicate.Prelude

type PP (TheseIn p q r :: Type) (These a b) = PP p a

type TheseId p q = TheseIn '(I, p) '(q, I) I Source #

data TheseX p q r s Source #

similar to mergeTheseWith but additionally provides 'p', '\q' and 'r' the original input as the first element in the tuple

>>> pz @(TheseX ((Fst (Fst Id) + Snd Id) >> ShowP Id) (ShowP Id) (Snd (Snd Id)) (Snd Id)) (9,This 123)
Present "132"
PresentT "132"
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (This 123)
Present (123,"fromthis")
PresentT (123,"fromthis")
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (That "fromthat")
Present (-99,"fromthat")
PresentT (-99,"fromthat")
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (These 123 "fromthese")
Present (123,"fromthese")
PresentT (123,"fromthese")
Instances
(P s x, P p (x, a), P q (x, b), P r (x, (a, b)), PP s x ~ These a b, PP p (x, a) ~ c, PP q (x, b) ~ c, PP r (x, (a, b)) ~ c) => P (TheseX p q r s :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (TheseX p q r s) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseX p q r s) -> POpts -> x -> m (TT (PP (TheseX p q r s) x)) Source #

type PP (TheseX p q r s :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (TheseX p q r s :: Type) x

fold / unfold expressions

data Scanl p q r Source #

similar to scanl

>>> pz @(Scanl (Snd Id :+ Fst Id) (Fst Id) (Snd Id)) ([99],[1..5])
Present [[99],[1,99],[2,1,99],[3,2,1,99],[4,3,2,1,99],[5,4,3,2,1,99]]
PresentT [[99],[1,99],[2,1,99],[3,2,1,99],[4,3,2,1,99],[5,4,3,2,1,99]]
>>> pz @(ScanN 4 Id (Succ Id)) 'c'
Present "cdefg"
PresentT "cdefg"
>>> pz @(FoldN 4 Id (Succ Id)) 'c'
Present 'g'
PresentT 'g'
Instances
(PP p (b, a) ~ b, PP q x ~ b, PP r x ~ [a], P p (b, a), P q x, P r x, Show b, Show a) => P (Scanl p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Scanl p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Scanl p q r) -> POpts -> x -> m (TT (PP (Scanl p q r) x)) Source #

type PP (Scanl p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Scanl p q r :: Type) x = [PP q x]

type ScanN n p q = Scanl (Fst Id >> q) p (EnumFromTo 1 n) Source #

type ScanNA q = ScanN (Fst Id) (Snd Id) q Source #

type FoldN n p q = Last (ScanN n p q) Source #

type Foldl p q r = Last (Scanl p q r) Source #

data Unfoldr p q Source #

similar to unfoldr

>>> pz @(Unfoldr (MaybeBool (Not Null) (SplitAt 2 Id)) Id) [1..5]
Present [[1,2],[3,4],[5]]
PresentT [[1,2],[3,4],[5]]
>>> pz @(IterateN 4 (Succ Id)) 4
Present [4,5,6,7]
PresentT [4,5,6,7]
Instances
(PP q a ~ s, PP p s ~ Maybe (b, s), P q a, P p s, Show s, Show b) => P (Unfoldr p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Unfoldr p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Unfoldr p q) -> POpts -> a -> m (TT (PP (Unfoldr p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Unfoldr p q :: Type) a

type IterateN n f = Unfoldr (MaybeBool (Fst Id > 0) '(Snd Id, Pred Id *** f)) '(n, Id) Source #

type IterateWhile p f = Unfoldr (MaybeBool p '(Id, f)) Id Source #

type IterateNWhile n p f = '(n, Id) >> (IterateWhile ((Fst Id > 0) && (Snd Id >> p)) (Pred Id *** f) >> Map (Snd Id) Id) Source #

type IterateNUntil n p f = IterateNWhile n (Not p) f Source #

failure expressions

data Fail t prt Source #

Fails the computation with a message

>>> pz @(Failt Int (PrintF "value=%03d" Id)) 99
Error value=099
FailT "value=099"
>>> pz @(FailS (PrintT "value=%03d string=%s" Id)) (99,"somedata")
Error value=099 string=somedata
FailT "value=099 string=somedata"
Instances
(P prt a, PP prt a ~ String) => P (Fail t prt :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Fail t prt) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Fail t prt) -> POpts -> a -> m (TT (PP (Fail t prt) a)) Source #

type PP (Fail t prt :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Fail t prt :: Type) a = PP t a

type Failt (t :: Type) prt = Fail (Hole t) prt Source #

type FailS s = Fail I s Source #

data Catch p q Source #

catch a failure

>>> pz @(Catch (Succ Id) (Fst Id >> Second (ShowP Id) >> PrintT "%s %s" Id >> 'LT)) GT
Present LT
PresentT LT
>>> pz @(Catch' (Succ Id) (Second (ShowP Id) >> PrintT "%s %s" Id)) GT
Error Succ IO e=Prelude.Enum.Ordering.succ: bad argument GT
FailT "Succ IO e=Prelude.Enum.Ordering.succ: bad argument GT"
>>> pz @(Catch' (Succ Id) (Second (ShowP Id) >> PrintT "%s %s" Id)) LT
Present EQ
PresentT EQ

more flexible: takes a (String,x) and a proxy so we can still call 'False 'True now takes the FailT string and x so you can print more detail if you want need the proxy so we can fail without having to explicitly specify a type

Instances
(P p x, P q ((String, x), Proxy (PP p x)), PP p x ~ PP q ((String, x), Proxy (PP p x))) => P (Catch p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Catch p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Catch p q) -> POpts -> x -> m (TT (PP (Catch p q) x)) Source #

type PP (Catch p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Catch p q :: Type) x = PP p x

type Catch' p s = Catch p (FailCatch s) Source #

zip expressions

data ZipThese p q Source #

similar to align thats pads with This or That if one list is shorter than the other

the key is that all information about both lists are preserved

>>> pz @(ZipThese (Fst Id) (Snd Id)) ("aBc", [1..5])
Present [These 'a' 1,These 'B' 2,These 'c' 3,That 4,That 5]
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,That 4,That 5]
>>> pz @(ZipThese (Fst Id) (Snd Id)) ("aBcDeF", [1..3])
Present [These 'a' 1,These 'B' 2,These 'c' 3,This 'D',This 'e',This 'F']
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,This 'D',This 'e',This 'F']
>>> pz @(ZipThese Id Reverse) "aBcDeF"
Present [These 'a' 'F',These 'B' 'e',These 'c' 'D',These 'D' 'c',These 'e' 'B',These 'F' 'a']
PresentT [These 'a' 'F',These 'B' 'e',These 'c' 'D',These 'D' 'c',These 'e' 'B',These 'F' 'a']
>>> pz @(ZipThese Id '[]) "aBcDeF"
Present [This 'a',This 'B',This 'c',This 'D',This 'e',This 'F']
PresentT [This 'a',This 'B',This 'c',This 'D',This 'e',This 'F']
>>> pz @(ZipThese '[] Id) "aBcDeF"
Present [That 'a',That 'B',That 'c',That 'D',That 'e',That 'F']
PresentT [That 'a',That 'B',That 'c',That 'D',That 'e',That 'F']
Instances
(PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipThese p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ZipThese p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ZipThese p q) -> POpts -> a -> m (TT (PP (ZipThese p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (ZipThese p q :: Type) a

data ZipL l p q Source #

zip two lists padding the left hand side if needed

>>> pl @(ZipL 99 '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (ZipL [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(ZipL 99 '[1,2] "abc") ()
Present [(1,'a'),(2,'b'),(99,'c')] (ZipL [(1,'a'),(2,'b'),(99,'c')] | p=[1,2] | q="abc")
PresentT [(1,'a'),(2,'b'),(99,'c')]
>>> pl @(ZipL 99 '[1] "abc") ()
Present [(1,'a'),(99,'b'),(99,'c')] (ZipL [(1,'a'),(99,'b'),(99,'c')] | p=[1] | q="abc")
PresentT [(1,'a'),(99,'b'),(99,'c')]
>>> pl @(ZipL 99 '[1,2,3] "ab") ()
Error ZipL(3,2) rhs would be truncated
FailT "ZipL(3,2) rhs would be truncated"
Instances
(PP l a ~ x, P l a, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipL l p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ZipL l p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ZipL l p q) -> POpts -> a -> m (TT (PP (ZipL l p q) a)) Source #

type PP (ZipL l p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (ZipL l p q :: Type) a

data ZipR r p q Source #

zip two lists padding the right hand side if needed

>>> pl @(ZipR (Char1 "Z") '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (ZipR [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(ZipR (Char1 "Z") '[1,2,3] "ab") ()
Present [(1,'a'),(2,'b'),(3,'Z')] (ZipR [(1,'a'),(2,'b'),(3,'Z')] | p=[1,2,3] | q="ab")
PresentT [(1,'a'),(2,'b'),(3,'Z')]
>>> pl @(ZipR (Char1 "Z") '[1,2,3] "a") ()
Present [(1,'a'),(2,'Z'),(3,'Z')] (ZipR [(1,'a'),(2,'Z'),(3,'Z')] | p=[1,2,3] | q="a")
PresentT [(1,'a'),(2,'Z'),(3,'Z')]
>>> pl @(ZipR (Char1 "Z") '[1,2] "abc") ()
Error ZipR(2,3) rhs would be truncated
FailT "ZipR(2,3) rhs would be truncated"
Instances
(PP r a ~ y, P r a, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipR r p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

type PP (ZipR r p q :: Type) a

data Zip p q Source #

zip two lists with the same length

>>> pl @(Zip '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (Zip [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(Zip '[1,2,3] "ab") ()
Error Zip(3,2) length mismatch
FailT "Zip(3,2) length mismatch"
>>> pl @(Zip '[1,2] "abc") ()
Error Zip(2,3) length mismatch
FailT "Zip(2,3) length mismatch"
Instances
(PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (Zip p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Zip p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Zip p q) -> POpts -> a -> m (TT (PP (Zip p q) a)) Source #

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

Defined in Predicate.Prelude

type PP (Zip p q :: Type) a

type Unzip = '(Map (Fst Id) Id, Map (Snd Id) Id) Source #

unzip equivalent

>>> pz @Unzip (zip [1..5] "abcd")
Present ([1,2,3,4],"abcd")
PresentT ([1,2,3,4],"abcd")

type Unzip3 = '(Map (Fst Id) Id, Map (Snd Id) Id, Map (Thd Id) Id) Source #

unzip3 equivalent

>>> pz @Unzip3 (zip3 [1..5] "abcd" (cycle [True,False]))
Present ([1,2,3,4],"abcd",[True,False,True,False])
PresentT ([1,2,3,4],"abcd",[True,False,True,False])

conditional expressions

data If p q r Source #

if p then run q else run r

>>> pz @(If (Gt 4) "greater than 4" "less than or equal to 4" ) 10
Present "greater than 4"
PresentT "greater than 4"
>>> pz @(If (Gt 4) "greater than 4" "less than or equal to 4") 0
Present "less than or equal to 4"
PresentT "less than or equal to 4"
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.Prelude

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.Prelude

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

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

Instances
(FailUnlessT (LenT ps == LenT qs) (((Text "lengths are not the same " :<>: ShowType (LenT ps)) :<>: Text " vs ") :<>: ShowType (LenT qs)), P (CaseImpl (LenT ps) e ps qs r) x) => P (Case e ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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.Prelude

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

type Case' (ps :: [k]) (qs :: [k1]) (r :: k2) = Case (Snd Id >> Failp "Case:no match") ps qs r Source #

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

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

Instances
(GetLen ps, P (GuardsImpl (LenT ps) ps) [a]) => P (Guards ps :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Guards ps) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (Guards ps) -> POpts -> [a] -> m (TT (PP (Guards ps) [a])) Source #

type PP (Guards ps :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (Guards ps :: Type) [a]

type GuardsQuick (prt :: k) (os :: [k1]) = Guards (ToGuardsT prt os) Source #

data Guard prt p Source #

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

>>> pz @(Guard "expected > 3" (Gt 3)) 17
Present 17
PresentT 17
>>> pz @(Guard "expected > 3" (Gt 3)) 1
Error expected > 3
FailT "expected > 3"
>>> pz @(Guard (PrintF "%d not > 3" Id) (Gt 3)) (-99)
Error -99 not > 3
FailT "-99 not > 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.Prelude

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.Prelude

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

type ExitWhen prt p = Guard prt (Not p) Source #

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 using ol and a boolean predicate unless you require failure on error

>>> pz @(GuardSimple (Luhn Id)) [1..4]
Error (Luhn map=[4,6,2,2] sum=14 ret=4 | [1,2,3,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]
Present [1,2,3,0]
PresentT [1,2,3,0]
>>> pz @(GuardSimple (Len > 30)) [1,2,3,0]
Error (4 > 30)
FailT "(4 > 30)"
Instances
(Show a, P p a, PP p a ~ Bool) => P (GuardSimple p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

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.Prelude

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)) [121,33,7,256]
Error id=4 must be between 0 and 255, found 256
FailT "id=4 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)) [121,33,7,44]
Present [121,33,7,44]
PresentT [121,33,7,44]
Instances
(GetLen (ToGuardsT prt (RepeatT n p)), P (GuardsImpl (LenT (ToGuardsT prt (RepeatT n p))) (ToGuardsT prt (RepeatT n p))) [a]) => P (GuardsN prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (GuardsN prt n p) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsN prt n p) -> POpts -> [a] -> m (TT (PP (GuardsN prt n p) [a])) Source #

type PP (GuardsN prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (GuardsN prt n p :: Type) [a]

type GuardsDetail (prt :: Symbol) (os :: [(k0, k1)]) = GuardsImplXX (ToGuardsDetailT prt os) Source #

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

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

pulls the top message from the tree if a predicate is false

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

Defined in Predicate.Prelude

Associated Types

type PP (Bools ps) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (Bools ps) -> POpts -> [a] -> m (TT (PP (Bools ps) [a])) Source #

type PP (Bools ps :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (Bools ps :: Type) [a] = Bool

type BoolsQuick (prt :: k) (ps :: [k1]) = Bools (ToGuardsT prt ps) Source #

data BoolsN prt (n :: Nat) p 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)) [121,33,7,256]
False (GuardBool(3) [id=3 must be between 0 and 255, found 256] (256 <= 255))
FalseT
>>> pz @(GuardsN (PrintT "id=%d must be between 0 and 255, found %d" Id) 4 (Between 0 255)) [121,33,7,44]
Present [121,33,7,44]
PresentT [121,33,7,44]
Instances
(GetLen (ToGuardsT prt (RepeatT n p)), PP (BoolsImpl (LenT (ToGuardsT prt (RepeatT n p))) (ToGuardsT prt (RepeatT n p))) [a] ~ Bool, P (BoolsImpl (LenT (ToGuardsT prt (RepeatT n p))) (ToGuardsT prt (RepeatT n p))) [a]) => P (BoolsN prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (BoolsN prt n p) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (BoolsN prt n p) -> POpts -> [a] -> m (TT (PP (BoolsN prt n p) [a])) Source #

type PP (BoolsN prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (BoolsN prt n p :: Type) [a]

IO expressions

data ReadFile p Source #

similar to readFile

>>> pz @(ReadFile ".ghci" >> 'Just Id >> Len > 0) ()
True
TrueT
>>> pz @(FileExists "xyzzy") ()
False
FalseT
Instances
(PP p x ~ String, P p x) => P (ReadFile p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadFile p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadFile p) -> POpts -> x -> m (TT (PP (ReadFile p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ReadFile p :: Type) x = Maybe String

data ReadDir p Source #

does the directory exists

>>> pz @(DirExists ".") ()
True
TrueT
Instances
(PP p x ~ String, P p x) => P (ReadDir p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadDir p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadDir p) -> POpts -> x -> m (TT (PP (ReadDir p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ReadDir p :: Type) x = Maybe [FilePath]

data ReadEnv p Source #

does the directory exists

>>> pz @(ReadEnv "PATH" >> 'Just Id >> 'True) ()
True
TrueT
Instances
(PP p x ~ String, P p x) => P (ReadEnv p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ReadEnv p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadEnv p) -> POpts -> x -> m (TT (PP (ReadEnv p) x)) Source #

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

Defined in Predicate.Prelude

type PP (ReadEnv p :: Type) x = Maybe String

data ReadEnvAll Source #

Instances
P ReadEnvAll a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ReadEnvAll a :: Type Source #

Methods

eval :: MonadEval m => Proxy ReadEnvAll -> POpts -> a -> m (TT (PP ReadEnvAll a)) Source #

type PP ReadEnvAll a Source # 
Instance details

Defined in Predicate.Prelude

type PP ReadEnvAll a = [(String, String)]

data TimeUtc Source #

Instances
P TimeUtc a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP TimeUtc a :: Type Source #

Methods

eval :: MonadEval m => Proxy TimeUtc -> POpts -> a -> m (TT (PP TimeUtc a)) Source #

type PP TimeUtc a Source # 
Instance details

Defined in Predicate.Prelude

type PP TimeUtc a = UTCTime

data TimeZt Source #

Instances
P TimeZt a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP TimeZt a :: Type Source #

Methods

eval :: MonadEval m => Proxy TimeZt -> POpts -> a -> m (TT (PP TimeZt a)) Source #

type PP TimeZt a Source # 
Instance details

Defined in Predicate.Prelude

type AppendFile (s :: Symbol) p = WriteFileImpl (FOther s WFAppend) p Source #

type WriteFile (s :: Symbol) p = WriteFileImpl (FOther s WFWrite) p Source #

type WriteFile' (s :: Symbol) p = WriteFileImpl (FOther s WFWriteForce) p Source #

type Stdout p = WriteFileImpl FStdout p Source #

type Stderr p = WriteFileImpl FStderr p Source #

data Stdin Source #

Instances
P Stdin a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Stdin a :: Type Source #

Methods

eval :: MonadEval m => Proxy Stdin -> POpts -> a -> m (TT (PP Stdin a)) Source #

type PP Stdin a Source # 
Instance details

Defined in Predicate.Prelude

type PP Stdin a = String

string expressions

data ToLower Source #

converts a string IsText value to lower case

>>> pz @ToLower "HeLlO wOrld!"
Present "hello world!"
PresentT "hello world!"
Instances
(Show a, IsText a) => P ToLower a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ToLower a :: Type Source #

Methods

eval :: MonadEval m => Proxy ToLower -> POpts -> a -> m (TT (PP ToLower a)) Source #

type PP ToLower a Source # 
Instance details

Defined in Predicate.Prelude

type PP ToLower a = a

data ToUpper Source #

converts a string IsText value to upper case

>>> pz @ToUpper "HeLlO wOrld!"
Present "HELLO WORLD!"
PresentT "HELLO WORLD!"
Instances
(Show a, IsText a) => P ToUpper a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP ToUpper a :: Type Source #

Methods

eval :: MonadEval m => Proxy ToUpper -> POpts -> a -> m (TT (PP ToUpper a)) Source #

type PP ToUpper a Source # 
Instance details

Defined in Predicate.Prelude

type PP ToUpper a = a

type Trim p = Trim' True True p Source #

type TrimStart p = Trim' True False p Source #

type TrimEnd p = Trim' False True p Source #

data StripLR (right :: Bool) p q Source #

similar to stripLeft stripRight

>>> pz @(StripLeft "xyz" Id) ("xyzHello" :: String)
Present Just "Hello"
PresentT (Just "Hello")
>>> pz @(StripLeft "xyz" Id) (T.pack "xyzHello")
Present Just "Hello"
PresentT (Just "Hello")
>>> pz @(StripLeft "xyz" Id) "xywHello"
Present Nothing
PresentT Nothing
>>> pz @(StripRight "xyz" Id) "Hello xyz"
Present Just "Hello "
PresentT (Just "Hello ")
>>> pz @(StripRight "xyz" Id) "xyzHelloxyw"
Present Nothing
PresentT Nothing
>>> pz @(StripRight "xyz" Id) ""
Present Nothing
PresentT Nothing
>>> pz @(StripRight "xyz" "xyz") ()
Present Just ""
PresentT (Just "")
Instances
(GetBool r, PP p x ~ String, P p x, IsText (PP q x), P q x) => P (StripLR r p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (StripLR r p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (StripLR r p q) -> POpts -> x -> m (TT (PP (StripLR r p q) x)) Source #

type PP (StripLR r p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (StripLR r p q :: Type) x = Maybe (PP q x)

type StripRight p q = StripLR True p q Source #

type StripLeft p q = StripLR False p q Source #

type IsPrefix p q = IsFixImpl LT False p q Source #

type IsInfix p q = IsFixImpl EQ False p q Source #

type IsSuffix p q = IsFixImpl GT False p q Source #

type IsPrefixI p q = IsFixImpl LT True p q Source #

type IsInfixI p q = IsFixImpl EQ True p q Source #

type IsSuffixI p q = IsFixImpl GT True p q Source #

type FromStringP (t :: Type) p = FromStringP' (Hole t) p Source #

data FromStringP' t s Source #

fromString function where you need to provide the type 't' of the result

>>> pz @(FromStringP (Identity _) Id) "abc"
Present Identity "abc"
PresentT (Identity "abc")
>>> pz @(FromStringP (Seq.Seq _) Id) "abc"
Present fromList "abc"
PresentT (fromList "abc")
Instances
(P s a, PP s a ~ String, Show (PP t a), IsString (PP t a)) => P (FromStringP' t s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FromStringP' t s) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromStringP' t s) -> POpts -> a -> m (TT (PP (FromStringP' t s) a)) Source #

type PP (FromStringP' t s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (FromStringP' t s :: Type) a = PP t a

print expressions

data PrintF s p Source #

uses PrintF to format output

>>> pz @(PrintF "value=%03d" Id) 12
Present "value=012"
PresentT "value=012"
>>> pz @(PrintF "%s" (Fst Id)) ("abc",'x')
Present "abc"
PresentT "abc"
>>> pz @(PrintF "%d" (Fst Id)) ("abc",'x')
Error PrintF (IO e=printf: bad formatting char 'd')
FailT "PrintF (IO e=printf: bad formatting char 'd')"
Instances
(PrintfArg (PP p x), Show (PP p x), PP s x ~ String, P s x, P p x) => P (PrintF s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PrintF s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (PrintF s p) -> POpts -> x -> m (TT (PP (PrintF s p) x)) Source #

type PP (PrintF s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (PrintF s p :: Type) x = String

data PrintL (n :: Nat) s p Source #

print for lists -- if you can use PrintT

>>> pl @(PrintL 4 "%s %s %s %s" '[W "xyz", ShowP (Fst Id), ShowP (Snd Id), Thd Id]) (123,'x',"ab")
Present "xyz 123 'x' ab" (PrintL(4) [xyz 123 'x' ab] | s=%s %s %s %s)
PresentT "xyz 123 'x' ab"
>>> pl @(PrintL 3 "first=%d second=%d third=%d" Id) [10,11,12]
Present "first=10 second=11 third=12" (PrintL(3) [first=10 second=11 third=12] | s=first=%d second=%d third=%d)
PresentT "first=10 second=11 third=12"
>>> pl @(PrintL 2 "first=%d second=%d third=%d" Id) [10,11,12]
Error PrintL(2) arg count=3
FailT "PrintL(2) arg count=3"
>>> pl @(PrintL 4 "first=%d second=%d third=%d" Id) [10,11,12]
Error PrintL(4) arg count=3
FailT "PrintL(4) arg count=3"
Instances
(KnownNat n, PrintC bs, (b, bs) ~ InductListP n a, InductListC n a, PrintfArg b, PP s x ~ String, PP p x ~ [a], P s x, P p x) => P (PrintL n s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PrintL n s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (PrintL n s p) -> POpts -> x -> m (TT (PP (PrintL n s p) x)) Source #

type PP (PrintL n s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (PrintL n s p :: Type) x = String

data PrintT s p Source #

print for flat n-tuples

>>> pl @(PrintT "%d %s %s %s" '(Fst Id, Snd Id, Snd Id,Snd Id)) (10,"Asdf")
Present "10 Asdf Asdf Asdf" (PrintT [10 Asdf Asdf Asdf] | s=%d %s %s %s)
PresentT "10 Asdf Asdf Asdf"
>>> pl @(PrintT "%c %d %s" Id) ('x', 10,"Asdf")
Present "x 10 Asdf" (PrintT [x 10 Asdf] | s=%c %d %s)
PresentT "x 10 Asdf"
>>> pz @(PrintT "fst=%s snd=%03d" Id) ("ab",123)
Present "fst=ab snd=123"
PresentT "fst=ab snd=123"
>>> pz @(PrintT "fst=%s snd=%03d thd=%s" Id) ("ab",123,"xx")
Present "fst=ab snd=123 thd=xx"
PresentT "fst=ab snd=123 thd=xx"
>>> pl @(PrintT "%s %d %c %s" '(W "xyz", Fst Id, Snd Id, Thd Id)) (123,'x',"ab")
Present "xyz 123 x ab" (PrintT [xyz 123 x ab] | s=%s %d %c %s)
PresentT "xyz 123 x ab"
>>> pl @(PrintT "%d %c %s" Id) (123,'x')
Error PrintT(IO e=printf: argument list ended prematurely)
FailT "PrintT(IO e=printf: argument list ended prematurely)"
>>> pl @(PrintT "%d %c %s" Id) (123,'x',"abc",11)
Error PrintT(IO e=printf: formatting string ended prematurely)
FailT "PrintT(IO e=printf: formatting string ended prematurely)"
Instances
(PrintC bs, (b, bs) ~ InductTupleP y, InductTupleC y, PrintfArg b, PP s x ~ String, PP p x ~ y, P s x, P p x, CheckT (PP p x) ~ True) => P (PrintT s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PrintT s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (PrintT s p) -> POpts -> x -> m (TT (PP (PrintT s p) x)) Source #

type PP (PrintT s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (PrintT s p :: Type) x = String

higher order expressions

data Pure (t :: Type -> Type) p Source #

similar to pure

>>> pz @(Pure Maybe Id) 4
Present Just 4
PresentT (Just 4)
>>> pz @(Pure [] Id) 4
Present [4]
PresentT [4]
>>> pz @(Pure (Either String) (Fst Id)) (13,True)
Present Right 13
PresentT (Right 13)
Instances
(P p x, Show (PP p x), Show (t (PP p x)), Applicative t) => P (Pure t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Pure t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pure t p) -> POpts -> x -> m (TT (PP (Pure t p) x)) Source #

type PP (Pure t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (Pure t p :: Type) x = t (PP p x)

data Pure2 (t :: Type -> Type) Source #

lift pure over a Functor

>>> pz @(Pure2 (Either String)) [1,2,4]
Present [Right 1,Right 2,Right 4]
PresentT [Right 1,Right 2,Right 4]
Instances
(Show (f (t a)), Show (f a), Applicative t, Functor f) => P (Pure2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Pure2 t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pure2 t) -> POpts -> f a -> m (TT (PP (Pure2 t) (f a))) Source #

type PP (Pure2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

type PP (Pure2 t :: Type) (f a) = f (t a)

type FoldMap (t :: Type) p = Map (Wrap t Id) p >> Unwrap (MConcat Id) Source #

similar to a limited form of foldMap

>>> pz @(FoldMap (SG.Sum _) Id) [44, 12, 3]
Present 59
PresentT 59
>>> pz @(FoldMap (SG.Product _) Id) [44, 12, 3]
Present 1584
PresentT 1584
>>> type Ands' p = FoldMap SG.All p
>>> pz @(Ands' Id) [True,False,True,True]
Present False
PresentT False
>>> pz @(Ands' Id) [True,True,True]
Present True
PresentT True
>>> pz @(Ands' Id) []
Present True
PresentT True
>>> type Ors' p = FoldMap SG.Any p
>>> pz @(Ors' Id) [False,False,False]
Present False
PresentT False
>>> pz @(Ors' Id) []
Present False
PresentT False
>>> pz @(Ors' Id) [False,False,False,True]
Present True
PresentT True
>>> type AllPositive' = FoldMap SG.All (Map Positive Id)
>>> pz @AllPositive' [3,1,-5,10,2,3]
Present False
PresentT False
>>> type AllNegative' = FoldMap SG.All (Map Negative Id)
>>> pz @AllNegative' [-1,-5,-10,-2,-3]
Present True
PresentT True
>>> :set -XKindSignatures
>>> type Max' (t :: Type) = FoldMap (SG.Max t) Id -- requires t be Bounded for monoid instance
>>> pz @(Max' Int) [10,4,5,12,3,4]
Present 12
PresentT 12

data p <$ q infixl 4 Source #

similar to <$

>>> pz @(Fst Id <$ Snd Id) ("abc",Just 20)
Present Just "abc"
PresentT (Just "abc")
Instances
(P p x, P q x, Show (PP p x), Functor t, PP q x ~ t c, ApplyConstT (PP q x) (PP p x) ~ t (PP p x)) => P (p <$ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p <$ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <$ q) -> POpts -> x -> m (TT (PP (p <$ q) x)) Source #

type PP (p <$ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p <$ q :: Type) x

data p <* q infixl 4 Source #

Instances
(Show (t c), P p x, P q x, Show (t b), Applicative t, t b ~ PP p x, PP q x ~ t c) => P (p <* q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p <* q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <* q) -> POpts -> x -> m (TT (PP (p <* q) x)) Source #

type PP (p <* q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p <* q :: Type) x = PP p x

type (*>) p q = q <* p infixl 4 Source #

similar to <*

>>> pz @(Fst Id <* Snd Id) (Just "abc",Just 20)
Present Just "abc"
PresentT (Just "abc")

data FMapFst Source #

similar to fmap fst

>>> pz @FMapFst (Just (13,"Asf"))
Present Just 13
PresentT (Just 13)

to make this work we grab the fst or snd out of the Maybe so it is a head or not/ is a tail or not etc! we still have access to the whole original list so we dont lose anything!

Instances
Functor f => P FMapFst (f (a, x)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP FMapFst (f (a, x)) :: Type Source #

Methods

eval :: MonadEval m => Proxy FMapFst -> POpts -> f (a, x) -> m (TT (PP FMapFst (f (a, x)))) Source #

type PP FMapFst (f (a, x)) Source # 
Instance details

Defined in Predicate.Prelude

type PP FMapFst (f (a, x)) = f a

data FMapSnd Source #

similar to fmap snd

>>> pz @FMapSnd (Just ("asf",13))
Present Just 13
PresentT (Just 13)
Instances
Functor f => P FMapSnd (f (x, a)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP FMapSnd (f (x, a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy FMapSnd -> POpts -> f (x, a) -> m (TT (PP FMapSnd (f (x, a)))) Source #

type PP FMapSnd (f (x, a)) Source # 
Instance details

Defined in Predicate.Prelude

type PP FMapSnd (f (x, a)) = f a

data Sequence Source #

similar to sequenceA

>>> pz @Sequence [Just 10, Just 20, Just 30]
Present Just [10,20,30]
PresentT (Just [10,20,30])
>>> pz @Sequence [Just 10, Just 20, Just 30, Nothing, Just 40]
Present Nothing
PresentT Nothing
Instances
(Show (f (t a)), Show (t (f a)), Traversable t, Applicative f) => P Sequence (t (f a)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Sequence (t (f a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Sequence -> POpts -> t (f a) -> m (TT (PP Sequence (t (f a)))) Source #

type PP Sequence (t (f a)) Source # 
Instance details

Defined in Predicate.Prelude

type PP Sequence (t (f a)) = f (t a)

type Traverse p q = Map p q >> Sequence Source #

data Join Source #

similar to join

>>> pz @Join  (Just (Just 20))
Present Just 20
PresentT (Just 20)
>>> pz @Join  ["ab","cd","","ef"]
Present "abcdef"
PresentT "abcdef"
Instances
(Show (t (t a)), Show (t a), Monad t) => P Join (t (t a)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Join (t (t a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Join -> POpts -> t (t a) -> m (TT (PP Join (t (t a)))) Source #

type PP Join (t (t a)) Source # 
Instance details

Defined in Predicate.Prelude

type PP Join (t (t a)) = t a

data EmptyT (t :: Type -> Type) p Source #

similar to empty

>>> pz @(EmptyT Maybe Id) ()
Present Nothing
PresentT Nothing
>>> pz @(EmptyT [] Id) ()
Present []
PresentT []
>>> pz @(EmptyT [] (Char1 "x")) (13,True)
Present ""
PresentT ""
>>> pz @(EmptyT (Either String) (Fst Id)) (13,True)
Present Left ""
PresentT (Left "")
Instances
(P p x, PP p x ~ a, Show (t a), Show a, Alternative t) => P (EmptyT t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (EmptyT t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EmptyT t p) -> POpts -> x -> m (TT (PP (EmptyT t p) x)) Source #

type PP (EmptyT t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (EmptyT t p :: Type) x = t (PP p x)

data p <|> q infixl 3 Source #

similar to <|>

>>> pz @(Fst Id <|> Snd Id) (Nothing,Just 20)
Present Just 20
PresentT (Just 20)
>>> pz @(Fst Id <|> Snd Id) (Just 10,Just 20)
Present Just 10
PresentT (Just 10)
>>> pz @(Fst Id <|> Snd Id) (Nothing,Nothing)
Present Nothing
PresentT Nothing
Instances
(P p x, P q x, Show (t b), Alternative t, t b ~ PP p x, PP q x ~ t b) => P (p <|> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p <|> q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <|> q) -> POpts -> x -> m (TT (PP (p <|> q) x)) Source #

type PP (p <|> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p <|> q :: Type) x = PP p x

data Extract Source #

similar to extract

>>> pz @Extract (Nothing,Just 20)
Present Just 20
PresentT (Just 20)
>>> pz @Extract (Identity 20)
Present 20
PresentT 20
Instances
(Show (t a), Show a, Comonad t) => P Extract (t a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Extract (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Extract -> POpts -> t a -> m (TT (PP Extract (t a))) Source #

type PP Extract (t a) Source # 
Instance details

Defined in Predicate.Prelude

type PP Extract (t a) = a

data Duplicate Source #

similar to duplicate

>>> pz @Duplicate (20,"abc")
Present (20,(20,"abc"))
PresentT (20,(20,"abc"))
Instances
(Show (t a), Show (t (t a)), Comonad t) => P Duplicate (t a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Duplicate (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Duplicate -> POpts -> t a -> m (TT (PP Duplicate (t a))) Source #

type PP Duplicate (t a) Source # 
Instance details

Defined in Predicate.Prelude

type PP Duplicate (t a) = t (t a)

expression combinators

data p $ q infixl 0 Source #

function application for expressions: similar to $

pz @(Fst Id $ Snd Id) ((*16),4) Present 64 PresentT 64

pz @(Id $ "def") ("abc"<>) Present "abcdef" PresentT "abcdef"

Instances
(P p x, P q x, PP p x ~ (a -> b), FnT (PP p x) ~ b, PP q x ~ a, Show a, Show b) => P (p $ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p $ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p $ q) -> POpts -> x -> m (TT (PP (p $ q) x)) Source #

type PP (p $ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (p $ q :: Type) x

data q & p infixr 1 Source #

flipped function application for expressions: similar to &

pz @(Snd Id & Fst Id) ((*16),4) Present 64 PresentT 64

pz @("def" & Id) ("abc"<>) Present "abcdef" PresentT "abcdef"

Instances
(P p x, P q x, PP p x ~ (a -> b), FnT (PP p x) ~ b, PP q x ~ a, Show a, Show b) => P (q & p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (q & p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (q & p) -> POpts -> x -> m (TT (PP (q & p) x)) Source #

type PP (q & p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

type PP (q & p :: Type) x

data Do (ps :: [k]) Source #

processes a type level list predicates running each in sequence: see >>

>>> pz @(Do [Pred Id, ShowP Id, Id &&& Len]) 9876543
Present ("9876542",7)
PresentT ("9876542",7)
>>> pz @(Do '[W 123, W "xyz", Len &&& Id, Pred Id *** Id<>Id]) ()
Present (2,"xyzxyz")
PresentT (2,"xyzxyz")
Instances
P (DoExpandT ps) a => P (Do ps :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Do ps) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Do ps) -> POpts -> a -> m (TT (PP (Do ps) a)) Source #

type PP (Do ps :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Do ps :: Type) a

data p >> q infixr 1 Source #

This is composition for predicates

>>> pz @(Fst Id >> Succ (Id !! 0)) ([11,12],'x')
Present 12
PresentT 12
>>> pz @(Len *** Succ Id >> ShowP (First (Pred Id))) ([11,12],'x')
Present "(1,'y')"
PresentT "(1,'y')"
Instances
(Show (PP p a), Show (PP q (PP p a)), P p a, P q (PP p a)) => P (p >> q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (p >> q) a :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

type PP (p >> q :: Type) a = PP q (PP p a)

type (<<) p q = q >> p infixr 1 Source #

type (>>>) p q = p >> q infixl 1 Source #

data DoN (n :: Nat) p Source #

leverages Do for repeating predicates (passthrough method) same as DoN n p == FoldN n p Id but more efficient

>>> pz @(DoN 4 (Succ Id)) 'c'
Present 'g'
PresentT 'g'
>>> pz @(DoN 4 (Id <> " | ")) "abc"
Present "abc |  |  |  | "
PresentT "abc |  |  |  | "
>>> pz @(DoN 4 (Id <> "|" <> Id)) "abc"
Present "abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc"
PresentT "abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc"
Instances
P (DoExpandT (RepeatT n p)) a => P (DoN n p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (DoN n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (DoN n p) -> POpts -> a -> m (TT (PP (DoN n p) a)) Source #

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

Defined in Predicate.Prelude

type PP (DoN n p :: Type) a = PP (Do (RepeatT n p)) a

parallel expressions

data Para (ps :: [k]) Source #

Instances
(GetLen ps, P (ParaImpl (LenT ps) ps) [a]) => P (Para ps :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Para ps) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (Para ps) -> POpts -> [a] -> m (TT (PP (Para ps) [a])) Source #

type PP (Para ps :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (Para ps :: Type) [a]

data ParaN (n :: Nat) p Source #

leverages Para for repeating predicates (passthrough method)

>>> pz @(ParaN 4 (Succ Id)) [1..4]
Present [2,3,4,5]
PresentT [2,3,4,5]
>>> pz @(ParaN 4 (Succ Id)) "azwxm"
Error Para: data elements(5) /= predicates(4)
FailT "Para: data elements(5) /= predicates(4)"
>>> pz @(ParaN 4 (Succ Id)) "azwx"
Present "b{xy"
PresentT "b{xy"
Instances
(P (ParaImpl (LenT (RepeatT n p)) (RepeatT n p)) [a], GetLen (RepeatT n p)) => P (ParaN n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ParaN n p) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaN n p) -> POpts -> [a] -> m (TT (PP (ParaN n p) [a])) Source #

type PP (ParaN n p :: Type) [a] Source # 
Instance details

Defined in Predicate.Prelude

type PP (ParaN n p :: Type) [a] = PP (Para (RepeatT n p)) [a]

data Repeat (n :: Nat) p Source #

creates a promoted list of predicates and then evaluates them into a list. see PP instance for '[k]

>>> pz @(Repeat 4 (Succ Id)) 'c'
Present "dddd"
PresentT "dddd"
>>> pz @(Repeat 4 "abc") ()
Present ["abc","abc","abc","abc"]
PresentT ["abc","abc","abc","abc"]
Instances
P (RepeatT n p) a => P (Repeat n p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Repeat n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Repeat n p) -> POpts -> a -> m (TT (PP (Repeat n p) a)) Source #

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

Defined in Predicate.Prelude

type PP (Repeat n p :: Type) a = PP (RepeatT n p) a

miscellaneous

data Prime p Source #

a predicate on prime numbers

>>> pz @(Prime Id) 2
True
TrueT
>>> pz @(Map '(Id,Prime Id) Id) [0..12]
Present [(0,False),(1,False),(2,True),(3,True),(4,False),(5,True),(6,False),(7,True),(8,False),(9,False),(10,False),(11,True),(12,False)]
PresentT [(0,False),(1,False),(2,True),(3,True),(4,False),(5,True),(6,False),(7,True),(8,False),(9,False),(10,False),(11,True),(12,False)]
Instances
(PP p x ~ a, P p x, Show a, Integral a) => P (Prime p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Prime p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Prime p) -> POpts -> x -> m (TT (PP (Prime p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Prime p :: Type) x = Bool

data Luhn p Source #

Luhn predicate check on last digit

>>> pz @(Luhn Id) [1,2,3,0]
True
TrueT
>>> pz @(Luhn Id) [1,2,3,4]
False
FalseT
>>> pz @(GuardSimple (Luhn Id)) [15,4,3,1,99]
Error (Luhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])
FailT "(Luhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])"
>>> pl @(Luhn Id) [15,4,3,1,99]
False (Luhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])
FalseT
Instances
(PP p x ~ [Int], P p x) => P (Luhn p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Luhn p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Luhn p) -> POpts -> x -> m (TT (PP (Luhn p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Luhn p :: Type) x = Bool

data Char1 (s :: Symbol) Source #

extracts the first character from a non empty Symbol

>>> pz @(Char1 "aBc") ()
Present 'a'
PresentT 'a'
Instances
(KnownSymbol s, NullT s ~ False) => P (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Char1 s) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Char1 s) -> POpts -> a -> m (TT (PP (Char1 s) a)) Source #

type PP (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Char1 s :: Type) a = Char

data Hide p Source #

run the expression 'p' but remove the subtrees

Instances
P p x => P (Hide p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Hide p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Hide p) -> POpts -> x -> m (TT (PP (Hide p) x)) Source #

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

Defined in Predicate.Prelude

type PP (Hide p :: Type) x = PP p x

data Hole (t :: Type) Source #

Instances
Typeable t => P (Hole t :: Type) a Source #

Acts as a proxy in this dsl where you can explicitly set the Type.

It is passed around as an argument to help the type checker when needed. see 'ReadP, ParseTimeP, ShowP

Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Hole t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Hole t) -> POpts -> a -> m (TT (PP (Hole t) a)) Source #

type PP (Hole t :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

type PP (Hole t :: Type) a = t

data Skip p Source #

just run the effect but skip the value for example for use with Stdout so it doesnt interfere with the 'a' on the rhs unless there is an error

Instances
(Show (PP p a), P p a) => P (Skip p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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

type (|>) p q = Skip p >> q infixr 1 Source #

type (>|) p q = p >> Skip q infixr 1 Source #

type (>|>) p q = Skip p >> Skip q infixr 1 Source #