Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Which xs = Which !Int Any
- impossible :: Which '[]
- pick :: forall xs x. UniqueMember x xs => x -> Which xs
- pick0 :: x -> Which (x ': xs)
- pickOnly :: x -> Which '[x]
- pickN :: forall n xs x proxy. MemberAt n x xs => proxy n -> x -> Which xs
- obvious :: Which '[a] -> a
- trial :: forall x xs. UniqueMember x xs => Which xs -> Either (Which (Without x xs)) x
- trial0 :: Which (x ': xs) -> Either (Which xs) x
- trialN :: forall n xs x proxy. MemberAt n x xs => proxy n -> Which xs -> Either (Which (WithoutIndex n xs)) x
- facet :: forall x xs. UniqueMember x xs => Prism' (Which xs) x
- facetN :: forall n xs x proxy. MemberAt n x xs => proxy n -> Prism' (Which xs) x
- type Diversify tree branch = Reduce Which (Switch (CaseDiversify tree branch)) branch (Which tree)
- diversify :: forall tree branch. Diversify tree branch => Which branch -> Which tree
- diversify0 :: proxy x -> Which xs -> Which (x ': xs)
- type DiversifyN indices tree branch = (Reduce Which (SwitchN (CaseDiversifyN indices) 0) (KindsAtIndices indices tree) (Which tree), KindsAtIndices indices tree ~ branch)
- diversifyN :: forall indices tree branch proxy. DiversifyN indices tree branch => proxy indices -> Which branch -> Which tree
- type Reinterpret branch tree = Reduce Which (Switch (CaseReinterpret branch tree)) tree (Either (Which (Complement tree branch)) (Which branch))
- reinterpret :: forall branch tree. Reinterpret branch tree => Which tree -> Either (Which (Complement tree branch)) (Which branch)
- type ReinterpretN indices branch tree = (Reduce Which (SwitchN (CaseReinterpretN indices) 0) tree (Maybe (Which (KindsAtIndices indices tree))), KindsAtIndices indices tree ~ branch)
- reinterpretN :: forall indices branch tree proxy. ReinterpretN indices branch tree => proxy indices -> Which tree -> Maybe (Which branch)
- inject :: forall branch tree. (Diversify tree branch, Reinterpret branch tree) => Prism' (Which tree) (Which branch)
- injectN :: forall indices branch tree proxy. (DiversifyN indices tree branch, ReinterpretN indices branch tree) => proxy indices -> Prism' (Which tree) (Which branch)
- newtype Switch c xs r = Switch (c xs r)
- which :: Reduce Which (Switch case') xs r => case' xs r -> Which xs -> r
- switch :: Reduce Which (Switch case') xs r => Which xs -> case' xs r -> r
- newtype SwitchN c n xs r = SwitchN (c n xs r)
- whichN :: Reduce Which (SwitchN case' n) xs r => case' n xs r -> Which xs -> r
- switchN :: Reduce Which (SwitchN case' n) xs r => Which xs -> case' n xs r -> 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:
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
Case c ((:) Type x ([] Type)) r => Reduce Which (Switch c) ((:) Type x ([] Type)) r Source # | Terminating case of the loop, ensuring that a instance of |
(Case c ((:) Type x ((:) Type x' xs)) r, Reduce Which (Switch c) ((:) Type x' xs) r, Reiterate * c ((:) Type x ((:) Type x' xs))) => Reduce Which (Switch c) ((:) Type x ((:) Type x' xs)) r Source # |
|
Case (c n) ((:) Type x ([] Type)) r => Reduce Which (SwitchN c n) ((:) Type x ([] Type)) r Source # | Terminating case of the loop, ensuring that a instance of |
(Case (c n) ((:) Type x ((:) Type x' xs)) r, Reduce Which (SwitchN c ((+) n 1)) ((:) Type x' xs) r, ReiterateN * c n ((:) Type x ((:) Type x' xs))) => Reduce Which (SwitchN c n) ((:) Type x ((:) Type x' xs)) r Source # |
|
Reduce Which (Switch CaseEqWhich) ((:) Type x xs) Bool => Eq (Which ((:) Type x xs)) Source # | Two |
Eq (Which ([] Type)) Source # | ( |
(Reduce Which (Switch CaseEqWhich) ((:) Type x xs) Bool, Reduce Which (Switch CaseOrdWhich) ((:) Type x xs) Ordering) => Ord (Which ((:) Type x xs)) Source # | A |
Ord (Which ([] Type)) Source # | ( |
AFoldable (Collector * EmitReadWhich ((:) Type x xs)) (ReadPrec (Int, WrappedAny)) => Read (Which ((:) Type x xs)) Source # | This |
Read (Which ([] Type)) Source # | read "impossible" == |
Reduce Which (Switch CaseShowWhich) ((:) Type x xs) ShowS => Show (Which ((:) Type x xs)) Source # | show ( |
Show (Which ([] Type)) Source # | read "impossible" == |
Generic (Which ((:) Type x ((:) Type x' xs))) Source # | A |
Generic (Which ((:) Type x ([] Type))) Source # | A terminating |
Generic (Which ([] Type)) Source # | A terminating |
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 '[] Source #
A Which
with no alternatives. You can't do anything with impossible
except Eq, Read, and Show it.
Using functions like switch
and trial
with impossible
is a compile error.
impossible
is only useful as a Left
-over from trial
ing a Which '[x]
with one type.
pick :: forall xs x. UniqueMember x xs => x -> Which xs Source #
Destruction
trialN :: forall n xs x proxy. MemberAt n x xs => proxy n -> Which xs -> Either (Which (WithoutIndex n xs)) x Source #
Lens
Multiple types
Injection
type Diversify tree branch = Reduce Which (Switch (CaseDiversify tree branch)) branch (Which tree) Source #
A friendlier constraint synonym for diversify
.
diversify :: forall tree branch. Diversify tree branch => 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. forall is used to tree
is ordered first, so TypeApplications can be used to specify tree
first.
let a =pick'
(5 :: Int) ::Which
'[Int] b =diversify
@[Int, Bool] a ::Which
'[Int, Bool] c =diversify
@[Bool, Int] b ::Which
'[Bool, Int]
diversify0 :: proxy x -> Which xs -> Which (x ': xs) Source #
A simple version of diversify
which add another type to the front of the typelist.
type DiversifyN indices tree branch = (Reduce Which (SwitchN (CaseDiversifyN indices) 0) (KindsAtIndices indices tree) (Which tree), KindsAtIndices indices tree ~ branch) Source #
A friendlier constraint synonym for diversifyN
.
diversifyN :: forall indices tree branch proxy. DiversifyN indices tree branch => proxy indices -> Which branch -> Which tree Source #
A variation of diversify
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
.
let y =pickOnly
(5 :: Int) y' =diversify
@[Int, Bool] y y'' =diversify
@[Bool, Int] y'switch
y'' (CaseTypeable
(show . typeRep . (pure @Proxy))) `shouldBe` "Int"
Inverse Injection
type Reinterpret branch tree = Reduce Which (Switch (CaseReinterpret branch tree)) tree (Either (Which (Complement tree branch)) (Which branch)) 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 ReinterpretN indices branch tree = (Reduce Which (SwitchN (CaseReinterpretN indices) 0) tree (Maybe (Which (KindsAtIndices indices tree))), KindsAtIndices indices tree ~ branch) Source #
A friendlier constraint synonym for reinterpretN
.
reinterpretN :: forall indices branch tree proxy. ReinterpretN indices branch tree => proxy indices -> 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
.
Lens
inject :: forall branch tree. (Diversify tree branch, Reinterpret branch tree) => Prism' (Which tree) (Which branch) Source #
diversify
(review
inject
) and reinterpret
(preview
inject
) in Prism'
form.
let x =pick
(5 :: Int) ::Which
'[String, Int] y =review
(inject
@_ @[Bool, Int, Char, String]) x --diversify
y `shouldBe` pick (5 :: Int) ::Which
'[Bool, Int, Char, String] let y' =preview
(inject
@[String, Int]) y --reinterpret
y' `shouldBe` Just (pick (5 :: Int)) :: Maybe (Which
'[String, Int])
injectN :: forall indices branch tree proxy. (DiversifyN indices tree branch, ReinterpretN indices branch tree) => proxy indices -> Prism' (Which tree) (Which branch) Source #
diversifyN
(review
injectN
) and reinterpretN
(preview
injectN
) in Prism'
form.
let x =pick
(5 :: Int) ::Which
'[String, Int] y =review
(injectN @[3, 1] @_ @[Bool, Int, Char, String] Proxy) x --diversifyN
y `shouldBe` pick (5 :: Int) ::Which
'[Bool, Int, Char, String] let y' =preview
(injectN
@[3, 1] @[String, Int] Proxy) y --reinterpertN'
y' `shouldBe` Just (pick
(5 :: Int)) :: Maybe (Which
'[String, Int])
Catamorphism
newtype Switch c xs r Source #
Switch
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.
Switch (c xs r) |
Case c ((:) Type x ([] Type)) r => Reduce Which (Switch c) ((:) Type x ([] Type)) r Source # | Terminating case of the loop, ensuring that a instance of |
(Case c ((:) Type x ((:) Type x' xs)) r, Reduce Which (Switch c) ((:) Type x' xs) r, Reiterate * c ((:) Type x ((:) Type x' xs))) => Reduce Which (Switch c) ((:) Type x ((:) Type x' xs)) r Source # |
|
switch :: Reduce Which (Switch case') xs r => Which xs -> case' xs r -> 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./
nul
)) `shouldBe` "5"
Or CaseTypeable
to apply a polymorphic function that work on all Typeables
.
let y =pick
(5 :: Int) ::Which
'[Int, Bool]switch
y (CaseTypeable
(show . typeRep . (pure @Proxy))) `shouldBe` Int
Or you may use your own custom instance of Case
.
newtype SwitchN c n xs r Source #
SwitchN
is a variation of Switch
which reiterateN
s through the possibilities in a Which
,
delegating work to CaseN
, ensuring termination when Which
only contains one type.
SwitchN (c n xs r) |
Case (c n) ((:) Type x ([] Type)) r => Reduce Which (SwitchN c n) ((:) Type x ([] Type)) r Source # | Terminating case of the loop, ensuring that a instance of |
(Case (c n) ((:) Type x ((:) Type x' xs)) r, Reduce Which (SwitchN c ((+) n 1)) ((:) Type x' xs) r, ReiterateN * c n ((:) Type x ((:) Type x' xs))) => Reduce Which (SwitchN c n) ((:) Type x ((:) Type x' xs)) r Source # |
|
switchN :: Reduce Which (SwitchN case' n) xs r => Which xs -> case' n xs r -> 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 Proxy (5 :: Int) ::Which
'[Int, Bool, Bool, Int]switchN
y (casesN
(show @Int./
show @Bool./
show @Bool./
show @Int./
nul
)) `shouldBe` "5"
Or you may use your own custom instance of Case
.