You can use GADTs to force the list of free variables to be empty. The free variables can be kept in a type-level list. Below, I chose to use De Bruijn indices to represent variables.
We start by defining how to append two type level lists:
{-# LANGUAGE KindSignatures, DataKinds, TypeFamilies, TypeOperators,
GADTs, ScopedTypeVariables, TypeApplications #-}
{-# OPTIONS -Wall #-}
import GHC.TypeLits
import Data.Proxy
-- Type level lists append
type family (xs :: [Nat]) ++ (ys :: [Nat]) :: [Nat] where
'[] ++ ys = ys
(x ': xs) ++ ys = x ': (xs ++ ys)
Then we compute the free variables of \ t
given those of t
.
-- Adjust Debuijn indices under a lambda:
-- remove zeros, decrement positives
type family Lambda (xs :: [Nat]) where
Lambda '[] = '[]
Lambda (0 ': xs) = Lambda xs
Lambda (x ': xs) = x-1 ': Lambda xs
Finally our GADT:
-- "BTerm free" represents a lambda term with free variables "free"
data BTerm (free :: [Nat]) where
BVar :: KnownNat n => BTerm '[n]
BLam :: BTerm free -> BTerm (Lambda free)
BApp :: BTerm free1 -> BTerm free2 -> BTerm (free1 ++ free2)
A type for closed terms is now trivial to define:
-- Closed terms have no free variables
type Closed = BTerm '[]
We are done. Let's write some tests. We start from a Show
instance to be able to actually print the terms.
showBVar :: forall n. KnownNat n => BTerm '[n] -> String
showBVar _ = "var" ++ show (natVal (Proxy @n))
instance Show (BTerm free) where
show t@BVar = showBVar t
show (BLam t) = "\\ " ++ show t
show (BApp t1 t2) = "(" ++ show t1 ++ ")(" ++ show t2 ++ ")"
And here's a couple of tests:
-- \x. \y. \z. z (x y)
-- Output: \ \ \ (var0)((var2)(var1))
test1 :: Closed
test1 = BLam (BLam (BLam (BApp z (BApp x y))))
where
z = BVar @0
y = BVar @1
x = BVar @2
-- \x. \y. x y (\z. z (x y))
-- Output: \ \ ((var1)(var0))(\ (var0)((var2)(var1)))
test2 :: Closed
test2 = BLam (BLam (BApp (BApp x' y') (BLam (BApp z (BApp x y)))))
where
z = BVar @0
y = BVar @1
x = BVar @2
y' = BVar @0
x' = BVar @1
Exp
includes a type parameter representing the expression's typing context, so anExp '[] t
with an empty typing context represents a closed term (witht
the type of the term itself). As a consequence,eval :: Exp '[] t -> Val t
never has to worry about encountering an undefined variable. – Radiosurgery