Copyright | (c) Fumiaki Kinoshita 2015 |
---|---|
License | BSD3 |
Maintainer | Fumiaki Kinoshita <fumiexcel@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This package defines an extensible type-indexed product type and a union type.
Both are determined from the type-level list [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
- module Data.Extensible.Inclusion
- module Data.Extensible.Match
- module Data.Extensible.Plain
- module Data.Extensible.Product
- module Data.Extensible.Sum
- data Position xs x
- runPosition :: Position (y : xs) x -> Either (x :~: y) (Position xs x)
- type (∈) x xs = Member xs x
- class Member xs x where
- membership :: Position xs x
- ord :: Int -> Q Exp
Reexport
module Data.Extensible.Inclusion
module Data.Extensible.Match
module Data.Extensible.Plain
module Data.Extensible.Product
module Data.Extensible.Sum
Lookup
The position of x
in the type level set xs
.
runPosition :: Position (y : xs) x -> Either (x :~: y) (Position xs x) Source
Embodies a type equivalence to ensure that the Position
points the first element.
class Member xs x where Source
Member x xs
or x ∈ xs
indicates that x
is an element of xs
.
membership :: Position xs x Source