hobbits-1.2: A library for canonically representing terms with binding

Copyright(c) 2011 Edwin Westbrook, Nicolas Frisby, and Paul Brauner
LicenseBSD3
Maintainerwestbrook@galois.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Data.Type.HList

Description

A type list contains types as elements. We use GADT proofs terms to establish membership and append relations. A Data.Type.HList.HList f is a vector indexed by a type list, where f :: * -> * is applied to each type element.

Synopsis

Documentation

data r :> a infixl 5 Source

Instances

TypeCtx ctx => TypeCtx ((:>) ctx a) Source 
(NuMatchingList args, NuMatching a) => NuMatchingList ((:>) args a) Source 
type r1 :++: ((:>) r2 a) = (:>) ((:++:) r1 r2) a Source 

type family r1 :++: r2 infixr 5 Source

Instances

type r :++: Nil = r Source 
type r1 :++: ((:>) r2 a) = (:>) ((:++:) r1 r2) a Source 

proxyCons :: Proxy r -> f a -> Proxy (r :> a) Source

data Member ctx a where Source

A Member ctx a is a "proof" that the type a is in the type list ctx, meaning that ctx equals

 t0 ':>' a ':>' t1 ':>' ... ':>' tn

for some types t0,t1,...,tn.

Constructors

Member_Base :: Member (ctx :> a) a 
Member_Step :: Member ctx a -> Member (ctx :> b) a 

Instances

weakenMemberL :: Proxy r1 -> Member r2 a -> Member (r1 :++: r2) a Source

membersEq :: Member ctx a -> Member ctx b -> Maybe (a :~: b) Source

data Append ctx1 ctx2 ctx where Source

An Append ctx1 ctx2 ctx is a "proof" that ctx = ctx1 :++: ctx2.

Constructors

Append_Base :: Append ctx Nil ctx 
Append_Step :: Append ctx1 ctx2 ctx -> Append ctx1 (ctx2 :> a) (ctx :> a) 

data HList f c where Source

A HList f c is a vector with exactly one element of type f a for each type a in the type list c.

Constructors

Nil :: HList f Nil 
(:>) :: HList f c -> f a -> HList f (c :> a) infixl 5 

Instances

empty :: HList f Nil Source

Create an empty HList vector.

singleton :: f a -> HList f (Nil :> a) Source

Create a singleton HList vector.

hlistLookup :: Member c a -> HList f c -> f a Source

Look up an element of a HList vector using a Member proof.

mapHList :: (forall x. f x -> g x) -> HList f c -> HList g c Source

Map a function on all elements of a HList vector.

mapHList2 :: (forall x. f x -> g x -> h x) -> HList f c -> HList g c -> HList h c Source

Map a binary function on all pairs of elements of two HList vectors.

appendHList :: HList f c1 -> HList f c2 -> HList f (c1 :++: c2) Source

Append two HList vectors.

mkAppend :: HList f c2 -> Append c1 c2 (c1 :++: c2) Source

Make an Append proof from any HList vector for the second argument of the append.

mkMonoAppend :: Proxy c1 -> HList f c2 -> Append c1 c2 (c1 :++: c2) Source

A version of mkAppend that takes in a Proxy argument.

proxiesFromAppend :: Append c1 c2 c -> HList Proxy c2 Source

The inverse of mkAppend, that builds an HList from an Append

splitHList :: (c ~ (c1 :++: c2)) => Proxy c1 -> HList any c2 -> HList f c -> (HList f c1, HList f c2) Source

Split an HList vector into two pieces. The first argument is a phantom argument that gives the form of the first list piece.

members :: HList f c -> HList (Member c) c Source

Create a vector of proofs that each type in c is a Member of c.

hlistToList :: HList (Constant a) c -> [a] Source

Convert an HList to a list

class TypeCtx ctx where Source

A type-class which ensures that ctx is a valid context, i.e., has | the form (Nil :> t1 :> ... :> tn) for some types t1 through tn

Instances