Cogs and Levers A blog full of technical stuff

Writing Your Own Lisp Interpreter in Haskell - Part 6

Introduction

In this update, we extend our Lisp interpreter with floating point numbers and floating point math functions. This brings us closer to full numeric support, allowing for a much richer mathematical capability.

If you’re following along, you can find the implementation for this article here.

Floating Point Type

Until now, our Lisp implementation only supported integers:

data LispVal
    = Atom String
    | Number Integer
    | Bool Bool
    | String String
    | Float Double  -- Added floating point support
    | List [LispVal]
    | Pair LispVal LispVal
    | Lambda [String] LispVal Env
    | BuiltinFunc ([LispVal] -> ThrowsError LispVal)
    | BuiltinFuncIO ([LispVal] -> IOThrowsError LispVal)

We introduced a new constructor Float Double to represent floating point numbers.

Parsing

We needed to update our parser to recognize floating point literals. We do this in such a way to operate alongside the current integer math that we currently support. We don’t want to disturb the work that we’ve already done, so we’ll use that effort here.

parseInteger :: Parser LispVal
parseInteger = do
    sign <- optionMaybe (char '-')  -- Look for optional '-'
    digits <- many1 digit
    let number = read digits
    return $ Number $ case sign of
        Just _  -> -number
        Nothing -> number

parseFloat :: Parser LispVal
parseFloat = do
    sign <- optionMaybe (char '-')  -- Look for optional '-'
    whole <- many1 digit
    char '.'
    fractional <- many1 digit
    let number = read (whole ++ "." ++ fractional)
    return $ Float $ case sign of
        Just _  -> -number
        Nothing -> number

parseNumber :: Parser LispVal
parseNumber = try parseFloat <|> parseInteger

So, we changed the meaning of parseNumber from our original implementation. Instead of parseNumber handling only integers, we split the logic into parseInteger and parseFloat, ensuring both number types are correctly parsed

This ensures that expressions like 3.14 are correctly interpreted as floating point numbers, while still maintaining expressions like 3 being handled as integers.

One extra added feature here is handling negative numbers. We never observed the - symbol that can appear before some numbers, so we’ve fixed this in the parser at the same time.

Numeric Coercion

Next, we needed to handle operations between integers and floats.

Our previous numeric functions assumed only integers, so we modified them to coerce integers to floats when necessary. This means that we can use integers and floats together in our expressions.

numericAdd, numericSub, numericMul, numericDiv :: [LispVal] -> ThrowsError LispVal

numericAdd [Number a, Number b] = return $ Number (a + b)
numericAdd [Float a, Float b] = return $ Float (a + b)
numericAdd [Number a, Float b] = return $ Float (fromIntegral a + b)
numericAdd [Float a, Number b] = return $ Float (a + fromIntegral b)
numericAdd args = throwError $ TypeMismatch "Expected numbers" (List args)

This same logic was applied to subtraction, multiplication, and division.

Division Considerations

Division needed special attention because it must always return a float when dividing integers:

numericDiv [Number a, Number b] =
    if b == 0 then throwError $ TypeMismatch "Division by zero" (Number b)
    else return $ Float (fromIntegral a / fromIntegral b)
numericDiv [Float a, Float b] = return $ Float (a / b)
numericDiv [Number a, Float b] = return $ Float (fromIntegral a / b)
numericDiv [Float a, Number b] = return $ Float (a / fromIntegral b)
numericDiv args = throwError $ TypeMismatch "Expected numbers" (List args)

This ensures that (/ 3 2) evaluates to 1.5 instead of performing integer division.

Adding Floating Point Math Functions

With float support in place, we introduced math functions like sin, cos, tan, exp, log, and sqrt:

import Prelude hiding (log)

numericSin, numericCos, numericTan, numericExp, numericLog, numericSqrt :: [LispVal] -> ThrowsError LispVal

numericSin [Float a] = return $ Float (sin a)
numericSin [Number a] = return $ Float (sin (fromIntegral a))
numericSin args = throwError $ TypeMismatch "Expected a number" (List args)

