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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.These

Contents

Description

promoted These functions

Synopsis

boolean predicates

data IsThis p Source #

Instances
P (IsThisT p) x => P (IsThis p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP (IsThis p :: Type) x

data IsThat p Source #

Instances
P (IsThatT p) x => P (IsThat p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP (IsThat p :: Type) x

data IsThese p Source #

Instances
P (IsTheseT p) x => P (IsThese p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP (IsThese p :: Type) x

constructors

data MkThis (t :: Type) p Source #

This constructor

>>> pl @(MkThis () Id) 'x'
Present This 'x' (MkThis This 'x')
PresentT (This 'x')
>>> pl @(MkThis () (Fst Id)) ('x',True)
Present This 'x' (MkThis This 'x')
PresentT (This 'x')
Instances
P (MkThisT t p) x => P (MkThis t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

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.Data.These

type PP (MkThis t p :: Type) x

data MkThis' t p Source #

This constructor

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

Defined in Predicate.Data.These

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.Data.These

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

data MkThat (t :: Type) p Source #

Instances
P (MkThatT t p) x => P (MkThat t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

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.Data.These

type PP (MkThat t p :: Type) x

data MkThat' t p Source #

That constructor

>>> pz @(MkThat _ Id) 44
PresentT (That 44)
>>> pz @(MkThat _ "Abc" <> MkThis _ '[1,2] <> MkThese [3,4] "def") ()
PresentT (These [1,2,3,4] "Abcdef")
>>> pl @(MkThat () Id) 'x'
Present That 'x' (MkThat That 'x')
PresentT (That 'x')
Instances
(Show (PP p x), P p x) => P (MkThat' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

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.Data.These

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')
PresentT (These 44 'x')
>>> pl @(MkThese Id 'True) 'x'
Present These 'x' True (MkThese These 'x' True)
PresentT (These 'x' True)
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.Data.These

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.Data.These

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

get rid of These

data This' Source #

tries to extract a value from the This constructor

>>> pz @(This' >> Succ Id) (This 20)
PresentT 21
>>> pz @(This' >> Succ Id) (That 'a')
FailT "This' found That"
Instances
Show a => P This' (These a x) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP This' (These a x) :: Type Source #

Methods

eval :: MonadEval m => proxy This' -> POpts -> These a x -> m (TT (PP This' (These a x))) Source #

type PP This' (These a x) Source # 
Instance details

Defined in Predicate.Data.These

type PP This' (These a x) = a

data That' Source #

tries to extract a value from the That constructor

>>> pz @(That' >> Succ Id) (That 20)
PresentT 21
>>> pz @(That' >> Succ Id) (This 'a')
FailT "That' found This"
Instances
Show a => P That' (These x a) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP That' (These x a) :: Type Source #

Methods

eval :: MonadEval m => proxy That' -> POpts -> These x a -> m (TT (PP That' (These x a))) Source #

type PP That' (These x a) Source # 
Instance details

Defined in Predicate.Data.These

type PP That' (These x a) = a

data These' Source #

tries to extract the values from the These constructor

>>> pz @(These' >> Second (Succ Id)) (These 1 'a')
PresentT (1,'b')
>>> pz @(That' >> Succ Id) (This 'a')
FailT "That' found This"
>>> pz @(These' >> Second (Succ Id)) (That 8)
FailT "These' found That"
Instances
(Show a, Show b) => P These' (These a b) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP These' (These a b) :: Type Source #

Methods

eval :: MonadEval m => proxy These' -> POpts -> These a b -> m (TT (PP These' (These a b))) Source #

type PP These' (These a b) Source # 
Instance details

Defined in Predicate.Data.These

type PP These' (These a b) = (a, b)

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)
PresentT (102 % 5)
>>> pz @(ThisDef (1 % 4) Id) (That "aa")
PresentT (1 % 4)
>>> pz @(ThisDef (1 % 4) Id) (These 2.3 "aa")
PresentT (1 % 4)
>>> pz @(ThisDef (PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id)) (Snd Id)) (123,That "xy")
PresentT "found That \"xy\" fst=123"
>>> pz @(ThisDef (MEmptyT _) Id) (That 222)
PresentT ()
>>> pz @(ThisDef (MEmptyT (SG.Sum _)) Id) (These 222 'x')
PresentT (Sum {getSum = 0})
>>> pl @(ThisDef (MEmptyT _) Id) (This (SG.Sum 12))
Present Sum {getSum = 12} (ThisDef This)
PresentT (Sum {getSum = 12})
>>> pl @(ThisDef (MEmptyT _) Id) (That 12)
Present () (ThisDef That)
PresentT ()
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.Data.These

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.Data.These

type PP (ThisDef p q :: Type) x = ThisT (PP q x)

data ThisFail p q Source #

extract the This value from a These otherwise fail with a message

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

>>> pz @(ThisFail "oops" Id) (This 20.4)
PresentT 20.4
>>> pz @(ThisFail "oops" Id) (That "aa")
FailT "oops"
>>> pz @(ThisFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,That "xy")
FailT "found That \"xy\" fst=123"
>>> pz @(ThisFail (MEmptyT _) Id) (That 222)
FailT ""
>>> pl @(ThisFail "sdf" Id) (This (SG.Sum 12))
Present Sum {getSum = 12} (This)
PresentT (Sum {getSum = 12})
>>> pl @(ThisFail "sdf" Id) (That (SG.Sum 12))
Error sdf (ThisFail That)
FailT "sdf"
>>> pl @(ThisFail "sdf" Id) (That 12)
Error sdf (ThisFail That)
FailT "sdf"
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.Data.These

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.Data.These

type PP (ThisFail p q :: Type) x = ThisT (PP q 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)
PresentT (102 % 5)
>>> pz @(ThatDef (1 % 4) Id) (This "aa")
PresentT (1 % 4)
>>> pz @(ThatDef (1 % 4) Id) (These "aa" 2.3)
PresentT (1 % 4)
>>> pz @(ThatDef (PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id)) (Snd Id)) (123,This "xy")
PresentT "found This \"xy\" fst=123"
>>> pz @(ThatDef (MEmptyT _) Id) (This 222)
PresentT ()
>>> pz @(ThatDef (MEmptyT (SG.Sum _)) Id) (These 'x' 1120)
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.Data.These

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.Data.These

type PP (ThatDef p q :: Type) x = ThatT (PP q x)

data ThatFail p q Source #

extract the That value from a These otherwise fail with a message

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

>>> pz @(ThatFail "oops" Id) (That 20.4)
PresentT 20.4
>>> pz @(ThatFail "oops" Id) (This "aa")
FailT "oops"
>>> pz @(ThatFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,This "xy")
FailT "found This \"xy\" fst=123"
>>> pz @(ThatFail (MEmptyT _) Id) (This 222)
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.Data.These

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.Data.These

type PP (ThatFail p q :: Type) x = ThatT (PP q 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")
PresentT (102 % 5,"x")
>>> pz @(TheseDef '(1 % 4,"zz") Id) (This 20.4)
PresentT (1 % 4,"zz")
>>> pz @(TheseDef '(1 % 4,"zz") Id) (That "x")
PresentT (1 % 4,"zz")
>>> pz @(TheseDef '(PrintT "found %s fst=%d" '(ShowP (Snd Id), Fst Id),999) (Snd Id)) (123,This "xy")
PresentT ("found This \"xy\" fst=123",999)
>>> pz @(TheseDef (MEmptyT (SG.Sum _, String)) Id) (This 222)
PresentT (Sum {getSum = 0},"")
>>> pz @(TheseDef (MEmptyT _) Id) (These (222 :: SG.Sum Int) "aa")
PresentT (Sum {getSum = 222},"aa")
>>> pl @(TheseDef '("xyz",'True) Id) (This "abc")
Present ("xyz",True) (TheseDef This)
PresentT ("xyz",True)
>>> pl @(TheseDef '("xyz",'True) Id) (That False)
Present ("xyz",True) (TheseDef That)
PresentT ("xyz",True)
>>> pl @(TheseDef '("xyz",'True) Id) (These "abc" False)
Present ("abc",False) (TheseDef These)
PresentT ("abc",False)
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.Data.These

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.Data.These

type PP (TheseDef p q :: Type) x = TheseT (PP q x)

data TheseFail p q Source #

extract the These value from a These otherwise fail with a message

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

>>> pz @(TheseFail "oops" Id) (These "abc" 20.4)
PresentT ("abc",20.4)
>>> pz @(TheseFail "oops" Id) (That "aa")
FailT "oops"
>>> pz @(TheseFail (PrintT "found %s fst=%d" '(ShowP (Snd Id),Fst Id)) (Snd Id)) (123,That "xy")
FailT "found That \"xy\" fst=123"
>>> pz @(TheseFail (MEmptyT _) Id) (That 222)
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.Data.These

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.Data.These

type PP (TheseFail p q :: Type) x = TheseT (PP q x)

data Thiss Source #

similar to catThis

>>> pz @(Thiss) [That 1, This 'a', These 'b' 33, This 'd', That 4]
PresentT "ad"
>>> pz @(Thiss) [That 1, This 'a', These 'b' 33]
PresentT "a"
>>> pz @(Thiss) [That 1, That 9, These 1 33]
PresentT []
Instances
P ThissT x => P Thiss x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Thiss x :: Type Source #

Methods

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

type PP Thiss x Source # 
Instance details

Defined in Predicate.Data.These

type PP Thiss x

data Thats Source #

similar to catThat

>>> pl @Thats [This 1, This 10,That 'x', This 99, That 'y']
Present "xy" (Snd "xy" | ([1,10,99],"xy",[]))
PresentT "xy"
Instances
P ThatsT x => P Thats x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Thats x :: Type Source #

Methods

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

type PP Thats x Source # 
Instance details

Defined in Predicate.Data.These

type PP Thats x

data Theses Source #

similar to catThese

>>> pz @(ZipThese Id (Tail Id) >> Theses) [1..10]
PresentT [(1,2),(2,3),(3,4),(4,5),(5,6),(6,7),(7,8),(8,9),(9,10)]
Instances
P ThesesT x => P Theses x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Theses x :: Type Source #

Methods

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

type PP Theses x Source # 
Instance details

Defined in Predicate.Data.These

type PP Theses x

data Theres Source #

similar to catThere

>>> pz @(ZipThese Id (Tail Id) >> Theres) [1..10]
PresentT [2,3,4,5,6,7,8,9,10]
Instances
(Show a, Show b) => P Theres [These a b] Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP Theres [These a b] = [b]

data Heres Source #

similar to catHere

>>> pz @(ZipThese Id (Tail Id) >> Heres) [1..10]
PresentT [1,2,3,4,5,6,7,8,9,10]
Instances
(Show a, Show b) => P Heres [These a b] Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP Heres [These a b] = [a]

data TheseIn p q r Source #

similar to these

>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (This 13)
PresentT 13
>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (That "this is a long string")
PresentT 21
>>> pz @(TheseIn Id Len (Fst Id + Length (Snd Id))) (These 20 "somedata")
PresentT 28
>>> pz @(TheseIn (MkLeft _ Id) (MkRight _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (That "this is a long string")
PresentT (Right "this is a long string")
>>> pz @(TheseIn (MkLeft _ Id) (MkRight _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 1 "this is a long string")
PresentT (Right "this is a long string")
>>> pz @(TheseIn (MkLeft _ Id) (MkRight _ Id) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 100 "this is a long string")
PresentT (Left 100)
>>> pl @(TheseIn "this" "that" "these") (This (SG.Sum 12))
Present "this" (TheseIn "this" | This Sum {getSum = 12})
PresentT "this"
>>> pl @(TheseIn (Id &&& 999) ("no value" &&& Id) Id) (These "Ab" 13)
Present ("Ab",13) (TheseIn ("Ab",13) | These "Ab" 13)
PresentT ("Ab",13)
>>> pl @(TheseIn (Id &&& 999) ("no value" &&& Id) Id) (This "Ab")
Present ("Ab",999) (TheseIn ("Ab",999) | This "Ab")
PresentT ("Ab",999)
>>> pl @(TheseIn (Id &&& 999) ("no value" &&& Id) Id) (That 13)
Present ("no value",13) (TheseIn ("no value",13) | That 13)
PresentT ("no value",13)
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.Data.These

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.Data.These

type PP (TheseIn p q r :: Type) (These a b) = PP p a

data TheseId p q Source #

TheseId: returns a tuple so you need to provide a value for rhs in the This case and lhs for the That case

>>> pl @(TheseId 'True "xyz") (This "abc")
Present ("abc",True) (TheseIn ("abc",True) | This "abc")
PresentT ("abc",True)
>>> pl @(TheseId 'True "xyz") (That False)
Present ("xyz",False) (TheseIn ("xyz",False) | That False)
PresentT ("xyz",False)
>>> pl @(TheseId 'True "xyz") (These "abc" False)
Present ("abc",False) (TheseIn ("abc",False) | These "abc" False)
PresentT ("abc",False)
Instances
P (TheseIdT p q) x => P (TheseId p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

type PP (TheseId p q :: Type) x

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]
PresentT ("ac",[2,4,99],[('z',1),('a',2)])
>>> pl @PartitionThese [This 4, That 'x', That 'y',These 3 'b', This 99, These 5 'x']
Present ([4,99],"xy",[(3,'b'),(5,'x')]) (PartitionThese ([4,99],"xy",[(3,'b'),(5,'x')]) | [This 4,That 'x',That 'y',These 3 'b',This 99,These 5 'x'])
PresentT ([4,99],"xy",[(3,'b'),(5,'x')])
>>> pl @PartitionThese [This 1,That 'x',This 4,That 'y',These 9 'z',This 10,These 8 'y']
Present ([1,4,10],"xy",[(9,'z'),(8,'y')]) (PartitionThese ([1,4,10],"xy",[(9,'z'),(8,'y')]) | [This 1,That 'x',This 4,That 'y',These 9 'z',This 10,These 8 'y'])
PresentT ([1,4,10],"xy",[(9,'z'),(8,'y')])
Instances
(Show a, Show b) => P PartitionThese [These a b] Source # 
Instance details

Defined in Predicate.Data.These

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.Data.These

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

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)
PresentT "132"
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (This 123)
PresentT (123,"fromthis")
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (That "fromthat")
PresentT (-99,"fromthat")
>>> pz @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (These 123 "fromthese")
PresentT (123,"fromthese")
>>> pl @(TheseX (PrintF "a=%d" (Succ (Snd Id))) ("b=" <> Snd Id) (PrintT "a=%d b=%s" (Snd Id)) Id) (These @Int 9 "rhs")
Present "a=9 b=rhs" (TheseX(These))
PresentT "a=9 b=rhs"
>>> pl @(TheseX (PrintF "a=%d" (Succ (Snd Id))) ("b=" <> Snd Id) (PrintT "a=%d b=%s" (Snd Id)) Id) (This @Int 9)
Present "a=10" (TheseX(This))
PresentT "a=10"
>>> pl @(TheseX (PrintF "a=%d" (Succ (Snd Id))) ("b=" <> Snd Id) (PrintT "a=%d b=%s" (Snd Id)) Id) (That @Int "rhs")
Present "b=rhs" (TheseX(That))
PresentT "b=rhs"
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.Data.These

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.Data.These

type PP (TheseX p q r s :: Type) x

miscellaneous

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])
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,That 4,That 5]
>>> pz @(ZipThese (Fst Id) (Snd Id)) ("aBcDeF", [1..3])
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,This 'D',This 'e',This 'F']
>>> pz @(ZipThese Id Reverse) "aBcDeF"
PresentT [These 'a' 'F',These 'B' 'e',These 'c' 'D',These 'D' 'c',These 'e' 'B',These 'F' 'a']
>>> pz @(ZipThese Id '[]) "aBcDeF"
PresentT [This 'a',This 'B',This 'c',This 'D',This 'e',This 'F']
>>> pz @(ZipThese '[] Id) "aBcDeF"
PresentT [That 'a',That 'B',That 'c',That 'D',That 'e',That 'F']
>>> pz @(ZipThese '[] '[]) "aBcDeF"
PresentT []
>>> pl @(ZipThese (Fst Id) (Snd Id) >> Map (TheseIn Id Id (Fst Id)) Id) (['w'..'y'],['a'..'f'])
Present "wxydef" ((>>) "wxydef" | {Map "wxydef" | [These 'w' 'a',These 'x' 'b',These 'y' 'c',That 'd',That 'e',That 'f']})
PresentT "wxydef"
>>> pl @(("sdf" &&& Id) >> ZipThese (Fst Id) (Snd Id) >> Map (TheseIn (Id &&& 0) (Head "x" &&& Id) Id) Id) [1..5]
Present [('s',1),('d',2),('f',3),('x',4),('x',5)] ((>>) [('s',1),('d',2),('f',3),('x',4),('x',5)] | {Map [('s',1),('d',2),('f',3),('x',4),('x',5)] | [These 's' 1,These 'd' 2,These 'f' 3,That 4,That 5]})
PresentT [('s',1),('d',2),('f',3),('x',4),('x',5)]
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.Data.These

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.Data.These

type PP (ZipThese p q :: Type) a = [These (ExtractAFromList (PP p a)) (ExtractAFromList (PP q a))]

data Assoc Source #

assoc using AssocC

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

Defined in Predicate.Data.These

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.Data.These

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

data Unassoc Source #

unassoc using AssocC

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

Defined in Predicate.Data.These

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.Data.These

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