Copyright | (C) 2015 Richard Eisenberg |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg ([email protected]) |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Language.Glambda.Exp
Description
The Exp GADT. Glambda expressions encoded in an Exp
value are
*always* well-typed.
- data Exp :: [*] -> * -> * where
- Var :: Elem ctx ty -> Exp ctx ty
- Lam :: Exp (arg ': ctx) res -> Exp ctx (arg -> res)
- App :: Exp ctx (arg -> res) -> Exp ctx arg -> Exp ctx res
- Arith :: Exp ctx Int -> ArithOp ty -> Exp ctx Int -> Exp ctx ty
- Cond :: Exp ctx Bool -> Exp ctx ty -> Exp ctx ty -> Exp ctx ty
- Fix :: Exp ctx (ty -> ty) -> Exp ctx ty
- IntE :: Int -> Exp ctx Int
- BoolE :: Bool -> Exp ctx Bool
- data Elem :: [a] -> a -> * where
- class GlamVal t where
- data Val t
- prettyVal :: Val t -> STy t -> Doc
- eqExp :: Exp ctx1 ty1 -> Exp ctx2 ty2 -> Bool
Documentation
data Exp :: [*] -> * -> * where Source #
Exp ctx ty
is a well-typed expression of type ty
in context
ctx
. Note that a context is a list of types, where a type's index
in the list indicates the de Bruijn index of the associated term-level
variable.
Constructors
Var :: Elem ctx ty -> Exp ctx ty | |
Lam :: Exp (arg ': ctx) res -> Exp ctx (arg -> res) | |
App :: Exp ctx (arg -> res) -> Exp ctx arg -> Exp ctx res | |
Arith :: Exp ctx Int -> ArithOp ty -> Exp ctx Int -> Exp ctx ty | |
Cond :: Exp ctx Bool -> Exp ctx ty -> Exp ctx ty -> Exp ctx ty | |
Fix :: Exp ctx (ty -> ty) -> Exp ctx ty | |
IntE :: Int -> Exp ctx Int | |
BoolE :: Bool -> Exp ctx Bool |
data Elem :: [a] -> a -> * where Source #
Elem xs x
is evidence that x
is in the list xs
.
EZ :: Elem xs x
is evidence that x
is the first element of xs
.
ES ev :: Elem xs x
is evidence that x
is one position later in
xs
than is indicated in ev
class GlamVal t where Source #
Classifies types that can be values of glambda expressions
Minimal complete definition
Associated Types
Well-typed closed values. Encoded as a data family with newtype instances in order to avoid runtime checking of values