Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Which (xs :: [Type]) = Which !Int Any
- impossible :: Which '[] -> a
- impossible' :: Which '[Void] -> 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. UniqueMember (Tagged l x) 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. UniqueMember (Tagged l x) xs => Which xs -> Either (Which (Remove (Tagged l x) xs)) x
- trialTag' :: forall l x xs. UniqueMember (Tagged l x) 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
- pattern W :: forall x xs. UniqueMember x xs => x -> Which xs
- type Diversify (branch :: [Type]) (tree :: [Type]) = Switch (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)
- type DiversifyL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls)
- diversifyL :: forall ls branch tree. DiversifyL ls branch tree => Which branch -> Which tree
- type DiversifyN (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (SwitchN Which (CaseDiversifyN ns) (Which tree) 0 branch, KindsAtIndices ns tree ~ branch)
- diversifyN :: forall ns branch tree. DiversifyN ns branch tree => Which branch -> Which tree
- type Reinterpret (branch :: [Type]) (tree :: [Type]) = Switch (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 :: [Type]) (tree :: [Type]) = Switch (CaseReinterpret' branch tree) (Maybe (Which branch)) tree
- reinterpret' :: forall branch tree. Reinterpret' branch tree => Which tree -> Maybe (Which branch)
- type ReinterpretL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Reinterpret branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls)
- reinterpretL :: forall ls branch tree. ReinterpretL ls branch tree => Which tree -> Either (Which (Complement tree branch)) (Which branch)
- type ReinterpretL' (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls)
- reinterpretL' :: forall ls branch tree. ReinterpretL' ls branch tree => Which tree -> Maybe (Which branch)
- type ReinterpretN' (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (SwitchN Which (CaseReinterpretN' ns) (Maybe (Which branch)) 0 tree, KindsAtIndices ns tree ~ branch)
- reinterpretN' :: forall ns branch tree. ReinterpretN' ns branch tree => Which tree -> Maybe (Which branch)
- type Switch c r xs = Reduce (Which xs) (Switcher c r xs)
- switch :: Switch c r xs => Which xs -> c r xs -> r
- which :: Switch c r xs => c r xs -> Which xs -> r
- newtype Switcher c r (xs :: [Type]) = Switcher (c r xs)
- class SwitchN w c r (n :: Nat) xs
- switchN :: SwitchN w c r n xs => w xs -> c r n xs -> r
- whichN :: SwitchN w c r n xs => c r n xs -> w xs -> r
- newtype SwitcherN c r (n :: Nat) (xs :: [Type]) = SwitcherN (c r n xs)
Which
type
data Which (xs :: [Type]) Source #
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:
diversifyN
andreinterpretN
- catamorphism:
whichN
orswitchN
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
Which !Int Any |
Instances
ATraversable Which c m ('[] :: [Type]) Source # | |
Defined in Data.Diverse.Which.Internal atraverse :: forall (xs' :: [Type]). (Applicative m, IsTraversalCase c, xs' ~ TraverseResults c m '[]) => c m '[] -> Which '[] -> m (Which xs') Source # | |
(Reiterate (c m) (a ': as), ATraversable Which c m as, Case (c m) (a ': as)) => ATraversable Which c m (a ': as) Source # | |
Defined in Data.Diverse.Which.Internal atraverse :: forall (xs' :: [Type]). (Applicative m, IsTraversalCase c, xs' ~ TraverseResults c m (a ': as)) => c m (a ': as) -> Which (a ': as) -> m (Which xs') Source # | |
AFunctor Which c ('[] :: [Type]) Source # | Terminating AFunctor instance for empty type list |
Defined in Data.Diverse.Which.Internal | |
(Reiterate c (a ': as), AFunctor Which c as, Case c (a ': as)) => AFunctor Which c (a ': as) Source # | Recursive AFunctor instance for non empty type list delegate afmap'ing the remainder to an instance of Collector' with one less type in the type list |
Defined in Data.Diverse.Which.Internal | |
Semigroup (Which ('[] :: [Type])) Source # | |
Generic (Which (x ': (x' ': xs))) Source # | A |
Generic (Which '[x]) Source # | A terminating |
Generic (Which ('[] :: [Type])) Source # | A terminating |
WhichRead (Which (x ': xs)) => Read (Which (x ': xs)) Source # | This |
Defined in Data.Diverse.Which.Internal | |
Switch (CaseShowWhich :: Type -> [Type] -> TYPE LiftedRep) ShowS (x ': xs) => Show (Which (x ': xs)) Source # | show ( |
Show (Which ('[] :: [Type])) Source # | |
Reduce (Which (x ': xs)) (Switcher (CaseFunc NFData) () (x ': xs)) => NFData (Which (x ': xs)) Source # | |
Defined in Data.Diverse.Which.Internal | |
NFData (Which ('[] :: [Type])) Source # | |
Defined in Data.Diverse.Which.Internal | |
Switch (CaseEqWhich :: Type -> [Type] -> Type) Bool (x ': xs) => Eq (Which (x ': xs)) Source # | Two |
Eq (Which ('[] :: [Type])) Source # | ( |
(Switch (CaseEqWhich :: Type -> [Type] -> Type) Bool (x ': xs), Switch (CaseOrdWhich :: Type -> [Type] -> Type) Ordering (x ': xs)) => Ord (Which (x ': xs)) Source # | A |
Defined in Data.Diverse.Which.Internal compare :: Which (x ': xs) -> Which (x ': xs) -> Ordering (<) :: Which (x ': xs) -> Which (x ': xs) -> Bool (<=) :: Which (x ': xs) -> Which (x ': xs) -> Bool (>) :: Which (x ': xs) -> Which (x ': xs) -> Bool (>=) :: Which (x ': xs) -> Which (x ': xs) -> Bool max :: Which (x ': xs) -> Which (x ': xs) -> Which (x ': xs) min :: Which (x ': xs) -> Which (x ': xs) -> Which (x ': xs) | |
Ord (Which ('[] :: [Type])) Source # | ( |
Defined in Data.Diverse.Which.Internal | |
Reduce (Which xs) (SwitcherN c r n xs) => SwitchN Which (c :: Type -> Nat -> [Type] -> Type) r n (xs :: [Type]) Source # | |
Defined in Data.Diverse.Which.Internal | |
Reduce (Which '[Void]) (Switcher c r ('[] :: [Type])) Source # | Allow 'Which '[Void]' to be |
(Case (c r) (x ': (x' ': xs)), Reduce (Which (x' ': xs)) (Switcher c r (x' ': xs)), Reiterate (c r) (x ': (x' ': xs)), r ~ CaseResult (c r) x) => Reduce (Which (x ': (x' ': xs))) (Switcher c r (x ': (x' ': xs))) Source # |
|
(Case (c r) '[x], r ~ CaseResult (c r) x) => Reduce (Which '[x]) (Switcher c r '[x]) Source # | Terminating case of the loop, ensuring that a instance of |
Reduce (Which ('[] :: [Type])) (Switcher c r ('[] :: [Type])) Source # | Allow 'Which '[]' to be |
(Case (c r n) (x ': (x' ': xs)), Reduce (Which (x' ': xs)) (SwitcherN c r (n + 1) (x' ': xs)), ReiterateN (c r) n (x ': (x' ': xs)), r ~ CaseResult (c r n) x) => Reduce (Which (x ': (x' ': xs))) (SwitcherN c r n (x ': (x' ': xs))) Source # |
|
(Case (c r n) '[x], r ~ CaseResult (c r n) x) => Reduce (Which '[x]) (SwitcherN c r n '[x]) Source # | Terminating case of the loop, ensuring that a instance of |
type Rep (Which (x ': (x' ': xs))) Source # | |
Defined in Data.Diverse.Which.Internal | |
type Rep (Which '[x]) Source # | |
Defined in Data.Diverse.Which.Internal type Rep (Which '[x]) = Rec0 x | |
type Rep (Which ('[] :: [Type])) Source # | |
Defined in Data.Diverse.Which.Internal type Rep (Which ('[] :: [Type])) = V1 :: Type -> Type |
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 trial
ing a Which '[x]
with one type.
It is an uninhabited type, just like Void
impossible' :: Which '[Void] -> a Source #
A Which '[Void]
is equivalent to Which '[]
A Which '[Void]
might occur if you lift a Void
into a Which
with pick
.
This allows you to convert it back to Void
or Which '[]
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 #
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. UniqueMember (Tagged l x) xs => Which xs -> Either (Which (Remove (Tagged l x) xs)) 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
pattern W :: forall x xs. UniqueMember x xs => x -> Which xs Source #
Pattern synonym that makes pattern matching on Which possible.
For example, this will return Just 5
:
let y = pick (5 :: Int) :: Which '[Bool, String, Int] in case y of W (i :: Int) -> Just i _ -> Nothing
Keep in mind, GHC is not smart enough and will always throw a warning about incomplete pattern matches without a catch-all clause.
Multiple types
Injection
type Diversify (branch :: [Type]) (tree :: [Type]) = Switch (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.
type DiversifyL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Diversify branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) Source #
A friendlier constraint synonym for diversifyL
.
diversifyL :: forall ls branch tree. DiversifyL ls branch tree => Which branch -> Which tree Source #
A variation of diversify
where branch
is 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]switch
y'' (CaseFunc
@Typeable
(show . typeRep . (pure @Proxy))) `shouldBe` "Tagged * Bar Int"
type DiversifyN (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (SwitchN Which (CaseDiversifyN ns) (Which tree) 0 branch, KindsAtIndices ns tree ~ branch) Source #
A friendlier constraint synonym for diversifyN
.
diversifyN :: forall ns branch tree. DiversifyN ns 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'switch
y'' (CaseFunc
@Typeable
(show . typeRep . (pure @Proxy))) `shouldBe` "Int"
Inverse Injection
type Reinterpret (branch :: [Type]) (tree :: [Type]) = Switch (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 Left
over 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 =reinterpret
pick
(5 :: Int)) ::Which
'[String, Int]
type Reinterpret' (branch :: [Type]) (tree :: [Type]) = Switch (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.
type ReinterpretL (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Reinterpret branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) Source #
A friendlier constraint synonym for reinterpretL
.
reinterpretL :: forall ls branch tree. ReinterpretL ls branch tree => 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
type ReinterpretL' (ls :: [k]) (branch :: [Type]) (tree :: [Type]) = (Reinterpret' branch tree, branch ~ KindsAtLabels ls tree, UniqueLabels ls tree, IsDistinct ls) Source #
A friendlier constraint synonym for reinterpretL
.
reinterpretL' :: forall ls branch tree. ReinterpretL' ls branch tree => Which tree -> Maybe (Which branch) Source #
Variation of reinterpretL
which returns a Maybe.
type ReinterpretN' (ns :: [Nat]) (branch :: [Type]) (tree :: [Type]) = (SwitchN Which (CaseReinterpretN' ns) (Maybe (Which branch)) 0 tree, KindsAtIndices ns tree ~ branch) Source #
A friendlier constraint synonym for reinterpretN
.
reinterpretN' :: forall ns branch tree. ReinterpretN' ns 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 reinterpretN
.
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]switch
y (cases
(show @Bool./
show @Int./
nil
)) `shouldBe` "5"
Or CaseFunc
@Typeable
to apply a polymorphic function that work on all Typeable
s.
let y =pick
(5 :: Int) ::Which
'[Int, Bool]switch
y (CaseFunc
@Typeable
(show . typeRep . (pure @Proxy))) `shouldBe` Int
Or you may use your own custom instance of Case
.
newtype Switcher c r (xs :: [Type]) Source #
Switcher
is an instance of Reduce
for which reiterate
s through the possibilities in a Which
,
delegating handling to Case
, ensuring termination when Which
only contains one type.
Switcher (c r xs) |
Instances
Reduce Void (Switcher c r ('[] :: [Type])) Source # | Allow |
Reduce (Which '[Void]) (Switcher c r ('[] :: [Type])) Source # | Allow 'Which '[Void]' to be |
(Case (c r) (x ': (x' ': xs)), Reduce (Which (x' ': xs)) (Switcher c r (x' ': xs)), Reiterate (c r) (x ': (x' ': xs)), r ~ CaseResult (c r) x) => Reduce (Which (x ': (x' ': xs))) (Switcher c r (x ': (x' ': xs))) Source # |
|
(Case (c r) '[x], r ~ CaseResult (c r) x) => Reduce (Which '[x]) (Switcher c r '[x]) Source # | Terminating case of the loop, ensuring that a instance of |
Reduce (Which ('[] :: [Type])) (Switcher c r ('[] :: [Type])) Source # | Allow 'Which '[]' to be |
type Reduced (Switcher c r xs) Source # | |
Defined in Data.Diverse.Which.Internal |
class SwitchN w c r (n :: Nat) xs 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]switchN
y (casesN
(show @Int./
show @Bool./
show @Bool./
show @Int./
nil
)) `shouldBe` "5"
Or you may use your own custom instance of Case
.
newtype SwitcherN c r (n :: Nat) (xs :: [Type]) Source #
SwitcherN
is a variation of Switcher
which reiterateN
s through the possibilities in a Which
,
delegating work to CaseN
, ensuring termination when Which
only contains one type.
SwitcherN (c r n xs) |
Instances
(Case (c r n) (x ': (x' ': xs)), Reduce (Which (x' ': xs)) (SwitcherN c r (n + 1) (x' ': xs)), ReiterateN (c r) n (x ': (x' ': xs)), r ~ CaseResult (c r n) x) => Reduce (Which (x ': (x' ': xs))) (SwitcherN c r n (x ': (x' ': xs))) Source # |
|
(Case (c r n) '[x], r ~ CaseResult (c r n) x) => Reduce (Which '[x]) (SwitcherN c r n '[x]) Source # | Terminating case of the loop, ensuring that a instance of |
type Reduced (SwitcherN c r n xs) Source # | |
Defined in Data.Diverse.Which.Internal |