| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Diverse.Which
Contents
Description
Re-export Which without the constructor
- data Which xs
- impossible :: Which '[] -> a
- pick :: forall x xs. UniqueMember x xs => x -> Which xs
- pick0 :: x -> Which (x ': xs)
- pickOnly :: x -> Which '[x]
- pickL :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => x -> Which xs
- pickTag :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => x -> Which xs
- pickN :: forall n x xs. MemberAt n x xs => x -> Which xs
- obvious :: Which '[a] -> a
- trial :: forall x xs. UniqueMember x xs => Which xs -> Either (Which (Remove x xs)) x
- trial' :: forall x xs. UniqueMember x xs => Which xs -> Maybe x
- trial0 :: forall x xs. Which (x ': xs) -> Either (Which xs) x
- trial0' :: forall x xs. Which (x ': xs) -> Maybe x
- trialL :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => Which xs -> Either (Which (Remove x xs)) x
- trialL' :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => Which xs -> Maybe x
- trialTag :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => Which xs -> Either (Which (Remove (Tagged l x) xs)) x
- trialTag' :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => Which xs -> Maybe x
- trialN :: forall n x xs. MemberAt n x xs => Which xs -> Either (Which (RemoveIndex n xs)) x
- trialN' :: forall n x xs. MemberAt n x xs => Which xs -> Maybe x
- type Diversify branch tree = Reduce (Which branch) (Switcher (CaseDiversify branch tree) (Which tree) branch)
- diversify :: forall branch tree. Diversify branch tree => Which branch -> Which tree
- diversify' :: forall branch tree. (Diversify branch tree, SameLength branch tree) => Which branch -> Which tree
- diversify0 :: forall x xs. Which xs -> Which (x ': xs)
- diversifyL :: forall ls branch tree. (Diversify branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which branch -> Which tree
- type DiversifyN indices branch tree = (Reduce (Which branch) (SwitcherN (CaseDiversifyN indices) (Which tree) 0 branch), KindsAtIndices indices tree ~ branch)
- diversifyN :: forall indices branch tree. DiversifyN indices branch tree => Which branch -> Which tree
- type Reinterpret branch tree = Reduce (Which tree) (Switcher (CaseReinterpret branch tree) (Either (Which (Complement tree branch)) (Which branch)) tree)
- reinterpret :: forall branch tree. Reinterpret branch tree => Which tree -> Either (Which (Complement tree branch)) (Which branch)
- type Reinterpret' branch tree = Reduce (Which tree) (Switcher (CaseReinterpret' branch tree) (Maybe (Which branch)) tree)
- reinterpret' :: forall branch tree. Reinterpret' branch tree => Which tree -> Maybe (Which branch)
- reinterpretL :: forall ls branch tree. (Reinterpret branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which tree -> Either (Which (Complement tree branch)) (Which branch)
- reinterpretL' :: forall ls branch tree. (Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which tree -> Maybe (Which branch)
- type ReinterpretN' indices branch tree = (Reduce (Which tree) (SwitcherN (CaseReinterpretN' indices) (Maybe (Which branch)) 0 tree), KindsAtIndices indices tree ~ branch)
- reinterpretN' :: forall indices branch tree. ReinterpretN' indices branch tree => Which tree -> Maybe (Which branch)
- type Switch c r xs = Reduce (Which xs) (Switcher c r xs)
- newtype Switcher c r xs = Switcher (c r xs)
- which :: Switch c r xs => c r xs -> Which xs -> r
- switch :: Switch c r xs => Which xs -> c r xs -> r
- type SwitchN c r n xs = Reduce (Which xs) (SwitcherN c r n xs)
- newtype SwitcherN c r n xs = SwitcherN (c r n xs)
- whichN :: SwitchN c r n xs => c r n xs -> Which xs -> r
- switchN :: SwitchN c r n xs => Which xs -> c r n xs -> r
Which type
A Which is an anonymous sum type (also known as a polymorphic variant, or co-record)
 which can only contain one of the types in the typelist.
 This is essentially a typed version of Dynamic.
The following functions are available can be used to manipulate unique types in the typelist
These functions are type specified. This means labels are not required because the types themselves can be used to access the Which.
 It is a compile error to use those functions for duplicate fields.