numericCos [Float a] = return $ Float (cos a)
numericCos [Number a] = return $ Float (cos (fromIntegral a))
numericCos args = throwError $ TypeMismatch "Expected a number" (List args)

numericTan [Float a] = return $ Float (tan a)
numericTan [Number a] = return $ Float (tan (fromIntegral a))
numericTan args = throwError $ TypeMismatch "Expected a number" (List args)

numericExp [Float a] = return $ Float (exp a)
numericExp [Number a] = return $ Float (exp (fromIntegral a))
numericExp args = throwError $ TypeMismatch "Expected a number" (List args)

numericLog [Float a] =
    if a <= 0 then throwError $ TypeMismatch "Logarithm domain error" (Float a)
    else return $ Float (log a)
numericLog [Number a] =
    if a <= 0 then throwError $ TypeMismatch "Logarithm domain error" (Number a)
    else return $ Float (log (fromIntegral a))
numericLog args = throwError $ TypeMismatch "Expected a positive number" (List args)

numericSqrt [Float a] =
    if a < 0 then throwError $ TypeMismatch "Square root of negative number" (Float a)
    else return $ Float (sqrt a)
numericSqrt [Number a] =
    if a < 0 then throwError $ TypeMismatch "Square root of negative number" (Number a)
    else return $ Float (sqrt (fromIntegral a))
numericSqrt args = throwError $ TypeMismatch "Expected a non-negative number" (List args)

We then added them to the built-in function table:

primitives =
  [ ("sin", BuiltinFunc numericSin),
    ("cos", BuiltinFunc numericCos),
    ("tan", BuiltinFunc numericTan),
    ("exp", BuiltinFunc numericExp),
    ("log", BuiltinFunc numericLog),
    ("sqrt", BuiltinFunc numericSqrt)
  ]

Testing

With these changes, we can now perform floating point math:

(sin 0.0)   ;; 0.0
(cos 0.0)   ;; 1.0
(exp 1.0)   ;; 2.718281828
(log 10.0)  ;; 2.302585092
(sqrt 16.0) ;; 4.0

Conclusion

In this update, we:

  • Added floating point support.
  • Added negative support.
  • Introduced numeric coercion between integers and floats.
  • Implemented floating point math functions.
  • Ensured division always returns a float.

Writing Your Own Lisp Interpreter in Haskell - Part 5

Introduction

In our previous installment, we added basic list operations to our Lisp interpreter, including cons, car, cdr, append, and reverse.

Now, we are expanding that functionality by introducing higher-order list functions:

  • map
  • filter
  • foldl and foldr
  • sort

Additionally, we’re introducing string manipulation functions that allow us to treat strings as lists of characters:

  • string->list
  • list->string

These changes bring our Lisp interpreter closer to standard Scheme-like behavior.

If you’re following along, you can find the updated implementation for this article here.

Lambda Expressions

A lambda function in computer programming is an anonymous function that we use to pass to higher-order functions.

To support map, filter, and fold, we implemented lambda functions properly. Previously, our Lisp could parse lambdas but couldn’t correctly apply them.

Adding Lambda Support

We modified eval to properly capture the current environment and store parameter names:

eval env (List [Atom "lambda", List params, body]) =
    case mapM getParamName params of
        Right paramNames -> return $ Lambda paramNames body env
        Left err -> throwError err
  where
    getParamName (Atom name) = Right name
    getParamName badArg = Left $ TypeMismatch "Expected parameter name" badArg

When a lambda function is applied, it creates a new local environment that maps function parameters to actual arguments.

apply (Lambda params body closure) args = do
    env <- liftIO $ readIORef closure
    if length params == length args
        then do
            let localEnv = Map.union (Map.fromList (zip params args)) env
            newEnvRef <- liftIO $ newIORef localEnv
            eval newEnvRef body
        else throwError $ NumArgs (length params) args

Example

Now, we can define and call lambda functions:

(define square (lambda (x) (* x x)))
(square 5)  ;; 25

Higher-Order List Functions

Now that lambda functions work, we can introduce list processing functions.

Map

map applies a function to each element in a list and returns a new list.

listMap :: [LispVal] -> IOThrowsError LispVal
listMap [Lambda params body env, List xs] =
    List <$> mapM (\x -> apply (Lambda params body env) [x]) xs
