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

Predicate.Data.These

Description

promoted These functions

Synopsis

predicates

data IsThis Source #

predicate on This

>>> pz @IsThis (This "aBc")
Val True
>>> pz @IsThis (These 1 'a')
Val False
>>> pl @IsThis (This 12)
True (IsThis | This 12)
Val True

Instances

Instances details
Show IsThis Source # 
Instance details

Defined in Predicate.Data.These

P IsThisT x => P IsThis x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThis x Source #

Methods

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

type PP IsThis x Source # 
Instance details

Defined in Predicate.Data.These

type PP IsThis x

data IsThat Source #

predicate on That

>>> pl @IsThat (This 12)
False (IsThat | This 12)
Val False

Instances

Instances details
Show IsThat Source # 
Instance details

Defined in Predicate.Data.These

P IsThatT x => P IsThat x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThat x Source #

Methods

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

type PP IsThat x Source # 
Instance details

Defined in Predicate.Data.These

type PP IsThat x

data IsThese Source #

predicate on These

>>> pl @IsThese (This 12)
False (IsThese | This 12)
Val False
>>> pz @IsThese (These 1 'a')
Val True
>>> pl @IsThese (These 'x' 12)
True (IsThese | These 'x' 12)
Val True
>>> pl @IsThese (That (SG.Sum 12))
False (IsThese | That (Sum {getSum = 12}))
Val False
>>> pl @IsThese (These 1 (SG.Sum 12))
True (IsThese | These 1 (Sum {getSum = 12}))
Val True

Instances

Instances details
Show IsThese Source # 
Instance details

Defined in Predicate.Data.These

P IsTheseT x => P IsThese x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThese x Source #

Methods

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

type PP IsThese x Source # 
Instance details

Defined in Predicate.Data.These

type PP IsThese x

constructors

data MkThis (t :: Type) p Source #

This constructor

>>> pl @(MkThis () Id) 'x'
Present This 'x' (MkThis This 'x')
Val (This 'x')
>>> pl @(MkThis () Fst) ('x',True)
Present This 'x' (MkThis This 'x')
Val (This 'x')
>>> pz @(MkThis _ Id) 44
Val (This 44)

Instances

Instances details
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 Source #

Methods

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

Show (MkThis t p) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> MkThis t p -> ShowS #

show :: MkThis t p -> String #

