clean-unions-0.1.1: Open unions without need for Typeable

Safe HaskellNone
LanguageHaskell2010

Data.OpenUnion1.Clean

Contents

Synopsis

Basic types and classes

data family Union s a Source

Instances

(Functor f, Functor (Union s)) => Functor (Union ((:>) (* -> *) f s)) 
Functor (Union (Empty (* -> *))) 
type f |> (Union s) = Union ((:>) (* -> *) f s) 
data Union (Empty (* -> *)) = Exhausted (Union (Empty (* -> *)) a) 
data Union ((:>) (* -> *) f s)  

type Nil = Union Empty Source

An uninhabited union.

type family f |> s :: * -> * infixr 5 Source

Append a new element to a union.

Instances

type f |> (Union s) = Union ((:>) (* -> *) f s) 

data List a Source

Poly-kinded list

Constructors

Empty 
a :> (List a) infixr 5 

class f s | s -> f infix 4 Source

Constraint f ∈ s indicates that f is an element of a type-level list s.

Minimal complete definition

position

Instances

(∈) k f s => (∈) k f ((:>) k g s) 
(∈) k f ((:>) k f s) 

type Member f s = f s Source

Construction

liftU :: forall s f a. f s => f a -> Union s a Source

Lift some value into a union.

Transformation

class s t where infix 4 Source

Type-level inclusion characterized by reunion.

Methods

reunion :: Union s a -> Union t a Source

Lift a union into equivalent or larger one, permuting elements if necessary.

Instances

(Empty (* -> *)) t

Every set has an empty set as its subset.

((∈) (* -> *) f t, (⊆) s t) => ((:>) (* -> *) f s) t 

type Include s t = s t Source

picked :: forall a s f g. (f s, Applicative g) => (f a -> g (f a)) -> Union s a -> g (Union s a) Source

Traversal for a specific element

hoistU :: f s => (f a -> f a) -> Union s a -> Union s a Source

Destruction

(||>) infixr 0 Source

Arguments

:: (f x -> r)

first case

-> (Union s x -> r)

otherwise

-> Union (f :> s) x -> r

matching function

Perform type-safe matching.

exhaust :: Nil x -> r Source

simply :: (f a -> r) -> (f |> Nil) a -> r Source

retractU :: f s => Union s a -> Maybe (f a) Source