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

Predicate.Data.Either

Description

promoted Either functions

Synopsis

predicates

data IsLeft Source #

similar to isLeft

>>> pz @IsLeft (Right 123)
Val False
>>> pz @IsLeft (Left 'a')
Val True

Instances

Instances details
Show IsLeft Source # 
Instance details

Defined in Predicate.Data.Either

x ~ Either a b => P IsLeft x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP IsLeft x Source #

Methods

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

type PP IsLeft x Source # 
Instance details

Defined in Predicate.Data.Either

type PP IsLeft x = Bool

data IsRight Source #

similar to isRight

>>> pz @IsRight (Right 123)
Val True
>>> pz @IsRight (Left "aa")
Val False

Instances

Instances details
Show IsRight Source # 
Instance details

Defined in Predicate.Data.Either

x ~ Either a b => P IsRight x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP IsRight x Source #

Methods

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

type PP IsRight x Source # 
Instance details

Defined in Predicate.Data.Either

type PP IsRight x = Bool

constructors

data MkLeft (t :: Type) p Source #

Left constructor

>>> pz @(MkLeft _ Id) 44
Val (Left 44)

Instances

Instances details
P (MkLeftT t p) x => P (MkLeft t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (MkLeft t p) x Source #

Methods

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

Show (MkLeft t p) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: MkLeft t p -> String #

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

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

Defined in Predicate.Data.Either

type PP (MkLeft t p :: Type) x

data MkLeft' t p Source #

Left constructor

Instances

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

Defined in Predicate.Data.Either

Associated Types

type PP (MkLeft' t p) x Source #

Methods

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

Show (MkLeft' t p) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: MkLeft' t p -> String #

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

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

Defined in Predicate.Data.Either

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

data MkRight (t :: Type) p Source #

Right constructor

>>> pz @(MkRight _ Id) 44
Val (Right 44)

Instances

Instances details
P (MkRightT t p) x => P (MkRight t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (MkRight t p) x Source #

Methods

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

Show (MkRight t p) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: MkRight t p -> String #

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

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

Defined in Predicate.Data.Either

type PP (MkRight t p :: Type) x

data MkRight' t p Source #

Right constructor

Instances

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

Defined in Predicate.Data.Either

Associated Types

type PP (MkRight' t p) x Source #

Methods

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

Show (MkRight' t p) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: MkRight' t p -> String #

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

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

Defined in Predicate.Data.Either

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

get rid of Either

data Left' Source #

extracts the left value from an Either

>>> pz @(Left' >> Succ) (Left 20)
Val 21
>>> pz @(Left' >> Succ) (Right 'a')
Fail "Left' found Right"

Instances

Instances details
Show Left' Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: Left' -> String #

showList :: [Left'] -> ShowS #

Show a => P Left' (Either a x) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Left' (Either a x) Source #

Methods

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

type PP Left' (Either a x) Source # 
Instance details

Defined in Predicate.Data.Either

type PP Left' (Either a x) = a

data Right' Source #

extracts the right value from an Either

>>> pz @(Right' >> Succ) (Right 20)
Val 21
>>> pz @(Right' >> Succ) (Left 'a')
Fail "Right' found Left"

Instances

Instances details
Show Right' Source # 
Instance details

Defined in Predicate.Data.Either

Show a => P Right' (Either x a) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Right' (Either x a) Source #

Methods

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

type PP Right' (Either x a) Source # 
Instance details

Defined in Predicate.Data.Either

type PP Right' (Either x a) = a

data LeftDef p q Source #

extract the Left value from an Either otherwise use the default value: similar to fromLeft

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)
Val (102 % 5)
>>> pz @(LeftDef (1 % 4) Id) (Right "aa")
Val (1 % 4)
>>> pz @(LeftDef (PrintT "found right=%s fst=%d" '(Fst,L21)) Snd) (123,Right "xy")
Val "found right=xy fst=123"
>>> pz @(LeftDef (MEmptyT _) Id) (Right 222)
Val ()
>>> pz @(LeftDef (MEmptyT (SG.Sum _)) Id) (Right 222)
Val (Sum {getSum = 0})

Instances

Instances details
(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.Data.Either

Associated Types

type PP (LeftDef p q) x Source #

Methods

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

Show (LeftDef p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: LeftDef p q -> String #

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

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

Defined in Predicate.Data.Either

type PP (LeftDef p q :: Type) x = LeftT (PP q x)

data LeftFail p q Source #

extract the Left value from an Either otherwise fail with a 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)
Val 20.4
>>> pz @(LeftFail "oops" Id) (Right "aa")
Fail "oops"
>>> pz @(LeftFail (PrintT "found right=%s fst=%d" '(Fst,L21)) Snd) (123,Right "xy")
Fail "found right=xy fst=123"
>>> pz @(LeftFail (MEmptyT _) Id) (Right 222)
Fail ""
>>> pl @(LeftFail (PrintF "someval=%d" L21) Snd) (13::Int,Right @(SG.Sum Int) "abc")
Error someval=13 (LeftFail Right)
Fail "someval=13"
>>> pl @(LeftFail (PrintF "someval=%s" Fst) Id) (Right @(SG.Sum Int) "abc")
Error someval=abc (LeftFail Right)
Fail "someval=abc"
>>> pl @(LeftFail (PrintF "found rhs=%d" Fst) Id) (Right @String @Int 10)
Error found rhs=10 (LeftFail Right)
Fail "found rhs=10"
>>> pl @(LeftFail (PrintF "found rhs=%d" (Snd >> L22)) L21) ('x',(Right 10,23))
Error found rhs=23 (LeftFail Right)
Fail "found rhs=23"
>>> pl @(LeftFail (PrintF "found rhs=%d" (L2 L22)) L21) ('x',(Left "abc",23))
Present "abc" (Left)
Val "abc"

Instances

Instances details
(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.Data.Either

Associated Types

type PP (LeftFail p q) x Source #

Methods

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

Show (LeftFail p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: LeftFail p q -> String #

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

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

Defined in Predicate.Data.Either

type PP (LeftFail p q :: Type) x = LeftT (PP q x)

data RightDef p q Source #

extract the Right value from an Either: similar to fromRight

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)
Val (102 % 5)
>>> pz @(RightDef (1 % 4) Id) (Left "aa")
Val (1 % 4)
>>> pz @(RightDef (PrintT "found left=%s fst=%d" '(Fst,L21)) Snd) (123,Left "xy")
Val "found left=xy fst=123"
>>> pz @(RightDef (MEmptyT _) Id) (Left 222)
Val ()
>>> pz @(RightDef (MEmptyT (SG.Sum _)) Id) (Left 222)
Val (Sum {getSum = 0})

Instances

Instances details
(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.Data.Either

Associated Types

type PP (RightDef p q) x Source #

Methods

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

Show (RightDef p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: RightDef p q -> String #

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

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

Defined in Predicate.Data.Either

type PP (RightDef p q :: Type) x = RightT (PP q x)

data RightFail p q Source #

extract the Right value from an Either otherwise fail with a 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)
Val 20.4
>>> pz @(RightFail "oops" Id) (Left "aa")
Fail "oops"
>>> pz @(RightFail (PrintT "found left=%s fst=%d" '(Fst,L21)) Snd) (123,Left "xy")
Fail "found left=xy fst=123"
>>> pz @(RightFail (MEmptyT _) Id) (Left 222)
Fail ""

Instances

Instances details
(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.Data.Either

Associated Types

type PP (RightFail p q) x Source #

Methods

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

Show (RightFail p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: RightFail p q -> String #

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

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

Defined in Predicate.Data.Either

type PP (RightFail p q :: Type) x = RightT (PP q 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 > 4) L21 L22) (24,(-1,999))
Val (Right 999)
>>> pz @(EitherBool (Fst > 4) L21 L22) (1,(-1,999))
Val (Left (-1))
>>> pl @(EitherBool (Fst > 10) L21 L22) (7,('x',99))
Present Left 'x' (EitherBool(False) Left 'x')
Val (Left 'x')
>>> pl @(EitherBool (Fst > 10) L21 L22) (11,('x',99))
Present Right 99 (EitherBool(True) Right 99)
Val (Right 99)
>>> pl @(EitherBool (Gt 10) "found left" 99) 12
Present Right 99 (EitherBool(True) Right 99)
Val (Right 99)
>>> pl @(EitherBool (Gt 10) "found left" 99) 7
Present Left "found left" (EitherBool(False) Left "found left")
Val (Left "found left")

Instances

Instances details
(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.Data.Either

Associated Types

type PP (EitherBool b p q) a Source #

Methods

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

Show (EitherBool b p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

showsPrec :: Int -> EitherBool b p q -> ShowS #

show :: EitherBool b p q -> String #

showList :: [EitherBool b p q] -> ShowS #

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

Defined in Predicate.Data.Either

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

data PartitionEithers Source #

similar to partitionEithers

>>> pz @PartitionEithers [Left 'a',Right 2,Left 'c',Right 4,Right 99]
Val ("ac",[2,4,99])
>>> pz @PartitionEithers [Right 2,Right 4,Right 99]
Val ([],[2,4,99])
>>> pz @PartitionEithers [Left 'a',Left 'c']
Val ("ac",[])
>>> pz @PartitionEithers ([] :: [Either () Int])
Val ([],[])
>>> pl @PartitionEithers [Left 4, Right 'x', Right 'y',Left 99]
Present ([4,99],"xy") (PartitionEithers ([4,99],"xy") | [Left 4,Right 'x',Right 'y',Left 99])
Val ([4,99],"xy")
>>> pl @PartitionEithers [Left 'x', Right 1,Left 'a', Left 'b',Left 'z', Right 10]
Present ("xabz",[1,10]) (PartitionEithers ("xabz",[1,10]) | [Left 'x',Right 1,Left 'a',Left 'b',Left 'z',Right 10])
Val ("xabz",[1,10])

Instances

Instances details
Show PartitionEithers Source # 
Instance details

Defined in Predicate.Data.Either

(Show a, Show b) => P PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP PartitionEithers [Either a b] 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.Data.Either

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

miscellaneous

data p ||| q infixr 2 Source #

similar |||

>>> pz @(Pred ||| Id) (Left 13)
Val 12
>>> pz @(ShowP Id ||| Id) (Right "hello")
Val "hello"
>>> pl @('True ||| 'False) (Left "someval")
True ((|||) Left True | "someval")
Val True
>>> pl @('True ||| 'False) (Right "someval")
False ((|||) Right False | "someval")
Val False
>>> pl @(ShowP Succ ||| ShowP Id) (Left 123)
Present "124" ((|||) Left "124" | 123)
Val "124"
>>> pl @(ShowP Succ ||| ShowP Id) (Right True)
Present "True" ((|||) Right "True" | True)
Val "True"
>>> pl @(Not Id ||| Id) (Right True)
Present True ((|||) Right True | True)
Val True
>>> pl @(Not Id ||| Id) (Left True)
False ((|||) Left False | True)
Val False

Instances

Instances details
(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.Data.Either

Associated Types

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

Methods

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

Show (p ||| q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

showsPrec :: Int -> (p ||| q) -> ShowS #

show :: (p ||| q) -> String #

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

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

Defined in Predicate.Data.Either

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

data p +++ q infixr 2 Source #

similar +++

>>> pz @(Pred +++ Id) (Left 13)
Val (Left 12)
>>> pz @(ShowP Id +++ Reverse) (Right "hello")
Val (Right "olleh")
>>> pl @(HeadDef 'False Id +++ Id) (Right @[Bool] 1) -- need @[Bool] to match with 'False
Present Right 1 ((+++) Right 1 | 1)
Val (Right 1)
>>> pl @(HeadDef 'False Id +++ Id) (Left [True,False]) -- need @[Bool] to match with 'False!
Present Left True ((+++) Left True | [True,False])
Val (Left True)
>>> pl @(Not Id +++ Id) (Right True)
Present Right True ((+++) Right True | True)
Val (Right True)
>>> pl @(Not Id +++ Id) (Right 12)
Present Right 12 ((+++) Right 12 | 12)
Val (Right 12)
>>> pl @(HeadDef () Id +++ Id) (Right @[()] 1) -- breaks otherwise: Id says () -> () so has to be a list of [()]
Present Right 1 ((+++) Right 1 | 1)
Val (Right 1)
>>> pl @(HeadDef () Id +++ Id) (Right @[()] 1) -- this breaks! as Left doesnt have a type
Present Right 1 ((+++) Right 1 | 1)
Val (Right 1)
>>> pl @(Not Id +++ Id) (Right @Bool 12)
Present Right 12 ((+++) Right 12 | 12)
Val (Right 12)

Instances

Instances details
(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.Data.Either

Associated Types

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

Methods

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

Show (p +++ q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

showsPrec :: Int -> (p +++ q) -> ShowS #

show :: (p +++ q) -> String #

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

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

Defined in Predicate.Data.Either

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

data EitherIn p q s t Source #

destructor for Either (similar to ||| but with an extra environment s) p Left a receives (PP t x,a) q Right b receives (PP t x,b) s points to the environment you want to pass in t points to the Either value

>>> pz @(EitherIn (ShowP (Fst + Snd)) (ShowP Id) Fst Snd) (9,Left 123)
Val "132"
>>> pz @(EitherIn (ShowP (Fst + Snd)) (ShowP Id) Fst Snd) (9,Right 'x')
Val "(9,'x')"
>>> pz @(EitherIn (ShowP Id) (ShowP (Second Succ)) Fst Snd) (9,Right 'x')
Val "(9,'y')"
>>> pz @(EitherIn (FailT _ (PrintF ("found left=%d") Snd)) (Second Succ) Fst Snd) (9,Right 'x')
Val (9,'y')
>>> pz @(EitherIn (FailT _ (PrintF ("found left=%d") Snd)) (Second Succ) Fst Snd) (9,Left 13)
Fail "found left=13"

Instances

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

Defined in Predicate.Data.Either

Associated Types

type PP (EitherIn p q s t) x Source #

Methods

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

Show (EitherIn p q s t) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

showsPrec :: Int -> EitherIn p q s t -> ShowS #

show :: EitherIn p q s t -> String #

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

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

Defined in Predicate.Data.Either

type PP (EitherIn p q s t :: Type) x = EitherInT p (PP s x) (PP t x)

data EitherId p q Source #

simple version of EitherIn with Id as the Either value and the environment set to ()

>>> pz @(EitherId '(Id,"fromleft") '(888,Id)) (Right "ok")
Val (888,"ok")
>>> pz @(EitherId '(Id,"fromleft") '(888,Id)) (Left 123)
Val (123,"fromleft")

Instances

Instances details
P (EitherIdT p q) x => P (EitherId p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (EitherId p q) x Source #

Methods

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

Show (EitherId p q) Source # 
Instance details

Defined in Predicate.Data.Either

Methods

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

show :: EitherId p q -> String #

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

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

Defined in Predicate.Data.Either

type PP (EitherId p q :: Type) x

data LeftDef' p q r Source #

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

>>> pz @(LeftDef' 999 () Id) (Right "sdf")
Val 999
>>> pz @(LeftDef' 999 () Id) (Left 1)
Val 1

Instances

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

Defined in Predicate.Data.Either

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Either

Methods

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

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

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

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

Defined in Predicate.Data.Either

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

data RightDef' p q r Source #

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

>>> pz @(RightDef' 999 () Id) (Left "sdf")
Val 999
>>> pz @(RightDef' 999 Fst Snd) (999,Right 1)
Val 1

Instances

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

Defined in Predicate.Data.Either

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Either

Methods

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

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

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

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

Defined in Predicate.Data.Either

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

type families

type family EitherInT (p :: k) (y :: Type) (lr :: Type) where ... Source #

calculate the return type for EitherIn

Equations

EitherInT p y (Either a _) = PP p (y, a) 
EitherInT _ _ o = TypeError ('Text "EitherInT: expected 'Either a b' " :$$: ('Text "o = " :<>: 'ShowType o))