For duplicate types in the list of possible types, Nat-indexed version of the functions are available:
- constructor: pickN
- destructor: trialN
- inejction: diversifyNandreinterpretN
- catamorphism: whichNorswitchN
Encoding: The variant contains a value whose type is at the given position in the type list. This is the same encoding as Haskus.Util.Variant and Data.Hlist.Variant.
The constructor is only exported in the Data.Diverse.Which.Internal module
Instances
| Reduce (Which ((:) Type x xs)) (Switcher * (CaseEqWhich *) Bool ((:) Type x xs)) => Eq (Which ((:) Type x xs)) Source # | Two  | 
| Eq (Which ([] Type)) Source # | ( | 
| (Reduce (Which ((:) Type x xs)) (Switcher * (CaseEqWhich *) Bool ((:) Type x xs)), Reduce (Which ((:) Type x xs)) (Switcher * (CaseOrdWhich *) Ordering ((:) Type x xs))) => Ord (Which ((:) Type x xs)) Source # | A  | 
| Ord (Which ([] Type)) Source # | ( | 
| WhichRead (Which_ ((:) Type x xs)) => Read (Which ((:) Type x xs)) Source # | This  | 
| Read (Which ([] Type)) Source # | Reading a 'Which '[]' value is always a parse error, considering 'Which '[]' as a data type with no constructors. | 
| Reduce (Which ((:) Type x xs)) (Switcher * (CaseShowWhich *) ShowS ((:) Type x xs)) => Show (Which ((:) Type x xs)) Source # | show ( | 
| Show (Which ([] Type)) Source # | |
| Generic (Which ((:) Type x ((:) Type x' xs))) Source # | A  | 
| Generic (Which ((:) Type x ([] Type))) Source # | A terminating  | 
| Generic (Which ([] Type)) Source # | A terminating  | 
| Semigroup (Which ([] Type)) Source # | |
| Reduce (Which ((:) Type x xs)) (Switcher * (CaseFunc NFData) () ((:) Type x xs)) => NFData (Which ((:) Type x xs)) Source # | |
| NFData (Which ([] Type)) Source # | |
| (Case (c r) ((:) Type x ([] Type)), (~) * r (CaseResult * Type (c r) x)) => Reduce (Which ((:) Type x ([] Type))) (Switcher * c r ((:) Type x ([] Type))) Source # | Terminating case of the loop, ensuring that a instance of  | 
| (Case (c r) ((:) Type x ((:) Type x' xs)), Reduce (Which ((:) Type x' xs)) (Switcher * c r ((:) Type x' xs)), Reiterate (c r) ((:) Type x ((:) Type x' xs)), (~) * r (CaseResult * Type (c r) x)) => Reduce (Which ((:) Type x ((:) Type x' xs))) (Switcher * c r ((:) Type x ((:) Type x' xs))) Source # | 
 | 
| Reduce (Which ([] Type)) (Switcher k c r ([] Type)) Source # | Allow 'Which '[]' to be  | 
| (Case (c r n) ((:) Type x ([] Type)), (~) * r (CaseResult * Type (c r n) x)) => Reduce (Which ((:) Type x ([] Type))) (SwitcherN * c r n ((:) Type x ([] Type))) Source # | Terminating case of the loop, ensuring that a instance of  | 
| (Case (c r n) ((:) Type x ((:) Type x' xs)), Reduce (Which ((:) Type x' xs)) (SwitcherN * c r ((+) n 1) ((:) Type x' xs)), ReiterateN (c r) n ((:) Type x ((:) Type x' xs)), (~) * r (CaseResult * Type (c r n) x)) => Reduce (Which ((:) Type x ((:) Type x' xs))) (SwitcherN * c r n ((:) Type x ((:) Type x' xs))) Source # | 
 | 
| type Rep (Which ((:) Type x ((:) Type x' xs))) Source # | |
| type Rep (Which ((:) Type x ([] Type))) Source # | |
| type Rep (Which ([] Type)) Source # | |
Single type
Construction
impossible :: Which '[] -> a Source #
Analogous to absurd. Renamed impossible to avoid conflicts.
Since 'Which '[]' values logically don't exist, this witnesses the logical reasoning tool of "ex falso quodlibet", ie "from falsehood, anything follows".
A 'Which '[]' is a Which with no alternatives, which may occur as a Left-over from trialing a Which '[x] with one type.
 It is an uninhabited type, just like Void
pick :: forall x xs. UniqueMember x xs => x -> Which xs Source #
pickL :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => x -> Which xs Source #
pickTag :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => x -> Which xs Source #
Destruction
trial' :: forall x xs. UniqueMember x xs => Which xs -> Maybe x Source #
Variation of trial which returns a Maybe
trial0' :: forall x xs. Which (x ': xs) -> Maybe x Source #
Variation of trial0 which returns a Maybe
trialL :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => Which xs -> Either (Which (Remove x xs)) x Source #
trialL' :: forall l x xs. (UniqueLabelMember l xs, x ~ KindAtLabel l xs) => Which xs -> Maybe x Source #
Variation of trialL which returns a Maybe
trialTag :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => Which xs -> Either (Which (Remove (Tagged l x) xs)) x Source #
trialTag' :: forall l x xs. (UniqueLabelMember l xs, Tagged l x ~ KindAtLabel l xs) => Which xs -> Maybe x Source #
trialN :: forall n x xs. MemberAt n x xs => Which xs -> Either (Which (RemoveIndex n xs)) x Source #
trialN' :: forall n x xs. MemberAt n x xs => Which xs -> Maybe x Source #
Variation of trialN which returns a Maybe
Multiple types
Injection
type Diversify branch tree = Reduce (Which branch) (Switcher (CaseDiversify branch tree) (Which tree) branch) Source #
A friendlier constraint synonym for diversify.
diversify :: forall branch tree. Diversify branch tree => Which branch -> Which tree Source #
Convert a Which to another Which that may include other possibilities.
 That is, branch is equal or is a subset of tree.
This can also be used to rearrange the order of the types in the Which.
It is a compile error if tree has duplicate types with branch.
NB. Use TypeApplications with _ to specify tree@.
let a =pick'(5 :: Int) ::Which'[Int] b =diversify@_ @[Int, Bool] a ::Which'[Int, Bool] c =diversify@_ @[Bool, Int] b ::Which'[Bool, Int]
diversify' :: forall branch tree. (Diversify branch tree, SameLength branch tree) => Which branch -> Which tree Source #
A restricted version of diversify which only rearranges the types
diversify0 :: forall x xs. Which xs -> Which (x ': xs) Source #
A simple version of diversify which add another type to the front of the typelist.
diversifyL :: forall ls branch tree. (Diversify branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which branch -> Which tree Source #
A variation of diversify where branchis additionally specified by a labels list.
let y =pickOnly(5 :: Tagged Bar Int) y' =diversifyL@'[Bar] y ::Which'[Tagged Bar Int, Tagged Foo Bool] y'' =diversifyL@'[Bar, Foo] y' ::Which'[Tagged Foo Bool, Tagged Bar Int]switchy'' (CaseFunc@Typeable(show . typeRep . (pure @Proxy))) `shouldBe` "Tagged * Bar Int"
type DiversifyN indices branch tree = (Reduce (Which branch) (SwitcherN (CaseDiversifyN indices) (Which tree) 0 branch), KindsAtIndices indices tree ~ branch) Source #
A friendlier constraint synonym for diversifyN.
diversifyN :: forall indices branch tree. DiversifyN indices branch tree => Which branch -> Which tree Source #
A variation of diversify which uses a Nat list indices to specify how to reorder the fields, where
indices[branch_idx] = tree_idx
This variation allows tree to contain duplicate types with branch since
 the mapping is specified by indicies.
let y =pickOnly(5 :: Int) y' =diversifyN@'[0] @_ @[Int, Bool] y y'' =diversifyN@[1,0] @_ @[Bool, Int] y'switchy'' (CaseFunc@Typeable(show . typeRep . (pure @Proxy))) `shouldBe` "Int"
Inverse Injection
type Reinterpret branch tree = Reduce (Which tree) (Switcher (CaseReinterpret branch tree) (Either (Which (Complement tree branch)) (Which branch)) tree) Source #
A friendlier constraint synonym for reinterpret.
reinterpret :: forall branch tree. Reinterpret branch tree => Which tree -> Either (Which (Complement tree branch)) (Which branch) Source #
Convert a Which into possibly another Which with a totally different typelist.
 Returns either a Which with the Right value, or a Which with the Leftover compliment types.
It is a compile error if branch or compliment has duplicate types with tree.
NB. forall used to specify branch first, so TypeApplications can be used to specify branch first.
let a =pick@[Int, Char, Bool] (5 :: Int) ::Which'[Int, Char, Bool] let b =reinterpret[String, Char] y b `shouldBe` Left ([String, Int] a c `shouldBe` Right (pick(5 :: Int)) ::Which'[Int, Bool] let c =reinterpretpick(5 :: Int)) ::Which'[String, Int]
type Reinterpret' branch tree = Reduce (Which tree) (Switcher (CaseReinterpret' branch tree) (Maybe (Which branch)) tree) Source #
A friendlier constraint synonym for reinterpret'.
reinterpret' :: forall branch tree. Reinterpret' branch tree => Which tree -> Maybe (Which branch) Source #
Variation of reinterpret which returns a Maybe.
reinterpretL :: forall ls branch tree. (Reinterpret branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which tree -> Either (Which (Complement tree branch)) (Which branch) Source #
A variation of reinterpret where the branch is additionally specified with a labels list.
let y =pick@[Tagged Bar Int, Tagged Foo Bool, Tagged Hi Char, Tagged Bye Bool] (5 :: Tagged Bar Int) y' =reinterpretL@[Foo, Bar] y x =pick@[Tagged Foo Bool, Tagged Bar Int] (5 :: Tagged Bar Int) y' `shouldBe` Right x
reinterpretL' :: forall ls branch tree. (Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) => Which tree -> Maybe (Which branch) Source #
Variation of reinterpretL which returns a Maybe.
type ReinterpretN' indices branch tree = (Reduce (Which tree) (SwitcherN (CaseReinterpretN' indices) (Maybe (Which branch)) 0 tree), KindsAtIndices indices tree ~ branch) Source #
A friendlier constraint synonym for reinterpretN.
reinterpretN' :: forall indices branch tree. ReinterpretN' indices branch tree => Which tree -> Maybe (Which branch) Source #
A limited variation of reinterpret which uses a Nat list n to specify how to reorder the fields, where
indices[branch_idx] = tree_idx
This variation allows tree to contain duplicate types with branch
 since the mapping is specified by indicies.
However, unlike reinterpert, in this variation,
 branch must be a subset of tree instead of any arbitrary Which.
 Also it returns a Maybe instead of Either.
This is so that the same indices can be used in narrowN.
Catamorphism
type Switch c r xs = Reduce (Which xs) (Switcher c r xs) Source #
A friendlier constraint synonym for switch.
newtype Switcher c r xs Source #
Switcher is an instance of Reduce for which reiterates through the possibilities in a Which,
 delegating handling to Case, ensuring termination when Which only contains one type.
Constructors
| Switcher (c r xs) | 
Instances
| (Case (c r) ((:) Type x ([] Type)), (~) * r (CaseResult * Type (c r) x)) => Reduce (Which ((:) Type x ([] Type))) (Switcher * c r ((:) Type x ([] Type))) Source # | Terminating case of the loop, ensuring that a instance of  | 
| (Case (c r) ((:) Type x ((:) Type x' xs)), Reduce (Which ((:) Type x' xs)) (Switcher * c r ((:) Type x' xs)), Reiterate (c r) ((:) Type x ((:) Type x' xs)), (~) * r (CaseResult * Type (c r) x)) => Reduce (Which ((:) Type x ((:) Type x' xs))) (Switcher * c r ((:) Type x ((:) Type x' xs))) Source # | 
 | 
| Reduce (Which ([] Type)) (Switcher k c r ([] Type)) Source # | Allow 'Which '[]' to be  | 
| type Reduced (Switcher * c r xs) Source # | |
switch :: Switch c r xs => Which xs -> c r xs -> r Source #
A switch/case statement for Which. This is equivalent to flip which
Use Case instances like Cases to apply a Which of functions to a variant of values.
let y =pick(5 :: Int) ::Which'[Int, Bool]switchy (cases(show @Bool./show @Int./nil)) `shouldBe` "5"
Or CaseFunc @Typeable to apply a polymorphic function that work on all Typeables.
let y =pick(5 :: Int) ::Which'[Int, Bool]switchy (CaseFunc@Typeable(show . typeRep . (pure @Proxy))) `shouldBe` Int
Or you may use your own custom instance of Case.
type SwitchN c r n xs = Reduce (Which xs) (SwitcherN c r n xs) Source #
A friendlier constraint synonym for switch.
newtype SwitcherN c r n xs Source #
SwitcherN is a variation of Switcher which reiterateNs through the possibilities in a Which,
 delegating work to CaseN, ensuring termination when Which only contains one type.
Constructors
| SwitcherN (c r n xs) | 
Instances
| (Case (c r n) ((:) Type x ([] Type)), (~) * r (CaseResult * Type (c r n) x)) => Reduce (Which ((:) Type x ([] Type))) (SwitcherN * c r n ((:) Type x ([] Type))) Source # | Terminating case of the loop, ensuring that a instance of  | 
| (Case (c r n) ((:) Type x ((:) Type x' xs)), Reduce (Which ((:) Type x' xs)) (SwitcherN * c r ((+) n 1) ((:) Type x' xs)), ReiterateN (c r) n ((:) Type x ((:) Type x' xs)), (~) * r (CaseResult * Type (c r n) x)) => Reduce (Which ((:) Type x ((:) Type x' xs))) (SwitcherN * c r n ((:) Type x ((:) Type x' xs))) Source # | 
 | 
| type Reduced (SwitcherN * c r n xs) Source # | |
switchN :: SwitchN c r n xs => Which xs -> c r n xs -> r Source #
A switch/case statement for Which. This is equivalent to flip whichN
Use Case instances like CasesN to apply a Which of functions to a variant of values
 in index order.
let y =pickN@0 (5 :: Int) ::Which'[Int, Bool, Bool, Int]switchNy (casesN(show @Int./show @Bool./show @Bool./show @Int./nil)) `shouldBe` "5"
Or you may use your own custom instance of Case.