This is part three of a six-part tour of a no-frills Brainfuck interpreter in Haskell. The source code for this project is available on github, and each post is written in literate Haskell, so you can execute these documents directly with GHC.
Beyond parsing, there’s a single pre-processing step that we’ll need in order to execute a given program: we need to map out which jump instructions ([
and ]
) match with which others.
To take the smallest possible example: given the program [JumpAhead, JumpBack]
, we want to know that the JumpAhead
at index 0 matches the JumpBack
at index 1, and vice-versa.
We start with some standard imports:
module Brainfuck.JumpMap where
import Brainfuck.Types
import qualified Data.Map as Map
import qualified Data.Vector as Vec
A JumpMap
is a Data.Map.Map
(also known as a hash map) with Index
keys and Index
values:
type JumpMap = Map.Map Index Index
Even though you and I know that a JumpMap
is really just a Map.Map Index Index
, I’d prefer to keep that fact hidden as a private implementation detail. In other words, other modules in this program should be able to use JumpMap
s for all their intended purposes without ever using Data.Map
s functions directly.
So given that fact and the fact that we want to expose an empty JumpMap
, here’s a quick alias:
empty :: JumpMap
= Map.empty empty
There are exactly two types of jump operations we’re concerned with: [
and ]
–a jump ahead and a jump back. Here’s a data type to represent them:
data Jump = Ahead | Back
As you may recall from part one, we’ve already defined a Program
type, which is a vector of commands. We’re enhancing that type here, so let’s call the thing we’re constructing a NumberedProgram
:
type NumberedProgram = [(Index, Command)]
Next, we’re going to want a list of every jump in the program, in the form of (Index, Jump)
pairs. This function iterates through a NumberedProgram
, converting JumpAhead
and JumpBack
commands into Ahead
and Back
jumps, discarding the rest:
type NumberedJump = (Index, Jump)
onlyJumps :: NumberedProgram -> [NumberedJump]
= []
onlyJumps [] JumpAhead):xs) = (idx, Ahead) : onlyJumps xs
onlyJumps ((idx, JumpBack):xs) = (idx, Back) : onlyJumps xs
onlyJumps ((idx, :xs) = onlyJumps xs onlyJumps (_
The next function, jumpMap'
is a real doozy. It does the hard part of building a jump map: figuring out which [
goes with which ]
. It uses a stack to keep track of open [
s, popping them off when it reaches a ]
:
jumpMap' :: JumpMap -> [NumberedJump] -> [NumberedJump] -> JumpMap
= acc
jumpMap' acc [] [] @(_,Ahead):jumps) = jumpMap' acc (j:stack) jumps
jumpMap' acc stack (jAhead):stack) ((bidx,Back):jumps) = jumpMap' (Map.insert aidx bidx acc) stack jumps jumpMap' acc ((aidx,
The jumpmap'
function also presents us with some of this program’s few error cases. In the interest of keeping things simple and not getting too fancy, I’ve chosen to use the built-in error
function, which has the misleading type error :: String -> a
, and in reality just bombs out of the entire program with a given message.
Calling error
like this is considered… not great. It totally circumvents the type system and generally makes it difficult to anticipate and recover from errors. That said, it’s great for this use case because:
Back):_) = error $ "no matching '[' for ']' at " ++ show idx ++ "!"
jumpMap' _ [] ((idx,:_) [] = error $ "no matching ']' for '[' at " ++ show idx ++ "!"
jumpMap' _ ((idx,_)= error "pretty sure this is a bad situation, but I don't know how to put it into words." jumpMap' _ _ _
The pseudo-jump map created above only maps from Ahead
s to Back
s, but we need a map that goes both ways. Here’s a quick function to make a unidirectional map bidirectional:
bidirectionalize :: Ord a => Map.Map a a -> Map.Map a a
=
bidirectionalize m let kvs = Map.toList m
= map (\(k, v) -> (v, k)) kvs
vks in Map.fromList (kvs ++ vks)
Finally, bring it all together and write a function that builds a JumpMap
for a given Program
.
makeJumpMap :: Program -> JumpMap
=
makeJumpMap prog let numbered = zip indexes (Vec.toList prog)
= onlyJumps numbered
jumps in bidirectionalize $ jumpMap' Map.empty [] jumps
where
indexes :: [Index]
= map Index ([0 ..] :: [Int]) indexes
We now have a complete, type-safe, and verified-valid Brainfuck program in memory. We’re halfway there! Next, we’ll start laying the groundwork for actually executing a program by building a representation of runtime memory.