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 |
This library implements multi-bindings as described in the paper E. Westbrook, N. Frisby, P. Brauner, "Hobbits for Haskell: A Library for Higher-Order Encodings in Functional Programming Languages".
Synopsis
- module Data.Binding.Hobbits.Mb
- module Data.Binding.Hobbits.Closed
- module Data.Binding.Hobbits.QQ
- module Data.Binding.Hobbits.Liftable
- module Data.Proxy
- module Data.Type.Equality
- data RList a
- data RAssign (f :: k -> *) (c :: RList k) where
- data Member (ctx :: RList k1) (a :: k2) where
- Member_Base :: Member (ctx :> a) a
- Member_Step :: Member ctx a -> Member (ctx :> b) a
- type family (r1 :: RList k) :++: (r2 :: RList k) :: RList k
- data Append ctx1 ctx2 ctx where
- Append_Base :: Append ctx RNil ctx
- Append_Step :: Append ctx1 ctx2 ctx -> Append ctx1 (ctx2 :> a) (ctx :> a)
- module Data.Binding.Hobbits.NuMatching
Values under multi-bindings
module Data.Binding.Hobbits.Mb
The Mb
type modeling multi-bindings is the
central abstract type of the library
Closed terms
module Data.Binding.Hobbits.Closed
Pattern-matching multi-bindings and closed terms
module Data.Binding.Hobbits.QQ
The nuP
quasiquoter allows safe pattern
matching on Mb
values. superCombP
is similar.
Lifting values out of multi-bindings
Ancilliary modules
module Data.Proxy
module Data.Type.Equality
Type lists track the types of bound variables.
A form of lists where elements are added to the right instead of the left
data RAssign (f :: k -> *) (c :: RList k) where Source #
An RAssign f r
an assignment of an f a
for each a
in the RList
r
Instances
Show (RAssign (Name :: k -> Type) c) Source # | |
NuMatchingAny1 f => NuMatching (RAssign f ctx) Source # | |
Defined in Data.Binding.Hobbits.NuMatching nuMatchingProof :: MbTypeRepr (RAssign f ctx) Source # | |
ClosableAny1 f => Closable (RAssign f ctx) Source # | |
data Member (ctx :: RList k1) (a :: k2) 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
.
Member_Base :: Member (ctx :> a) a | |
Member_Step :: Member ctx a -> Member (ctx :> b) a |
Instances
TestEquality (Member ctx :: k -> Type) Source # | |
Defined in Data.Type.RList | |
Eq (Member ctx a) Source # | |
Show (Member r a) Source # | |
NuMatching (Member ctx a) Source # | |
Defined in Data.Binding.Hobbits.NuMatchingInstances nuMatchingProof :: MbTypeRepr (Member ctx a) Source # | |
Closable (Member ctx a) Source # | |
Liftable (Member c a) Source # | |
type family (r1 :: RList k) :++: (r2 :: RList k) :: RList k infixr 5 Source #
Append two RList
s at the type level
data Append ctx1 ctx2 ctx where Source #
An Append ctx1 ctx2 ctx
is a "proof" that ctx = ctx1
.:++:
ctx2
Append_Base :: Append ctx RNil ctx | |
Append_Step :: Append ctx1 ctx2 ctx -> Append ctx1 (ctx2 :> a) (ctx :> a) |
The Data.Binding.Hobbits.NuMatching module exposes the NuMatching class, which allows pattern-matching on (G)ADTs in the bodies of multi-bindings