| Copyright | (c) 2011 Edwin Westbrook Nicolas Frisby and Paul Brauner | 
|---|---|
| License | BSD3 | 
| Maintainer | emw4@rice.edu | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Binding.Hobbits.Mb
Description
This module defines multi-bindings as the type Mb, as well as a number of
 operations on multi-bindings. See the paper E. Westbrook, N. Frisby,
 P. Brauner, "Hobbits for Haskell: A Library for Higher-Order Encodings in
 Functional Programming Languages" for more information.
Synopsis
- data Name (a :: k)
- type Binding (a :: k) = Mb (RNil :> a)
- data Mb (ctx :: RList k) b
- nu :: forall k1 (a :: k1) (b :: *). (Name a -> b) -> Binding a b
- nuMulti :: RAssign f ctx -> (RAssign Name ctx -> b) -> Mb ctx b
- nus :: forall k (f :: k -> Type) (ctx :: RList k) b. RAssign f ctx -> (RAssign (Name :: k -> Type) ctx -> b) -> Mb ctx b
- emptyMb :: a -> Mb RNil a
- extMb :: Mb ctx a -> Mb (ctx :> tp) a
- extMbMulti :: RAssign f ctx2 -> Mb ctx1 a -> Mb (ctx1 :++: ctx2) a
- cmpName :: Name a -> Name b -> Maybe (a :~: b)
- hcmpName :: forall k1 k2 (a :: k1) (b :: k2). Name a -> Name b -> Maybe (a :~~: b)
- mbNameBoundP :: forall k1 k2 (a :: k1) (ctx :: RList k2). Mb ctx (Name a) -> Either (Member ctx a) (Name a)
- mbCmpName :: forall k1 k2 (a :: k1) (b :: k1) (c :: RList k2). Mb c (Name a) -> Mb c (Name b) -> Maybe (a :~: b)
- elimEmptyMb :: Mb RNil a -> a
- mbCombine :: forall k (c1 :: RList k) (c2 :: RList k) a b. Mb c1 (Mb c2 b) -> Mb (c1 :++: c2) b
- mbSeparate :: forall k (ctx1 :: RList k) (ctx2 :: RList k) (any :: k -> *) a. RAssign any ctx2 -> Mb (ctx1 :++: ctx2) a -> Mb ctx1 (Mb ctx2 a)
- mbToProxy :: forall k (ctx :: RList k) (a :: *). Mb ctx a -> RAssign Proxy ctx
- mbSwap :: Mb ctx1 (Mb ctx2 a) -> Mb ctx2 (Mb ctx1 a)
- mbPure :: RAssign f ctx -> a -> Mb ctx a
- mbApply :: Mb ctx (a -> b) -> Mb ctx a -> Mb ctx b
- mbMap2 :: (a -> b -> c) -> Mb ctx a -> Mb ctx b -> Mb ctx c
- nuMultiWithElim :: (RAssign Name ctx -> RAssign Identity args -> b) -> RAssign (Mb ctx) args -> Mb ctx b
- nuWithElim :: (Name a -> RAssign Identity args -> b) -> RAssign (Mb (RNil :> a)) args -> Binding a b
- nuMultiWithElim1 :: (RAssign Name ctx -> arg -> b) -> Mb ctx arg -> Mb ctx b
- nuWithElim1 :: (Name a -> arg -> b) -> Binding a arg -> Binding a b
Abstract types
A Name a is a bound name that is associated with type a.
Instances
| TestEquality (Name :: k -> Type) Source # | |
| Defined in Data.Binding.Hobbits.Internal.Name | |
| NuMatchingAny1 (Name :: k -> Type) Source # | |
| Defined in Data.Binding.Hobbits.NuMatching Methods nuMatchingAny1Proof :: forall (a :: k0). MbTypeRepr (Name a) Source # | |
| Eq (Name a) Source # | |
| Ord (Name a) Source # | |
| Show (Name a) Source # | |
| NuMatching (Name a) Source # | |
| Defined in Data.Binding.Hobbits.NuMatching Methods nuMatchingProof :: MbTypeRepr (Name a) Source # | |
| Show (RAssign (Name :: k -> Type) c) Source # | |
type Binding (a :: k) = Mb (RNil :> a) Source #
A Binding is simply a multi-binding that binds one name
data Mb (ctx :: RList k) b Source #
An Mb ctx b is a multi-binding that binds one name for each type
  in ctx, where ctx has the form RNil :> t1 :> ... :> tnMbTypeRepr for the body type, to ensure
  that the names given in the pair can be relaced by fresher names.
Instances
| Functor (Mb ctx) Source # | |
| TypeCtx ctx => Applicative (Mb ctx) Source # | |
| Eq a => Eq (Mb ctx a) Source # | |
| Show a => Show (Mb c a) Source # | |
| NuMatching a => NuMatching (Mb ctx a) Source # | |
| Defined in Data.Binding.Hobbits.NuMatching Methods nuMatchingProof :: MbTypeRepr (Mb ctx a) Source # | |
Multi-binding constructors
nu :: forall k1 (a :: k1) (b :: *). (Name a -> b) -> Binding a b Source #
nu f creates a binding which binds a fresh name n and whose
  body is the result of f n.
nuMulti :: RAssign f ctx -> (RAssign Name ctx -> b) -> Mb ctx b Source #
The expression nuMulti p f creates a multi-binding of zero or more
  names, one for each element of the vector p. The bound names are
  passed the names to f, which returns the body of the
  multi-binding.  The argument p, of type RAssign f ctxctx at the
  term level; thus it is unimportant what the type function f is.
