extensible-0.1: Poly-kinded, extensible ADTs

Copyright(c) Fumiaki Kinoshita 2015
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Extensible

Contents

Description

This package defines an extensible type-indexed product type and a union type. Both are determined from the type-level list of elements which has kind [k] and a wrapper (k -> *). We can define ADTs not only for plain values, but also parameterized ones.

>>> let t = K0 (42 :: Int) <:* K0 "foo" <:* K0 (Just "bar") <:* Nil
>>> t
K0 42 <:* K0 "foo" <:* K0 (Just "bar") <:* Nil
>>> :t t
t :: K0 :* '[Int, [Char], Maybe [Char]]
>>> pluck t :: Int
42

Synopsis

Lookup

data Position x xs Source

Instances

Eq (Position k x xs) 
Ord (Position k x xs) 
Show (Position k x xs) 

runPosition :: Position x (y : xs) -> Either (x :~: y) (Position x xs) Source

class Member x xs where Source

Methods

position :: Position x xs Source

Instances

Record Nat (Lookup k x xs) => Member k x xs 

Product

data h :* s where Source

The extensible product type

Constructors

Nil :: h :* [] 
Tree :: h x -> (h :* Half xs) -> (h :* Half (Tail xs)) -> h :* (x : xs) 

Instances

(Show ((:*) k h xs), Show (h x)) => Show ((:*) k h ((:) k x xs)) 
Show ((:*) k h ([] k)) 

(<:*) :: forall h x xs. h x -> (h :* xs) -> h :* (x : xs) infixr 5 Source

O(log n) Add an element to a product.

unconsP :: forall h x xs. (h :* (x : xs)) -> (h x, h :* xs) Source

hoistP :: (forall x. g x -> h x) -> (g :* xs) -> h :* xs Source

outP :: forall h x xs. x xs => (h :* xs) -> h x Source

O(log n) Pick a specific element.

sector :: forall h x xs f. (Functor f, x xs) => (h x -> f (h x)) -> (h :* xs) -> f (h :* xs) Source

O(log n) A lens for a specific element.

sectorAt :: forall h x xs f. Functor f => Position x xs -> (h x -> f (h x)) -> (h :* xs) -> f (h :* xs) Source

O(log n)

class Generate xs where Source

Methods

generate :: (forall x. Position x xs -> h x) -> h :* xs Source

Instances

Generate k ([] k) 
Generate k xs => Generate k ((:) k x xs) 

Sum

data h :| s where Source

The extensible sum type

Constructors

UnionAt :: Position x xs -> h x -> h :| xs 

Instances

(Show (h x), Show ((:|) k h xs)) => Show ((:|) k h ((:) k x xs)) 
Show ((:|) k h ([] k)) 

(<:|) :: (h x -> r) -> ((h :| xs) -> r) -> (h :| (x : xs)) -> r infixr 1 Source

O(1) Naive pattern match

exhaust :: (h :| []) -> r Source

inS :: x xs => h x -> h :| xs Source

O(log n) lift a value.

picked :: forall f h x xs. (x xs, Applicative f) => (h x -> f (h x)) -> (h :| xs) -> f (h :| xs) Source

Inclusion/Permutation

class Include xs ys where Source

Methods

shrink :: (h :* ys) -> h :* xs Source

O(m log n) Select some elements.

spread :: (h :| xs) -> h :| ys Source

O(m log n) Embed to a larger union.

Instances

Include k ([] k) xs 
((∈) k x ys, Include k xs ys) => Include k ((:) k x xs) ys 

Pattern match

newtype Match h a x Source

Constructors

Match 

Fields

runMatch :: h x -> a
 

match :: (Match h a :* xs) -> (h :| xs) -> a Source

O(log n) Perform pattern match.

mapMatch :: (a -> b) -> Match h a x -> Match h b x Source

Monomorphic

newtype K0 a Source

Constructors

K0 

Fields

getK0 :: a
 

Instances

Eq a => Eq (K0 a) 
Ord a => Ord (K0 a) 
Read a => Read (K0 a) 
Show a => Show (K0 a) 
Typeable (* -> *) K0 

(<%) :: x -> (K0 :* xs) -> K0 :* (x : xs) infixr 5 Source

O(log n) Add a plain value to a product.

pluck :: x xs => (K0 :* xs) -> x Source

bury :: x xs => x -> K0 :| xs Source

(<%|) :: (x -> r) -> ((K0 :| xs) -> r) -> (K0 :| (x : xs)) -> r Source

record :: forall f x xs. (x xs, Functor f) => (x -> f x) -> (K0 :* xs) -> f (K0 :* xs) Source

O(log n) A lens for a plain value in a product.

(<?%) :: (x -> a) -> (Match K0 a :* xs) -> Match K0 a :* (x : xs) infixr 1 Source

Parameterized

newtype K1 a f Source

Constructors

K1 

Fields

getK1 :: f a
 

Instances

Typeable (k -> (k -> *) -> *) (K1 k) 
Eq (f a) => Eq (K1 k a f) 
Ord (f a) => Ord (K1 k a f) 
Read (f a) => Read (K1 k a f) 
Show (f a) => Show (K1 k a f) 

newtype Union fs a Source

Constructors

Union 

Fields

getUnion :: K1 a :| fs
 

Instances

(Functor f, Functor (Union * fs)) => Functor (Union * ((:) (* -> *) f fs)) 
Functor (Union * ([] (* -> *))) 
(Show (f a), Show (Union k fs a)) => Show (Union k ((:) (k -> *) f fs) a) 
Show (Union k ([] (k -> *)) a) 

liftU :: f fs => f a -> Union fs a Source

(<?!) :: (f x -> a) -> (Match (K1 x) a :* xs) -> Match (K1 x) a :* (f : fs) infixr 1 Source