| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Union
Description
Extensible type-safe unions.
- data Union f as 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 as i where
- class is ~ RImage as bs => USubset as bs is where
- type OpenUnion = Union Identity
- openUnion :: forall a as. UElem a as (RIndex a as) => Prism' (OpenUnion as) a
Documentation
data Union f as 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 a1), Eq (Union a f as)) => Eq (Union a f ((:) a a1 as)) Source # | |
| Eq (Union u f ([] u)) Source # | |
| (Ord (f a1), Ord (Union a f as)) => Ord (Union a f ((:) a a1 as)) Source # | |
| Ord (Union u f ([] u)) Source # | |
| (Show (f a1), Show (Union a f as)) => Show (Union a f ((:) a a1 as)) Source # | |
| Show (Union u f ([] u)) Source # | |
| ((~) (* -> *) f Identity, Exception a, Typeable [*] as, Exception (Union * f as)) => Exception (Union * f ((:) * a as)) Source # | |
| (~) (* -> *) f Identity => Exception (Union * f ([] *)) Source # | |
| (NFData (f a1), NFData (Union a f as)) => NFData (Union a f ((:) a a1 as)) Source # | |
| NFData (Union u 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.