Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensible type-safe unions.
>>>
let a = openUnion # (5 :: Int) :: OpenUnion '[Bool, Int]
>>>
a ^? openUnion @Int
Just 5
>>>
a ^? openUnion @Bool
Nothing
>>>
a ^? openUnion @Char
<interactive>:7:6: error: • No instance for (UElem Char '[] (RIndex Char '[])) arising from a use of ‘openUnion’ • In the second argument of ‘(^?)’, namely ‘openUnion @Char’ In the expression: a ^? openUnion @Char In an equation for ‘it’: it = a ^? openUnion @Char
Synopsis
- data Union (f :: u -> *) (as :: [u]) where
- union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c
- absurdUnion :: Union f '[] -> a
- umap :: (forall a. f a -> g a) -> Union f as -> Union g as
- _This :: Prism (Union f (a ': as)) (Union f (b ': as)) (f a) (f b)
- _That :: Prism (Union f (a ': as)) (Union f (a ': bs)) (Union f as) (Union f bs)
- class i ~ RIndex a as => UElem (a :: u) (as :: [u]) (i :: Nat) where
- class is ~ RImage as bs => USubset (as :: [u]) (bs :: [u]) is where
- type OpenUnion = Union Identity
- openUnion :: forall a as. UElem a as (RIndex a as) => Prism' (OpenUnion as) a
Documentation
data Union (f :: u -> *) (as :: [u]) where Source #
A union is parameterized by a universe u
, an interpretation f
and a list of labels as
. The labels of the union are given by
inhabitants of the kind u
; the type of values at any label a ::
u
is given by its interpretation f a :: *
.
Instances
(Eq (f a2), Eq (Union f as)) => Eq (Union f (a2 ': as)) Source # | |
Eq (Union f ([] :: [u])) Source # | |
(Ord (f a2), Ord (Union f as)) => Ord (Union f (a2 ': as)) Source # | |
Defined in Data.Union compare :: Union f (a2 ': as) -> Union f (a2 ': as) -> Ordering # (<) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (<=) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (>) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # (>=) :: Union f (a2 ': as) -> Union f (a2 ': as) -> Bool # max :: Union f (a2 ': as) -> Union f (a2 ': as) -> Union f (a2 ': as) # min :: Union f (a2 ': as) -> Union f (a2 ': as) -> Union f (a2 ': as) # | |
Ord (Union f ([] :: [u])) Source # | |
(Show (f a2), Show (Union f as)) => Show (Union f (a2 ': as)) Source # | |
Show (Union f ([] :: [u])) Source # | |
Generic (Union f (a ': as)) Source # | |
Generic (Union f ([] :: [u])) Source # | |
(f ~ Identity, Exception a, Typeable as, Exception (Union f as)) => Exception (Union f (a ': as)) Source # | |
Defined in Data.Union toException :: Union f (a ': as) -> SomeException # fromException :: SomeException -> Maybe (Union f (a ': as)) # displayException :: Union f (a ': as) -> String # | |
f ~ Identity => Exception (Union f ([] :: [*])) Source # | |
Defined in Data.Union toException :: Union f [] -> SomeException # fromException :: SomeException -> Maybe (Union f []) # displayException :: Union f [] -> String # | |
(NFData (f a2), NFData (Union f as)) => NFData (Union f (a2 ': as)) Source # | |
Defined in Data.Union | |
NFData (Union f ([] :: [u])) Source # | |
Defined in Data.Union | |
(Hashable (f a2), Hashable (Union f as)) => Hashable (Union f (a2 ': as)) Source # | |
Defined in Data.Union | |
Hashable (Union f ([] :: [u])) Source # | |
Defined in Data.Union | |
type Rep (Union f (a ': as)) Source # | |
type Rep (Union f ([] :: [u])) Source # | |
union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c Source #
Case analysis for unions.
absurdUnion :: Union f '[] -> a Source #
Since a union with an empty list of labels is uninhabited, we can recover any type from it.
class i ~ RIndex a as => UElem (a :: u) (as :: [u]) (i :: Nat) where Source #
class is ~ RImage as bs => USubset (as :: [u]) (bs :: [u]) is where Source #