showList :: [MkThis t p] -> ShowS #

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 @(Proxy Int >> MkThis' UnproxyT 10) []
Val (This 10)

Instances

Instances details
(P p x, Show (PP p x)) => P (MkThis' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (MkThis' t p) x Source #

Methods

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

Show (MkThis' t p) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> MkThis' t p -> ShowS #

show :: MkThis' t p -> String #

showList :: [MkThis' t p] -> ShowS #

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 #

That constructor

>>> pz @(MkThat _ Id) 44
Val (That 44)
>>> pz @(MkThat _ "Abc" <> MkThis _ '[1,2] <> MkThese [3,4] "def") ()
Val (These [1,2,3,4] "Abcdef")
>>> pl @(MkThat () Id) 'x'
Present That 'x' (MkThat That 'x')
Val (That 'x')

Instances

Instances details
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 Source #

Methods

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

Show (MkThat t p) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> MkThat t p -> ShowS #

show :: MkThat t p -> String #

showList :: [MkThat t p] -> ShowS #

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 #

similar to MkThat where t references the type

Instances

Instances details
(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 Source #

Methods

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

Show (MkThat' t p) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> MkThat' t p -> ShowS #

show :: MkThat' t p -> String #

showList :: [MkThat' t p] -> ShowS #

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 Snd) (44,'x')
Val (These 44 'x')
>>> pl @(MkThese Id 'True) 'x'
Present These 'x' True (MkThese These 'x' True)
Val (These 'x' True)

Instances

Instances details
(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 Source #

Methods

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

Show (MkThese p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> MkThese p q -> ShowS #

show :: MkThese p q -> String #

showList :: [MkThese p q] -> ShowS #

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)

destructors

data This' Source #

tries to extract a value from the This constructor

>>> pz @(This' >> Succ) (This 20)
Val 21
>>> pz @(This' >> Succ) (That 'a')
Fail "This' found That"

Instances

Instances details
Show This' Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> This' -> ShowS #

show :: This' -> String #

showList :: [This'] -> ShowS #

Show a => P This' (These a x) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP This' (These a x) 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) (That 20)
Val 21
>>> pz @(That' >> Succ) (This 'a')
Fail "That' found This"

Instances

Instances details
Show That' Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> That' -> ShowS #

show :: That' -> String #

showList :: [That'] -> ShowS #

Show a => P That' (These x a) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP That' (These x a) 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) (These 1 'a')
Val (1,'b')
>>> pz @(That' >> Succ) (This 'a')
Fail "That' found This"
>>> pz @(These' >> Second Succ) (That 8)
Fail "These' found That"

Instances

Instances details
Show These' Source # 
Instance details

Defined in Predicate.Data.These

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

Instances

Instances details
(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 Source #

Methods

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

Show (ThisDef p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThisDef p q -> ShowS #

show :: ThisDef p q -> String #

showList :: [ThisDef p q] -> ShowS #

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

Instances

Instances details
(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 Source #

Methods

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

Show (ThisFail p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThisFail p q -> ShowS #

show :: ThisFail p q -> String #

showList :: [ThisFail p q] -> ShowS #

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

Instances

Instances details
(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 Source #

Methods

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

Show (ThatDef p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThatDef p q -> ShowS #

show :: ThatDef p q -> String #

showList :: [ThatDef p q] -> ShowS #

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

Instances

Instances details
(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 Source #

Methods

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

Show (ThatFail p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThatFail p q -> ShowS #

show :: ThatFail p q -> String #

showList :: [ThatFail p q] -> ShowS #

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

Instances

Instances details
(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 Source #

Methods

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

Show (TheseDef p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseDef p q -> ShowS #

show :: TheseDef p q -> String #

showList :: [TheseDef p q] -> ShowS #

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

Instances

Instances details
(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 Source #

Methods

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

Show (TheseFail p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseFail p q -> ShowS #

show :: TheseFail p q -> String #

showList :: [TheseFail p q] -> ShowS #

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]
Val "ad"
>>> pz @(Thiss) [That 1, This 'a', These 'b' 33]
Val "a"
>>> pz @(Thiss) [That 1, That 9, These 1 33]
Val []

Instances

Instances details
Show Thiss Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> Thiss -> ShowS #

show :: Thiss -> String #

showList :: [Thiss] -> ShowS #

P ThissT x => P Thiss x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Thiss x 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" ((>>) "xy" | {Snd "xy" | ([1,10,99],"xy",[])})
Val "xy"

Instances

Instances details
Show Thats Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> Thats -> ShowS #

show :: Thats -> String #

showList :: [Thats] -> ShowS #

P ThatsT x => P Thats x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Thats x 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 >> Theses) [1..10]
Val [(1,2),(2,3),(3,4),(4,5),(5,6),(6,7),(7,8),(8,9),(9,10)]

Instances

Instances details
Show Theses Source # 
Instance details

Defined in Predicate.Data.These

P ThesesT x => P Theses x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP Theses x 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 >> Theres) [1..10]
Val [2,3,4,5,6,7,8,9,10]

Instances

Instances details
Show Theres Source # 
Instance details

Defined in Predicate.Data.These

(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] 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 >> Heres) [1..10]
Val [1,2,3,4,5,6,7,8,9,10]

Instances

Instances details
Show Heres Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> Heres -> ShowS #

show :: Heres -> String #

showList :: [Heres] -> ShowS #

(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] 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 s t Source #

destructor for These (similar to these but with an extra environment s) p This a receives (PP t x,a) q That b receives (PP t x,b) r These a b receives (PP t x,(a,b)) s points to the environment you want to pass in t points to the These value

>>> pz @(TheseIn Snd Fst L21 Fst Snd) (999,This 123)
Val 123
>>> pz @(TheseIn Snd Fst L21 Fst Snd) (999,That 123)
Val 999
>>> pz @(TheseIn Snd Fst L21 Fst Snd) (999,These 9 11)
Val 9
>>> pz @(TheseIn '(Snd,L12) '(L11,Snd) Snd Fst Snd) ((999,'a'), These 12 'x')
Val (12,'x')
>>> pz @(TheseIn '(Snd,L12) '(L11,Snd) Snd Fst Snd) ((999,'a'), That 'z')
Val (999,'z')
>>> pz @(TheseIn Snd (Snd >> Len) (Snd >> Fst + Length Snd) () Id) (This 13)
Val 13
>>> pz @(TheseIn Snd (Snd >> Len) (Snd >> Fst + Length Snd) () Id) (That "abcdef")
Val 6
>>> pl @(TheseIn "left" "right" "both" () Id) (This (SG.Sum 12))
Present "left" (TheseIn "left" | This Sum {getSum = 12})
Val "left"
>>> pl @(TheseIn '(Snd,999) '("no value",Snd) Snd () Id) (These "Ab" 13)
Present ("Ab",13) (TheseIn ("Ab",13) | These "Ab" 13)
Val ("Ab",13)
>>> pl @(TheseIn '(Snd,999) '("no value",Snd) Snd () Id) (This "Ab")
Present ("Ab",999) (TheseIn ("Ab",999) | This "Ab")
Val ("Ab",999)
>>> pz @(TheseIn ((Fst + Snd) >> ShowP Id) Snd "Xx" Fst Snd) (9,This 123)
Val "132"
>>> pz @(TheseIn '(Snd,"fromthis") '(Negate 99,Snd) Snd () Id) (This 123)
Val (123,"fromthis")
>>> pz @(TheseIn '(Snd,"fromthis") '(Negate 99,Snd) Snd () Id) (That "fromthat")
Val (-99,"fromthat")
>>> pz @(TheseIn '(Snd,"fromthis") '(Negate 99,Snd) Snd () Id) (These 123 "fromthese")
Val (123,"fromthese")
>>> pl @(TheseIn (PrintF "a=%d" (Snd >> Succ)) ("b=" <> Snd) (PrintT "a=%d b=%s" Snd) () Id) (These @Int 9 "rhs")
Present "a=9 b=rhs" (TheseIn "a=9 b=rhs" | These 9 "rhs")
Val "a=9 b=rhs"
>>> pl @(TheseIn (PrintF "a=%d" (Snd >> Succ)) ("b=" <> Snd) (PrintT "a=%d b=%s" Snd) () Id) (This @Int 9)
Present "a=10" (TheseIn "a=10" | This 9)
Val "a=10"
>>> pl @(TheseIn (PrintF "a=%d" (Snd >> Succ)) ("b=" <> Snd) (PrintT "a=%d b=%s" Snd) () Id) (That @Int "rhs")
Present "b=rhs" (TheseIn "b=rhs" | That "rhs")
Val "b=rhs"
>>> pz @(TheseIn ((Fst + Snd) >> ShowP Id) (ShowP Id) L22 Fst Snd) (9,This 123)
Val "132"

Instances

Instances details
(Show a, Show b, Show (PP r (y, (a, b))), P p (y, a), P q (y, b), P r (y, (a, b)), PP p (y, a) ~ PP q (y, b), PP q (y, b) ~ PP r (y, (a, b)), P s x, P t x, PP s x ~ y, PP t x ~ These a b) => P (TheseIn p q r s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseIn p q r s t) x Source #

Methods

eval :: MonadEval m => proxy (TheseIn p q r s t) -> POpts -> x -> m (TT (PP (TheseIn p q r s t) x)) Source #

Show (TheseIn p q r s t) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseIn p q r s t -> ShowS #

show :: TheseIn p q r s t -> String #

showList :: [TheseIn p q r s t] -> ShowS #

type PP (TheseIn p q r s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

type PP (TheseIn p q r s t :: Type) x = TheseInT r (PP s x) (PP t x)

data TheseId p q r Source #

simple version of TheseIn with Id as the These value and the environment set to ()

>>> pz @(TheseId '(Id,"fromleft") '(888,Id) Id) (These 222 "ok")
Val (222,"ok")
>>> pz @(TheseId '(Id,"fromleft") '(888,Id) Id) (That "ok")
Val (888,"ok")
>>> pz @(TheseId '(Id,"fromleft") '(888,Id) Id) (This 123)
Val (123,"fromleft")

Instances

Instances details
P (TheseIdT p q r) x => P (TheseId p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseId p q r) x Source #

Methods

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

Show (TheseId p q r) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseId p q r -> ShowS #

show :: TheseId p q r -> String #

showList :: [TheseId p q r] -> ShowS #

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

Defined in Predicate.Data.These

type PP (TheseId p q r :: Type) x

data ThesePair s t Source #

provide the default pair in s and t refers to These

>>> pz @(ThesePair Fst Snd) ((999,"oops"),These 2 "xx")
Val (2,"xx")
>>> pz @(ThesePair Fst Snd) ((999,"oops"),That "ok")
Val (999,"ok")

Instances

Instances details
P (ThesePairT s t) x => P (ThesePair s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThesePair s t) x Source #

Methods

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

Show (ThesePair s t) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThesePair s t -> ShowS #

show :: ThesePair s t -> String #

showList :: [ThesePair s t] -> ShowS #

type PP (ThesePair s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

type PP (ThesePair s t :: Type) x

data ThisDef' p q r Source #

get This or use the default value p: q is the environment and r is the These value

>>> pz @(ThisDef' Id Fst Snd) (999,These 1 "xx")
Val 999
>>> pz @(ThisDef' 999 () Id) (That "sdf")
Val 999
>>> pz @(ThisDef' 999 () Id) (This 1)
Val 1

Instances

Instances details
P (ThisDefT' p q r) x => P (ThisDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThisDef' p q r) x Source #

Methods

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

Show (ThisDef' p q r) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThisDef' p q r -> ShowS #

show :: ThisDef' p q r -> String #

showList :: [ThisDef' p q r] -> ShowS #

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

Defined in Predicate.Data.These

type PP (ThisDef' p q r :: Type) x

data ThatDef' p q r Source #

get That or use the default value p: q is the environment and r is the These value

>>> pz @(ThatDef' 999 () Id) (These "x" 1)
Val 999
>>> pz @(ThatDef' 999 () Id) (This "sdf")
Val 999
>>> pz @(ThatDef' 999 Fst Snd) (999,That 1)
Val 1

Instances

Instances details
P (ThatDefT' p q r) x => P (ThatDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThatDef' p q r) x Source #

Methods

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

Show (ThatDef' p q r) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ThatDef' p q r -> ShowS #

show :: ThatDef' p q r -> String #

showList :: [ThatDef' p q r] -> ShowS #

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

Defined in Predicate.Data.These

type PP (ThatDef' p q r :: Type) x

data TheseDef' p q r Source #

get These or use the default value p: q is the environment and r is the These value

>>> pz @(TheseDef' '(999,"xx") () Id) (These 12 "yy")
Val (12,"yy")
>>> pz @(TheseDef' '(999,"xx") () Id) (That "abc")
Val (999,"xx")
>>> pz @(TheseDef' '(999,"xx") () Id) (This 1)
Val (999,"xx")
>>> pz @(TheseDef' '(999,"xx") () Id) (These 1 "abc")
Val (1,"abc")
>>> pz @(TheseDef' Id Fst Snd) ((999,"xx"),That "yy")
Val (999,"xx")

Instances

Instances details
P (TheseDefT' p q r) x => P (TheseDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseDef' p q r) x Source #

Methods

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

Show (TheseDef' p q r) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseDef' p q r -> ShowS #

show :: TheseDef' p q r -> String #

showList :: [TheseDef' p q r] -> ShowS #

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

Defined in Predicate.Data.These

type PP (TheseDef' p q r :: Type) x

data TheseInSimple p q r Source #

similar to these but without any environment

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

Instances

Instances details
P (TheseInSimpleT p q r) x => P (TheseInSimple p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseInSimple p q r) x Source #

Methods

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

Show (TheseInSimple p q r) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> TheseInSimple p q r -> ShowS #

show :: TheseInSimple p q r -> String #

showList :: [TheseInSimple p q r] -> ShowS #

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

Defined in Predicate.Data.These

type PP (TheseInSimple p q r :: 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]
Val ("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'])
Val ([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'])
Val ([1,4,10],"xy",[(9,'z'),(8,'y')])

Instances

Instances details
Show PartitionThese Source # 
Instance details

Defined in Predicate.Data.These

(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] 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)])

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

Instances

Instances details
(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 Source #

Methods

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

Show (ZipThese p q) Source # 
Instance details

Defined in Predicate.Data.These

Methods

showsPrec :: Int -> ZipThese p q -> ShowS #

show :: ZipThese p q -> String #

showList :: [ZipThese p q] -> ShowS #

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))]

type families

type family TheseInT r y elr where ... Source #

calculate the return type for TheseIn

Equations

TheseInT r y (These a b) = PP r (y, (a, b)) 
TheseInT _ _ o = TypeError ('Text "TheseInT: expected 'These a b' " :$$: ('Text "o = " :<>: 'ShowType o))