| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Elr
Description
Elr related methods
Synopsis
- data ENone'
- data ELeft'
- data ERight'
- data EBoth'
- data ElrIn n p q r s t
- data ElrId n p q r
- data ElrPair s t
- data ElrInSimple n p q r
- data PartitionElr
- data ENoneDef p q r
- data ELeftDef p q r
- data ERightDef p q r
- data EBothDef p q r
- data MkENone (t :: Type) (t1 :: Type)
- data MkELeft (t :: Type) p
- data MkERight (t :: Type) p
- data MkEBoth p q
- data MkENone' t t1
- data MkELeft' t p
- data MkERight' t p
- data IsENone
- data IsELeft
- data IsERight
- data IsEBoth
- data These2Elr
- data Elr2These
- data Elr2Maybe
destructors
tries to extract a () from the ENone constructor
>>>pz @ENone' ENoneVal ()
>>>pz @ENone' (ERight 'a')Fail "ENone' found ERight"
tries to extract a value from the ELeft constructor
>>>pz @(ELeft' >> Succ) (ELeft 20)Val 21
>>>pz @(ELeft' >> Succ) (ERight 'a')Fail "ELeft' found ERight"
tries to extract a value from the ERight constructor
>>>pz @(ERight' >> Succ) (ERight 20)Val 21
>>>pz @(ERight' >> Succ) (ELeft 'a')Fail "ERight' found ELeft"
tries to extract the values from the EBoth constructor
>>>pz @(EBoth' >> Second Succ) (EBoth 1 'a')Val (1,'b')
>>>pz @(ERight' >> Succ) (ELeft 'a')Fail "ERight' found ELeft"
>>>pz @(EBoth' >> Second Succ) (ERight 8)Fail "EBoth' found ERight"
data ElrIn n p q r s t Source #
destructs an Elr value
n ENone receives (PP s x)
p ELeft a receives (PP s x,a)
q ERight b receives (PP s x,b)
r EBoth a b receives (PP s x,(a,b))
s points to the environment you want to pass in
t points to the Elr value
>>>pz @(ElrIn Id '(Snd,L12) '(L11,Snd) Snd Fst Snd) ((999,'a'), EBoth 12 'x')Val (12,'x')
>>>pz @(ElrIn Id '(Snd,L12) '(L11,Snd) Snd Fst Snd) ((999,'a'), ENone)Val (999,'a')
>>>pz @(ElrIn Id '(Snd,L12) '(L11,Snd) Snd Fst Snd) ((999,'a'), ERight 'z')Val (999,'z')
>>>pz @(ElrIn 999 Snd (Snd >> Len) (Snd >> Fst + Length Snd) () Id) (ELeft 13)Val 13
>>>pz @(ElrIn 999 Snd (Snd >> Len) (Snd >> Fst + Length Snd) () Id) (ERight "abcdef")Val 6
>>>pl @(ElrIn "none" "left" "right" "both" () Id) (ELeft (SG.Sum 12))Present "left" (ElrIn(ELeft) "left" | Sum {getSum = 12}) Val "left"
>>>pl @(ElrIn '("",2) '(Snd,999) '("no value",Snd) Snd () Id) (EBoth "Ab" 13)Present ("Ab",13) (ElrIn(EBoth) ("Ab",13) | ("Ab",13)) Val ("Ab",13)
>>>pl @(ElrIn '("",2) '(Snd,999) '("no value",Snd) Snd () Id) (ELeft "Ab")Present ("Ab",999) (ElrIn(ELeft) ("Ab",999) | "Ab") Val ("Ab",999)
>>>pl @(ElrIn '("",2) '(Snd,999) '("no value",Snd) Snd () Id) ENonePresent ("",2) (ElrIn(ENone) ("",2) | ()) Val ("",2)
>>>pl @(ElrIn (FailT _ "none found") '(Snd,"fromleft") '(888,Snd) Snd () Id) ENoneError none found (ElrIn(ENone) n failed) Fail "none found"
Instances
| (Show a, Show b, Show (PP r (y, (a, b))), P n y, P p (y, a), P q (y, b), P r (y, (a, b)), PP n y ~ PP p (y, a), PP p (y, a) ~ PP q (y, b), PP q (y, b) ~ PP r (y, (a, b)), P s x, P t x, PP t x ~ Elr a b, PP s x ~ y) => P (ElrIn n p q r s t :: Type) x Source # | |
| Show (ElrIn n p q r s t) Source # | |
| type PP (ElrIn n p q r s t :: Type) x Source # | |
simple version of ElrIn with Id as the Elr value and the environment set to ()
>>>pz @(ElrId '(999,"oops") '(Id,"fromleft") '(888,Id) Id) (EBoth 222 "ok")Val (222,"ok")
>>>pz @(ElrId '(999,"oops") '(Id,"fromleft") '(888,Id) Id) (ERight "ok")Val (888,"ok")
>>>pz @(ElrId '(999,"oops") '(Id,"fromleft") '(888,Id) Id) ENoneVal (999,"oops")
>>>pz @(ElrId '(999,"oops") '(Id,"fromleft") '(888,Id) Id) (ELeft 123)Val (123,"fromleft")
>>>pl @(ElrId (FailT _ "none found") '(Id,"fromleft") '(888,Id) Id) ENoneError none found (ElrIn(ENone) n failed) Fail "none found"
creates a pair where the values are filled in by s and t holds the Elr value
>>>pz @(ElrPair Fst Snd) ((999,"oops"),EBoth 2 "xx")Val (2,"xx")
>>>pz @(ElrPair Fst Snd) ((999,"oops"),ENone)Val (999,"oops")
>>>pz @(ElrPair Fst Snd) ((999,"oops"),ERight "ok")Val (999,"ok")
data ElrInSimple n p q r Source #
similar to ElrIn but without an environment s and uses Id for t
>>>pz @(ElrInSimple 999 Id Len (Fst + Length Snd)) (ELeft 13)Val 13
>>>pz @(ElrInSimple 999 Id Len (Fst + Length Snd)) ENoneVal 999
>>>pz @(ElrInSimple 999 Id Len (Fst + Length Snd)) (ERight "this is a long string")Val 21
>>>pz @(ElrInSimple 999 Id Len (Fst + Length Snd)) (EBoth 20 "somedata")Val 28
>>>pz @(ElrInSimple (FailT _ "err") (MkLeft _ Id) (MkRight _ Id) (If (Fst > Length Snd) (MkLeft _ Fst) (MkRight _ Snd))) (ERight "this is a long string")Val (Right "this is a long string")
>>>pz @(ElrInSimple (FailT _ "err") (MkLeft _ Id) (MkRight _ Id) (If (Fst > Length Snd) (MkLeft _ Fst) (MkRight _ Snd))) ENoneFail "err"
>>>pz @(ElrInSimple (FailT _ "err") (MkLeft _ Id) (MkRight _ Id) (If (Fst > Length Snd) (MkLeft _ Fst) (MkRight _ Snd))) (EBoth 1 "this is a long string")Val (Right "this is a long string")
>>>pz @(ElrInSimple (FailT _ "err") (MkLeft _ Id) (MkRight _ Id) (If (Fst > Length Snd) (MkLeft _ Fst) (MkRight _ Snd))) (EBoth 100 "this is a long string")Val (Left 100)
>>>pl @(ElrInSimple "none" "left" "right" "both") (ELeft (SG.Sum 12))Present "left" (ElrIn(ELeft) "left" | Sum {getSum = 12}) Val "left"
>>>pl @(ElrInSimple (FailT _ "err") (Id &&& 999) ("no value" &&& Id) Id) (EBoth "Ab" 13)Present ("Ab",13) (ElrIn(EBoth) ("Ab",13) | ("Ab",13)) Val ("Ab",13)
>>>pl @(ElrInSimple (FailT _ "err") (Id &&& 999) ("no value" &&& Id) Id) (ELeft "Ab")Present ("Ab",999) (ElrIn(ELeft) ("Ab",999) | "Ab") Val ("Ab",999)
>>>pl @(ElrInSimple (FailT _ "err") (Id &&& 999) ("no value" &&& Id) Id) (ERight 13)Present ("no value",13) (ElrIn(ERight) ("no value",13) | 13) Val ("no value",13)
Instances
| P (ElrInSimpleT n p q r) x => P (ElrInSimple n p q r :: Type) x Source # | |
Defined in Predicate.Data.Elr Associated Types type PP (ElrInSimple n p q r) x Source # Methods eval :: MonadEval m => proxy (ElrInSimple n p q r) -> POpts -> x -> m (TT (PP (ElrInSimple n p q r) x)) Source # | |
| Show (ElrInSimple n p q r) Source # | |
Defined in Predicate.Data.Elr Methods showsPrec :: Int -> ElrInSimple n p q r -> ShowS # show :: ElrInSimple n p q r -> String # showList :: [ElrInSimple n p q r] -> ShowS # | |
| type PP (ElrInSimple n p q r :: Type) x Source # | |
Defined in Predicate.Data.Elr | |
data PartitionElr Source #
similar to PartitionThese for Elr. returns a 4-tuple with the results so use Fst Snd Thd L4 to extract
>>>pz @PartitionElr [ELeft 'a', ENone, ERight 2, ELeft 'c', EBoth 'z' 1, ERight 4, EBoth 'a' 2, ERight 99, ENone]Val ([(),()],"ac",[2,4,99],[('z',1),('a',2)])
>>>pz @PartitionElr [ELeft 4, ERight 'x', ERight 'y',EBoth 3 'b', ELeft 99, EBoth 5 'x']Val ([],[4,99],"xy",[(3,'b'),(5,'x')])
>>>pz @PartitionElr [ENone,ELeft 1,ERight 'x',ELeft 4,ERight 'y',EBoth 9 'z',ELeft 10,EBoth 8 'y']Val ([()],[1,4,10],"xy",[(9,'z'),(8,'y')])
Instances
| Show PartitionElr Source # | |
Defined in Predicate.Data.Elr Methods showsPrec :: Int -> PartitionElr -> ShowS # show :: PartitionElr -> String # showList :: [PartitionElr] -> ShowS # | |
| (Show a, Show b) => P PartitionElr [Elr a b] Source # | |
Defined in Predicate.Data.Elr Associated Types type PP PartitionElr [Elr a b] Source # | |
| type PP PartitionElr [Elr a b] Source # | |
Defined in Predicate.Data.Elr | |
get ENone or run p: really only useful when p is set to Fail: where q is the environment and r is the Elr value
>>>pz @(ENoneDef (FailT _ "not ENone") () Id) ENoneVal ()
>>>pz @(ENoneDef (FailT _ "not ENone") () Id) (ELeft 1)Fail "not ENone"
>>>pz @(ENoneDef (FailT _ Id) Fst Snd) ("not right",EBoth 1 2)Fail "not right"
get ELeft or use the default value p: q is the environment and r is the Elr value
>>>pz @(ELeftDef Id Fst Snd) (999,ENone)Val 999
>>>pz @(ELeftDef 999 () Id) (ERight "sdf")Val 999
>>>pz @(ELeftDef 999 () Id) (ELeft 1)Val 1
get ERight or use the default value p: q is the environment and r is the Elr value
>>>pz @(ERightDef 999 () Id) ENoneVal 999
>>>pz @(ERightDef 999 () Id) (ELeft "sdf")Val 999
>>>pz @(ERightDef 999 Fst Snd) (999,ERight 1)Val 1
get EBoth or use the default value p: q is the environment and r is the Elr value
>>>pz @(EBothDef '(999,"xx") () Id) ENoneVal (999,"xx")
>>>pz @(EBothDef '(999,"xx") () Id) (ERight "abc")Val (999,"xx")
>>>pz @(EBothDef '(999,"xx") () Id) (ELeft 1)Val (999,"xx")
>>>pz @(EBothDef '(999,"xx") () Id) (EBoth 1 "abc")Val (1,"abc")
>>>pz @(EBothDef Id Fst Snd) ((999,"xx"),ENone)Val (999,"xx")
constructors
data MkENone (t :: Type) (t1 :: Type) Source #
ENone constructor
>>>pl @(MkENone () Id) 'x'Present ENone (MkENone) Val ENone
data MkELeft (t :: Type) p Source #
ELeft constructor
>>>pl @(MkELeft () Id) 'x'Present ELeft 'x' (MkELeft) Val (ELeft 'x')
>>>pl @(MkELeft () Fst) ('x',True)Present ELeft 'x' (MkELeft) Val (ELeft 'x')
>>>pz @(MkELeft _ Id) 44Val (ELeft 44)
data MkERight (t :: Type) p Source #
ERight constructor
>>>pz @(MkERight _ Id) 44Val (ERight 44)
>>>pz @(MkERight _ "Abc" <> MkELeft _ '[1,2] <> MkEBoth [3,4] "def") ()Val (EBoth [1,2,3,4] "Abcdef")
>>>pl @(MkERight () Id) 'x'Present ERight 'x' (MkERight) Val (ERight 'x')
EBoth constructor
>>>pz @(MkEBoth Fst Snd) (44,'x')Val (EBoth 44 'x')
>>>pl @(MkEBoth Id 'True) 'x'Present EBoth 'x' True (MkEBoth) Val (EBoth 'x' True)
>>>pz @(MkENone _ _ <> MkELeft _ '[1] <> MkERight _ "abc" <> MkELeft _ '[2] <> MkEBoth '[3,4,5] "def") ()Val (EBoth [1,2,3,4,5] "abcdef")
ENone constructor
>>>pz @(Proxy Int >> MkENone' UnproxyT 10) []Val ENone
ELeft constructor
>>>pz @(Proxy Int >> MkELeft' UnproxyT 10) []Val (ELeft 10)
similar to MkERight where t references the type
predicates
predicate on ELeft
>>>pz @IsELeft (ELeft "aBc")Val True
>>>pz @IsELeft (EBoth 1 'a')Val False
>>>pl @IsELeft (ELeft 12)True (IsELeft | ELeft 12) Val True
predicate on ERight
>>>pl @IsERight (ELeft 12)False (IsERight | ELeft 12) Val False
predicate on EBoth
>>>pl @IsEBoth (ELeft 12)False (IsEBoth | ELeft 12) Val False
>>>pz @IsEBoth (EBoth 1 'a')Val True
>>>pl @IsEBoth (EBoth 'x' 12)True (IsEBoth | EBoth 'x' 12) Val True
>>>pl @IsEBoth (ERight (SG.Sum 12))False (IsEBoth | ERight (Sum {getSum = 12})) Val False
>>>pl @IsEBoth (EBoth 1 (SG.Sum 12))True (IsEBoth | EBoth 1 (Sum {getSum = 12})) Val True
converters
>>>pz @These2Elr (These 12 'x')Val (EBoth 12 'x')
>>>pz @These2Elr (This 123)Val (ELeft 123)
>>>pz @Elr2These ENoneVal Nothing
>>>pz @Elr2These (ELeft 123)Val (Just (This 123))
converts Elr to a pair of Maybes
>>>pz @Elr2Maybe ENoneVal (Nothing,Nothing)
>>>pz @Elr2Maybe (ELeft 123)Val (Just 123,Nothing)
>>>pz @Elr2Maybe (EBoth 'x' 123)Val (Just 'x',Just 123)
>>>pz @Elr2Maybe (ERight 123)Val (Nothing,Just 123)