nus :: forall k (f :: k -> Type) (ctx :: RList k) b. RAssign f ctx -> (RAssign (Name :: k -> Type) ctx -> b) -> Mb ctx b Source #
nus = nuMulti
extMb :: Mb ctx a -> Mb (ctx :> tp) a Source #
Extend the context of a name-binding by adding a single type
extMbMulti :: RAssign f ctx2 -> Mb ctx1 a -> Mb (ctx1 :++: ctx2) a Source #
Extend the context of a name-binding with multiple types
Queries on names
cmpName :: Name a -> Name b -> Maybe (a :~: b) Source #
cmpName n m compares names n and m of types Name a and Name b,
  respectively. When they are equal, Some e is returned for e a proof
  of type a :~: b that their types are equal. Otherwise, None is returned.
For example:
nu $ \n -> nu $ \m -> cmpName n n == nu $ \n -> nu $ \m -> Some Refl nu $ \n -> nu $ \m -> cmpName n m == nu $ \n -> nu $ \m -> None
hcmpName :: forall k1 k2 (a :: k1) (b :: k2). Name a -> Name b -> Maybe (a :~~: b) Source #
Heterogeneous comparison of names, that could be at different kinds
mbNameBoundP :: forall k1 k2 (a :: k1) (ctx :: RList k2). Mb ctx (Name a) -> Either (Member ctx a) (Name a) Source #
Checks if a name is bound in a multi-binding, returning Left mem
  when the name is bound, where mem is a proof that the type of the
  name is in the type list for the multi-binding, and returning
  Right n when the name is not bound, where n is the name.
For example:
nu $ \n -> mbNameBoundP (nu $ \m -> m) == nu $ \n -> Left Member_Base nu $ \n -> mbNameBoundP (nu $ \m -> n) == nu $ \n -> Right n
mbCmpName :: forall k1 k2 (a :: k1) (b :: k1) (c :: RList k2). Mb c (Name a) -> Mb c (Name b) -> Maybe (a :~: b) Source #
Compares two names inside bindings, taking alpha-equivalence into
  account; i.e., if both are the ith name, or both are the same name
  not bound in their respective multi-bindings, then they compare as
  equal. The return values are the same as for cmpName, so that
  Some Refl is returned when the names are equal and Nothing is
  returned when they are not.
Operations on multi-bindings
elimEmptyMb :: Mb RNil a -> a Source #
Eliminates an empty binding, returning its body. Note that
  elimEmptyMb is the inverse of emptyMb.
mbCombine :: forall k (c1 :: RList k) (c2 :: RList k) a b. Mb c1 (Mb c2 b) -> Mb (c1 :++: c2) b Source #
Combines a binding inside another binding into a single binding.
mbSeparate :: forall k (ctx1 :: RList k) (ctx2 :: RList k) (any :: k -> *) a. RAssign any ctx2 -> Mb (ctx1 :++: ctx2) a -> Mb ctx1 (Mb ctx2 a) Source #
Separates a binding into two nested bindings. The first argument, of
  type RAssign any c2c should be split.
mbToProxy :: forall k (ctx :: RList k) (a :: *). Mb ctx a -> RAssign Proxy ctx Source #
Returns a proxy object that enumerates all the types in ctx.
mbSwap :: Mb ctx1 (Mb ctx2 a) -> Mb ctx2 (Mb ctx1 a) Source #
Take a multi-binding inside another multi-binding and move the outer binding inside the ineer one.
mbApply :: Mb ctx (a -> b) -> Mb ctx a -> Mb ctx b Source #
Applies a function in a multi-binding to an argument in a multi-binding that binds the same number and types of names.
mbMap2 :: (a -> b -> c) -> Mb ctx a -> Mb ctx b -> Mb ctx c Source #
Lift a binary function function to Mbs
Eliminators for multi-bindings
nuMultiWithElim :: (RAssign Name ctx -> RAssign Identity args -> b) -> RAssign (Mb ctx) args -> Mb ctx b Source #
asdfasdf
The expression nuWithElimMulti args f takes a sequence args of one or more
  multi-bindings (it is a runtime error to pass an empty sequence of arguments),
  each of type Mb ctx ai for the same type context ctx of bound names, and a
  function f and does the following:
- Creates a multi-binding that binds names n1,...,nn, one name for each type inctx;
- Substitutes the names n1,...,nnfor the names bound by each argument in theargssequence, yielding the bodies of theargs(using the new namen); and then
- Passes the sequence n1,...,nnalong with the result of substituting intoargsto the functionf, which then returns the value for the newly created binding.
For example, here is an alternate way to implement mbApply:
mbApply' :: Mb ctx (a -> b) -> Mb ctx a -> Mb ctx b
mbApply' f a =
    nuWithElimMulti ('MNil' :>: f :>: a)
                    (\_ ('MNil' :>: 'Identity' f' :>: 'Identity' a') -> f' a')nuWithElim :: (Name a -> RAssign Identity args -> b) -> RAssign (Mb (RNil :> a)) args -> Binding a b Source #
Similar to nuMultiWithElim but binds only one name. Note that the argument
  list here is allowed to be empty.
nuMultiWithElim1 :: (RAssign Name ctx -> arg -> b) -> Mb ctx arg -> Mb ctx b Source #
Similar to nuMultiWithElim but takes only one argument
nuWithElim1 :: (Name a -> arg -> b) -> Binding a arg -> Binding a b Source #
Similar to nuMultiWithElim but takes only one argument that binds
  a single name.