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

Copyright(c) 2016 Edwin Westbrook
LicenseBSD3
Maintainerwestbrook@galois.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Data.Type.RList

Description

A right list, or RList, is a list where cons adds to the end, or the right-hand side, of a list. This is useful conceptually for contexts of name-bindings, where the most recent name-binding is intuitively at the end of the context.

Synopsis

Documentation

data RList a Source

Constructors

RNil 
(RList a) :> a 

type family r1 :++: r2 :: RList * infixr 5 Source

Instances

type r :++: (RNil *) = 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 RNil ctx 
Append_Step :: Append ctx1 ctx2 ctx -> Append ctx1 (ctx2 :> a) (ctx :> a) 

data MapRList f c where Source

A MapRList f r is a vector with exactly one element of type f a for each type a in the type RList r.

Constructors

MNil :: MapRList f RNil 
(:>:) :: MapRList f c -> f a -> MapRList f (c :> a) 

empty :: MapRList f RNil Source

Create an empty MapRList vector.

singleton :: f a -> MapRList f (RNil :> a) Source

Create a singleton MapRList vector.

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

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

mapMapRList :: (forall x. f x -> g x) -> MapRList f c -> MapRList g c Source

Map a function on all elements of a MapRList vector.

mapMapRList2 :: (forall x. f x -> g x -> h x) -> MapRList f c -> MapRList g c -> MapRList h c Source

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

appendMapRList :: MapRList f c1 -> MapRList f c2 -> MapRList f (c1 :++: c2) Source

Append two MapRList vectors.

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

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

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

A version of mkAppend that takes in a Proxy argument.

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

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

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

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

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

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

mapRListToList :: MapRList (Constant a) c -> [a] Source

Convert an MapRList to a list

class TypeCtx ctx where Source

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

Instances

TypeCtx (RNil *) Source 
TypeCtx ctx => TypeCtx ((:>) * ctx a) Source