listMap args = throwError $ TypeMismatch "Expected a function and a list" (List args)

Example

(map (lambda (x) (* x 2)) '(1 2 3 4))
;; => (2 4 6 8)

Filter

filter removes elements that don’t satisfy a given predicate.

listFilter :: [LispVal] -> IOThrowsError LispVal
listFilter [func@(Lambda _ _ _), List xs] = do
    filtered <- filterM (\x -> do
        result <- apply func [x]
        case result of
            Bool True  -> return True
            Bool False -> return False
            _          -> throwError $ TypeMismatch "Expected boolean return" result
        ) xs
    return $ List filtered
listFilter args = throwError $ TypeMismatch "Expected a function and a list" (List args)

Example

(filter (lambda (x) (> x 5)) '(2 4 6 8))
;; => (6 8)

Fold (Reduce)

foldl and foldr accumulate values from left to right or right to left.

listFoldL :: [LispVal] -> IOThrowsError LispVal
listFoldL [Lambda params body env, initial, List xs] =
    foldM (\acc x -> apply (Lambda params body env) [acc, x]) initial xs
listFoldL args = throwError $ TypeMismatch "Expected a function, initial value, and a list" (List args)
listFoldR :: [LispVal] -> IOThrowsError LispVal
listFoldR [Lambda params body env, initial, List xs] =
    foldM (\acc x -> apply (Lambda params body env) [x, acc]) initial (reverse xs)
listFoldR args = throwError $ TypeMismatch "Expected a function, initial value, and a list" (List args)

Example

(foldl (lambda (acc x) (+ acc x)) 0 '(1 2 3 4 5))
;; => 15

This works like (((((0 + 1) + 2) + 3) + 4) + 5).

Whilst swapping out foldr for foldl in this scenario gives us the same result, it’s very different in execution. It ends up working like (1 + (2 + (3 + (4 + (5 + 0))))).

Sort

sort Sorts a list in ascending order by default or with a custom comparator.

listSort :: [LispVal] -> ThrowsError LispVal
listSort [List xs] =
    case xs of
        [] -> return $ List []
        (Number _:_) -> return $ List (sortBy compareNumbers xs)
        (String _:_) -> return $ List (sortBy compareStrings xs)
        _ -> throwError $ TypeMismatch "Cannot sort mixed types" (List xs)
  where
    compareNumbers (Number a) (Number b) = compare a b
    compareStrings (String a) (String b) = compare a b

listSort [Lambda params body closure, List xs] =
    case xs of
        [] -> return $ List []
        _  -> throwError $ TypeMismatch "Custom sorting requires ThrowsErrorIO" (List xs)
        -- If you later want custom sorting, you'd need `ThrowsErrorIO`
listSort args = throwError $ TypeMismatch "Expected a list (optionally with a comparator function)" (List args)

Example

(sort '(5 3 8 1 4))
;; => (1 3 4 5 8)

Optionally, the implementation allows you to specify a predicate to control the sort.

String Manipulation

Strings are now treated as lists of characters in our Lisp. This can sometimes make things easier to work with when dealing with strings.

Example

We can convert a string into a list (and therefore operate on it like it’s a list) by using string->list.

stringToList :: [LispVal] -> ThrowsError LispVal
stringToList [String s] = return $ List (map (String . (:[])) s)
stringToList args = throwError $ NumArgs 1 args
(string->list "hello")
;; => ("h" "e" "l" "l" "o")

We reverse this process with list->string.

listToString :: [LispVal] -> ThrowsError LispVal
listToString [List chars] = case mapM extractChar chars of
    Right strList -> return $ String (concat strList)
    Left err -> throwError err
  where
    extractChar (String [c]) = Right [c]
    extractChar invalid = Left $ TypeMismatch "Expected a list of single-character strings" invalid
listToString args = throwError $ NumArgs 1 args
(list->string '("h" "e" "l" "l" "o"))
;; => "hello"

Conclusion

We now how have higher order functions and lambda functions controlling our list processing. Stay tuned for further updates as we add more features to our Lisp.

Writing Your Own Lisp Interpreter in Haskell - Part 4

Introduction

In the previous post we added conditionals to our basic Lisp interpreter. Now, it’s time to introduce list manipulation – one of Lisp’s most fundamental features.

This update brings support for:

  • Pairs (cons), first element (car), and rest (cdr)
  • List predicates (null?)
  • Common list operations (append, length, reverse)
  • Proper parsing of quoted lists ('(...))

Pairs and Lists

In Lisp, lists are built from pairs (cons cells). Each pair contains a head (car) and a tail (cdr). We’ll add Pair into our LispVal data type:

data LispVal
    = Atom String
    | Number Integer
    | Bool Bool
    | String String
    | List [LispVal]
    | Pair LispVal LispVal  
    | Lambda [String] LispVal Env
    | BuiltinFunc ([LispVal] -> ThrowsError LispVal)

This allows us to represent both lists and dotted pairs like:

(cons 1 2)    ;; (1 . 2)
(cons 1 '(2)) ;; (1 2)

cons, car, and cdr

cons is a function in most dialects of Lisp that constructs memory objects which hold two values or pointers to two values.

cons :: [LispVal] -> ThrowsError LispVal
cons [x, List xs] = return $ List (x : xs)  
cons [x, y]       = return $ Pair x y       
cons args         = throwError $ NumArgs 2 args

This allows us to build pairs and lists alike:

(cons 1 2)       ;; (1 . 2)
(cons 1 '(2 3))  ;; (1 2 3)

(car and cdr)[https://en.wikipedia.org/wiki/CAR_and_CDR] are list primitives that allow you to return the first or second component of a pair.

The expression (car (cons x y)) evaluates to x, and (cdr (const x y)) evaluates to y.

car :: [LispVal] -> ThrowsError LispVal
car [List (x : _)] = return x
car [Pair x _]     = return x  
car [List []]      = throwError $ TypeMismatch "Cannot take car of empty list" (List [])
car [arg]          = throwError $ TypeMismatch "Expected a pair or list" arg
car args           = throwError $ NumArgs 1 args

cdr :: [LispVal] -> ThrowsError LispVal
cdr [List (_ : xs)] = return $ List xs  
cdr [Pair _ y]      = return y          
cdr [List []]       = throwError $ TypeMismatch "Cannot take cdr of empty list" (List [])
cdr [arg]           = throwError $ TypeMismatch "Expected a pair or list" arg
cdr args            = throwError $ NumArgs 1 args

We can now uwe these functions to work with our lists and pairs:

(car '(1 2 3))   ;; 1
(car '(a b c))   ;; a
(car '(5 . 6))   ;; 5

(cdr '(1 2 3))   ;; (2 3)
(cdr '(a b c))   ;; (b c)
(cdr '(5 . 6))   ;; 6

Checking for Empty Lists

We need a way to determine if our list is empty, and we do that with isNull:

isNull :: [LispVal] -> ThrowsError LispVal
isNull [List []] = return $ Bool True
isNull [_]       = return $ Bool False
isNull args      = throwError $ NumArgs 1 args

This is pretty straight forward to use:

(null? '())      ;; #t
(null? '(1 2 3)) ;; #f

Extending List Operations

Going a little bit further now, we can easily implement append, length, and reverse.

listAppend :: [LispVal] -> ThrowsError LispVal
listAppend [List xs, List ys] = return $ List (xs ++ ys)
listAppend [List xs, y] = return $ List (xs ++ [y])  
listAppend [x, List ys] = return $ List ([x] ++ ys)  
listAppend args = throwError $ TypeMismatch "Expected two lists or a list and an element" (List args)

listLength :: [LispVal] -> ThrowsError LispVal
listLength [List xs] = return $ Number (toInteger (length xs))
listLength [arg] = throwError $ TypeMismatch "Expected a list" arg
listLength args = throwError $ NumArgs 1 args

listReverse :: [LispVal] -> ThrowsError LispVal
listReverse [List xs] = return $ List (reverse xs)
listReverse [arg] = throwError $ TypeMismatch "Expected a list" arg
listReverse args = throwError $ NumArgs 1 args

These functions allow us to perform some more interesting processing of our lists:

(append '(1 2) '(3 4))  ;; (1 2 3 4)
(append '(a b) 'c)      ;; (a b c)
(append 'a '(b c))      ;; (a b c)

(length '(1 2 3 4 5))   ;; 5
(length '())            ;; 0

(reverse '(1 2 3 4 5))   ;; (5 4 3 2 1)
(reverse '())            ;; ()

Quoted Lists

Finally, Lisp allows shorthand notation for quoting lists. For example, '(1 2 3) is equivalent to (quote (1 2 3)).

parseQuote :: Parser LispVal
parseQuote = do
    char '\''
    expr <- parseExpr 
    return $ List [Atom "quote", expr]

Conclusion

Our Lisp interpreter is now becoming a little more sophisticated. List processing is so fundamental to how Lisp operates that we needed to get this implemented as soon as possible. The code for this particular article is available up on GitHub to pull down and take a look at.

(define names '("Sally" "Joe" "Tracey" "Bob"))
("Sally" "Joe" "Tracey" "Bob")

(reverse names)
("Bob" "Tracey" "Joe" "Sally")

(car (cdr (reverse names)))
"Tracey"

(append names '("Stacey" "Peter"))
("Sally" "Joe" "Tracey" "Bob" "Stacey" "Peter")

Writing Your Own Lisp Interpreter in Haskell - Part 3

Introduction

In our previous post, we introduced persistent variables into our Lisp interpreter, making it possible to store and retrieve values across expressions.

Now, it’s time to make our Lisp smarter by adding conditionals and logic.

In this post, we’ll extend our interpreter with:

  • if expressions
  • Boolean logic (and, or, xor, not)
  • String support for conditionals
  • Expanded numeric comparisons (<=, >=)

By the end of this post, you’ll be able to write real conditional logic in our Lisp, compare both numbers and strings, and use logical expressions effectively.

Adding if Statements

We start with the classic Lisp conditional expression:

(if (< 10 5) "yes" "no")  ;; Expected result: "no"
(if (= 3 3) "equal" "not equal")  ;; Expected result: "equal"

We add support for this by adjusting eval:

eval env (List [Atom "if", condition, thenExpr, elseExpr]) = do
    result <- eval env condition
    case result of
        Bool True  -> return thenExpr  -- Return without evaluating again
        Bool False -> return elseExpr  -- Return without evaluating again
        _          -> throwError $ TypeMismatch "Expected boolean in if condition" result

Testing

We can see this in action now:

λ> (if (> 10 20) "yes" "no")
"no"
λ> (if (= 42 42) "match" "no-match")
"match"
λ> (if #f 10 20)
20

Expanding Boolean Logic

Now, we’ll add some boolean operators that are standard in conditionals:

  • (and ...) → Returns #t if all values are #t.
  • (or ...) → Returns #t if at least one value is #t.
  • (xor ...) → Returns #t if exactly one value is #t.
  • (not x) → Returns #t if x is #f, otherwise returns #f.

These functions get added to Eval.hs:

booleanAnd, booleanOr, booleanXor :: [LispVal] -> ThrowsError LispVal

booleanAnd args = return $ Bool (all isTruthy args)  -- Returns true only if all args are true
booleanOr args = return $ Bool (any isTruthy args)  -- Returns true if at least one arg is true

booleanXor args =
    let countTrue = length (filter isTruthy args)
    in return $ Bool (countTrue == 1)  -- True if exactly one is true

notFunc :: [LispVal] -> ThrowsError LispVal
notFunc [Bool b] = return $ Bool (not b)  -- Negates the boolean
notFunc [val] = throwError $ TypeMismatch "Expected boolean" val
notFunc args = throwError $ NumArgs 1 args

isTruthy :: LispVal -> Bool
isTruthy (Bool False) = False  -- Only #f is false
isTruthy _ = True  -- Everything else is true

These functions get added as primitives to our Lisp:

primitives =
  [ ("not", BuiltinFunc notFunc),
    ("and", BuiltinFunc booleanAnd),
    ("or", BuiltinFunc booleanOr),
    ("xor", BuiltinFunc booleanXor)
  ]

Testing

We can now exercise these new built-ins:

λ> (and #t #t #t)
#t
λ> (or #f #f #t)
#t
λ> (xor #t #f)
#t
λ> (not #t)
#f

We now have a full suite of logical operators.

Strings

Before this point, our Lisp has been very number based. Strings haven’t really seen much attention as our focus has been on putting together basic functionality first. With conditionals being added into our system, it’s time to give strings a little bit of attention.

First job is to expand = to also support strings.

numericEquals [Number a, Number b] = return $ Bool (a == b)
numericEquals [String a, String b] = return $ Bool (a == b)  -- Added string support
numericEquals args = throwError $ TypeMismatch "Expected numbers or strings" (List args)

Testing

We can see this in action now with a string variable:

λ> (define name "Joe")
"Joe"
λ> (if (= name "Joe") "yes" "no")
"yes"
λ> (if (= name "Alice") "yes" "no")
"no"

More Numeric Comparators

To round out all of our comparison operators, we throw in implementations for <= and >=.

numericLessThanEq [Number a, Number b] = return $ Bool (a <= b)
numericLessThanEq args = throwError $ TypeMismatch "Expected numbers" (List args)

numericGreaterThanEq [Number a, Number b] = return $ Bool (a >= b)
numericGreaterThanEq args = throwError $ TypeMismatch "Expected numbers" (List args)

These also require registration in our primitive set:

primitives =
  [ ("<=", BuiltinFunc numericLessThanEq),
    (">=", BuiltinFunc numericGreaterThanEq)
  ]

Conclusion

We’ve added some great features to support conditional process here. As always part 3 of the code to follow this tutorial is available.

Writing Your Own Lisp Interpreter in Haskell - Part 2

Introduction

In our previous post we put a very simple Lisp interpreter together that was capable of some very basic arithmetic.

In today’s update, we’ll introduce variable definitions into our Lisp interpreter, allowing users to define and retrieve values persistently. This required a number of structural changes to support mutable environments, error handling, and function lookups.

All the changes here will set us up to do much more sophisticated things in our system.

If you’re following along, you can find the implementation for this article here.

Mutable Environment

In order to store variables in our environment, we need to make it mutable. This way we can store new values in the environment as we define them.

Env was originally a pure Map:

type Env = Map String LispVal

This meant that variable bindings were immutable and couldn’t persist across expressions.

We changed Env to an IORef (Map String LispVal), making it mutable:

type Env = IORef (Map String LispVal)

We added nullEnv to create an empty environment:

nullEnv :: IO Env
nullEnv = newIORef Map.empty

Why?

  • This allows variables to persist across expressions.
  • Future changes (like set! for modifying variables) require mutability.
  • IORef enables safe concurrent updates in a controlled manner.

REPL update

Now we need to update our REPL at the top level to be able to use this mutable state.

Previously, our REPL was just using the primitiveEnv value.

main :: IO ()
main = do
    putStrLn "Welcome to Mini Lisp (Haskell)"
    repl primitiveEnv

We now pass it in as a value. Note that the underlying types have changed.

main :: IO ()
main = do
    env <- primitiveEnv  -- Create a new environment
    putStrLn "Welcome to Mini Lisp (Haskell)"
    repl env

Why?

  • The REPL now uses a mutable environment (primitiveEnv).
  • This ensures variables persist across expressions instead of resetting each time.

Variable Definition

We introduced defineVar to allow defining variables:

defineVar :: Env -> String -> LispVal -> IOThrowsError LispVal
defineVar envRef var val = do
    env <- liftIO $ readIORef envRef  -- Read environment
    liftIO $ writeIORef envRef (Map.insert var val env)  -- Update environment
    return val

This enables us to define variables like this:

(define x 10)

defineVar reads the current environment, updates it, and then writes it back.

Evaluation

Probably the biggest change is that our evaluation no longer returns just a ThrowsError LispVal.

eval :: Env -> LispVal -> ThrowsError LispVal

This has had to be upgraded to support our IO activity as we now have mutable state.

eval :: Env -> LispVal -> IOThrowsError LispVal

This change allows eval to interact with mutable variables stored in Env and perform IO actions when updating environment bindings

We also added parsing support for define:

eval env (List [Atom "define", Atom var, expr]) = do
    val <- eval env expr
    defineVar env var val

Variable Lookup

Our lookupVar now needs an upgrade:

lookupVar :: Env -> String -> ThrowsError LispVal
lookupVar env var = case Map.lookup var env of
    Just val -> Right val
    Nothing  -> Left $ UnboundVar var

It’s not designed to work in a mutable IORef environment. We create getVar to accomodate.

getVar :: Env -> String -> IOThrowsError LispVal
getVar envRef var = do
    env <- liftIO $ readIORef envRef  -- Read environment from IORef
    case Map.lookup var env of
        Just val -> return val
        Nothing  -> throwError $ UnboundVar ("Undefined variable: " ++ var)

This now allows variables to be defined and retrieved across multiple expressions.

Builtins

Previously, built-in functions were not stored as part of the environment.

primitives :: [(String, LispVal)]
primitives =
  [ ("+", BuiltinFunc numericAdd),
    ("-", BuiltinFunc numericSub),
    ("*", BuiltinFunc numericMul),
    ("/", BuiltinFunc numericDiv)
  ]

This has changed now with primitiveEnv which will store a set of these.

primitiveEnv :: IO Env
primitiveEnv = newIORef (Map.fromList primitives)

This change enables us to dynamically add more built-in functions in the future.

Fixing eval

With the introduction of IO into our program, our evaluation logic needed updates to handle variable bindings correctly.

eval env (List (Atom func : args)) = do
    func' <- eval env (Atom func)
    args' <- mapM (eval env) args
    apply func' args'

Now, we’ll look up the function in the environment:

eval env (List (Atom func : args)) = do
    func' <- getVar env func  -- Look up function in the environment
    args' <- mapM (eval env) args  -- Evaluate arguments
    apply func' args'

Now, we’ll find any of our functions in the environment itself.

Fixing apply

Now, we need to look at the apply function.

apply (BuiltinFunc f) args = f args

We add support for functions out of the environment with the liftThrows helper:

apply (BuiltinFunc f) args = liftThrows $ f args

Provision is also added for user-defined functions (lambda):

apply (Lambda params body closure) args = do
    env <- liftIO $ readIORef closure  -- Read function's closure environment
    if length params == length args
        then eval closure body
        else throwError $ NumArgs (length params) args

ThrowsError

Previously, ThrowsError was used for error handling:

type ThrowsError = Either LispError

However, since we now interact with IO, we introduce IOThrowsError:

type IOThrowsError = ExceptT LispError IO

We also add helper functions to manage conversions between them:

runIOThrows :: IOThrowsError String -> IO String
runIOThrows action = runExceptT action >>= return . extract
  where
    extract (Left err)  = "Error: " ++ show err
    extract (Right val) = val

liftThrows :: ThrowsError a -> IOThrowsError a
liftThrows (Left err)  = throwError err
liftThrows (Right val) = return val

Why?

  • Allows IO operations inside error handling (necessary for mutable Env).
  • Prevents mixing IO and pure computations incorrectly.
  • Enables future features like reading files, user-defined functions, etc.

Fixing readExpr

Finally, we need to fix readExpr. It’s current defined like this:

readExpr :: String -> ThrowsError LispVal

It changes to support IOThrowsError:

readExpr :: String -> IOThrowsError LispVal
readExpr input = liftThrows $ case parse parseExpr "lisp" input of
    Left err -> Left $ ParserError (show err)
    Right val -> Right val

This allows readExpr to integrate with our new IOThrowsError-based evaluator.

Running

With all of these pieces in place, we can use define to define variables and start to work with them.

Welcome to Mini Lisp (Haskell)
λ> (define a 50)
50
λ> (define b 120)
120
λ> (define c 4)
4
λ> (+ (- b c) a)
166
λ>

Conclusion

This update introduced:

  • Persistent variables using define
  • A mutable environment with IORef
  • Function lookup inside the environment
  • A fully working REPL that retains state across expressions

We’ll continue to add to this as we go. See you in the next chapter!