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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Either

Contents

Description

promoted Either functions

Synopsis

boolean predicates

data IsLeft p Source #

similar to isLeft

>>> pz @(IsLeft Id) (Right 123)
FalseT
>>> pz @(IsLeft Id) (Left 'a')
TrueT
Instances
(P p x, PP p x ~ Either a b) => P (IsLeft p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Either

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

data IsRight p Source #

similar to isRight

>>> pz @(IsRight Id) (Right 123)
TrueT
>>> pz @(IsRight Id) (Left "aa")
FalseT
Instances
(P p x, PP p x ~ Either a b) => P (IsRight p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Either

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

constructors

data MkLeft (t :: Type) p Source #

Left constructor

>>> pz @(MkLeft _ Id) 44
PresentT (Left 44)
Instances
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 :: 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.Data.Either

type PP (MkLeft t p :: Type) x

data MkLeft' t p Source #

Left constructor

Instances
(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 :: 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.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
PresentT (Right 44)
Instances
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 :: 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.Data.Either

type PP (MkRight t p :: Type) x

data MkRight' t p Source #

Right constructor

Instances
(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 :: 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.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 Id) (Left 20)
PresentT 21
>>> pz @(Left' >> Succ Id) (Right 'a')
FailT "Left' found Right"
Instances
Show a => P Left' (Either a x) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Left' (Either a x) :: Type 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 Id) (Right 20)
PresentT 21
>>> pz @(Right' >> Succ Id) (Left 'a')
FailT "Right' found Left"
Instances
Show a => P Right' (Either x a) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Right' (Either x a) :: Type 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)
PresentT (102 % 5)
>>> pz @(LeftDef (1 % 4) Id) (Right "aa")
PresentT (1 % 4)
>>> pz @(LeftDef (PrintT "found right=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Right "xy")
PresentT "found right=xy fst=123"
>>> pz @(LeftDef (MEmptyT _) Id) (Right 222)
PresentT ()
>>> pz @(LeftDef (MEmptyT (SG.Sum _)) Id) (Right 222)
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.Data.Either

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.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)
PresentT 20.4
>>> pz @(LeftFail "oops" Id) (Right "aa")
FailT "oops"
>>> pz @(LeftFail (PrintT "found right=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Right "xy")
FailT "found right=xy fst=123"
>>> pz @(LeftFail (MEmptyT _) Id) (Right 222)
FailT ""
>>> pl @(LeftFail (PrintF "someval=%d" (Fst (Snd Id))) (Snd Id)) (13::Int,Right @(SG.Sum Int) "abc")
Error someval=13 (LeftFail Right)
FailT "someval=13"
>>> pl @(LeftFail (PrintF "someval=%s" (Fst Id)) Id) (Right @(SG.Sum Int) ("abc" :: String))
Error someval=abc (LeftFail Right)
FailT "someval=abc"
>>> pl @(LeftFail (PrintF "found rhs=%d" (Fst Id)) Id) (Right @String @Int 10)
Error found rhs=10 (LeftFail Right)
FailT "found rhs=10"
>>> pl @(LeftFail (PrintF "found rhs=%d" (Snd Id >> Snd Id >> Snd Id)) (Snd Id >> Fst Id)) ('x',(Right 10,23::Int))
Error found rhs=23 (LeftFail Right)
FailT "found rhs=23"
>>> pl @(LeftFail (PrintF "found rhs=%d" (Snd (Snd (Snd Id)))) (Fst (Snd Id))) ('x',(Left "abc",23::Int))
Present "abc" (Left)
PresentT "abc"
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.Data.Either

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

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.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)
PresentT 20.4
>>> pz @(RightFail "oops" Id) (Left "aa")
FailT "oops"
>>> pz @(RightFail (PrintT "found left=%s fst=%d" '(Fst Id,Fst (Snd Id))) (Snd Id)) (123,Left "xy")
FailT "found left=xy fst=123"
>>> pz @(RightFail (MEmptyT _) Id) (Left 222)
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.Data.Either

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.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 Id > 4) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (24,(-1,999))
PresentT (Right 999)
>>> pz @(EitherBool (Fst Id > 4) (Fst (Snd Id)) (Snd (Snd Id))) (1,(-1,999))
PresentT (Left (-1))
>>> pl @(EitherBool (Fst Id > 10) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (7,('x',99))
Present Left 'x' (EitherBool(False) Left 'x')
PresentT (Left 'x')
>>> pl @(EitherBool (Fst Id > 10) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (11,('x',99))
Present Right 99 (EitherBool(True) Right 99)
PresentT (Right 99)
>>> pl @(EitherBool (Gt 10) "found left" 99) 12
Present Right 99 (EitherBool(True) Right 99)
PresentT (Right 99)
>>> pl @(EitherBool (Gt 10) "found left" 99) 7
Present Left "found left" (EitherBool(False) Left "found left")
PresentT (Left "found left")
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.Data.Either

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

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

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

data PartitionEithers Source #

similar to partitionEithers

>>> pz @PartitionEithers [Left 'a',Right 2,Left 'c',Right 4,Right 99]
PresentT ("ac",[2,4,99])
>>> pz @PartitionEithers [Right 2,Right 4,Right 99]
PresentT ([],[2,4,99])
>>> pz @PartitionEithers [Left 'a',Left 'c']
PresentT ("ac",[])
>>> pz @PartitionEithers ([] :: [Either () Int])
PresentT ([],[])
>>> 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])
PresentT ([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])
PresentT ("xabz",[1,10])
Instances
(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] :: 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.Data.Either

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

miscellaneous

data p ||| q infixr 2 Source #

similar |||

>>> pz @(Pred Id ||| Id) (Left 13)
PresentT 12
>>> pz @(ShowP Id ||| Id) (Right "hello")
PresentT "hello"
>>> pl @('True ||| 'False) (Left "someval")
True ((|||) Left True | "someval")
TrueT
>>> pl @('True ||| 'False) (Right "someval")
False ((|||) Right False | "someval")
FalseT
>>> pl @(ShowP (Succ Id) ||| ShowP Id) (Left 123)
Present "124" ((|||) Left "124" | 123)
PresentT "124"
>>> pl @(ShowP (Succ Id) ||| ShowP Id) (Right True)
Present "True" ((|||) Right "True" | True)
PresentT "True"
>>> pl @(EitherIn (Not Id) Id) (Right True)
Present True ((|||) Right True | True)
PresentT True
>>> pl @(EitherIn (Not Id) Id) (Left True)
False ((|||) Left False | True)
FalseT
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.Data.Either

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

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

data p +++ q infixr 2 Source #

similar +++

>>> pz @(Pred Id +++ Id) (Left 13)
PresentT (Left 12)
>>> pz @(ShowP Id +++ Reverse) (Right "hello")
PresentT (Right "olleh")
>>> pl @(HeadDef 'False Id +++ Id) (Right @[Bool] 1) -- need @[Bool] cos we said 'False!
Present Right 1 ((+++) Right 1 | 1)
PresentT (Right 1)
>>> pl @(HeadDef 'False Id +++ Id) (Left [True,False]) -- need @[Bool] cos we said 'False!
Present Left True ((+++) Left True | [True,False])
PresentT (Left True)
>>> pl @(Not Id +++ Id) (Right True)
Present Right True ((+++) Right True | True)
PresentT (Right True)
>>> pl @(Not Id +++ Id) (Right 12)
Present Right 12 ((+++) Right 12 | 12)
PresentT (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)
PresentT (Right 1)
>>> pl @(HeadDef () Id +++ Id) (Right @[()] 1) -- this breaks! cos Left doesnt have a type
Present Right 1 ((+++) Right 1 | 1)
PresentT (Right 1)
>>> pl @(Not Id +++ Id) (Right @Bool 12)
Present Right 12 ((+++) Right 12 | 12)
PresentT (Right 12)
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.Data.Either

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

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