It shags the mind!

Posted on 2020-08-08; last updated 2020-08-13

As announced earlier, I’ve been streaming and I even got around to editing it. It was good to get back to it. It was tough that it’s still so hot around here. It wasn’t so good that I forgot so much of my best practices that I still wasn’t able to start on time with no technical glitches. This is the place where I’d like to say “live and learn”, but for some reason it doesn’t want to apply to me.

But enough meta, let’s talk brainfuck.

Esolangs

Did I ever mention I’ve got a sweet spot for esolangs?

Esoteric programming languagess are the perfect counterexample to a lot of ill-conceived opinions outsiders tend to build about programming languages and programming in general.

  • programming languages are deterministic
  • programming languages are friendly
  • programming languages need
    • Turing-completeness
    • a loop construct
    • data structures
    • function definitions
    • objects (lol)
    • anything specific, really
    to be of any use
  • C++ and Java are adequate programming languages
  • programming languages have a tree structure
  • programming languages compose from EBCDIC, ASCII or Unicode
  • programming languages are serious business

One does not simply code in Malbolge

I love perfect counterexamples.

Brainfuck

Classic brainfuck is generally classified as a Turing tarpit, though IMHO in that category it’s really far from being the worst offender. Its mode of operation is actually very similar to an “actual” Turing machine, with the transition table replaced by a reified structured AST.

It’s probably the most popular esolang there is. Its unforgettable name may have a lot to do with it. But its ease of implementation undoubtedly played a part too.

Its stated design goal on first release was to have the smallest possible compiler. Indeed, that language is much easier to compile than to interpret. The original compiled to Amiga machine code, but it’s just as easy to compile to Perl. Let’s do just that.

You can check out the CG puzzle for details on the specific dialect that’s expected. For a more general summary:

  • < and > move an I/O cursor left or right on the memory tape.
  • + and - increment or decrement the value at the cursor.
  • , and . read and write a byte to/from the tape.
  • [ and ] run what’s between them as long as the cursor points to a non-null. Caveats:
    • They can nest.
    • The cursor can move in-between, and most likely will. The check is performed at the time the square brackets are encountered in the code flow.

Compiling

my %instructions = (
  '<' => ' $pointer--;                      ',
  '>' => ' $pointer++;                      ',
  '+' => ' $array[$pointer]++;              ',
  '-' => ' $array[$pointer]--;              ',
  '.' => ' print chr($array[$pointer]);     ',
  ',' => ' $array[$pointer] = ord(getchar); ',
);

Brainfuck instructions directly map to the Perl ones! We can compile programs by simple text substitution:

sub compile { shift =~ s/./$instructions{$&}/gre }

write_file 'null.pl', compile( '.'      );  # output a NUL
write_file 'incr.pl', compile( ',+.'    );  # increment a byte
write_file 'swap.pl', compile( ',>,.<.' );  # swap two bytes

…and run them:

$ perl null.pl | od -ta
0000000 nul
0000001
$ perl incr.pl <<< 'A'
B
$ perl swap.pl <<< 'AB'
BA

Look, ma! No loops!

Of course you noticed I left out the looping instructions. They’re the part that can make interpretation slightly more complicated, as the interpreter will have to track which opening square bracket matches each closing one. But… there’s no such issue with a compiler. We can directly convert each bracket individually, and leave the pairing chore to the host language!

  '[' => ' while ( $array[$pointer] ) { ',
  ']' => ' } ',

In my experience advocating TC languages, I’ve noticed the population splits roughtly half-to-half on whether their subconscious self accepts the possibility of generating unbalanced fragments of host curly braces. If you need to, take a while to ponder what the resulting code ought to look like, and why the scheme works. In the meantime, we’ll be trying out our new feature.

write_file 'cat.pl', compile( ',[.,]'       );
write_file 'dup.pl', compile( ',[..,]'      );
write_file 'add.pl', compile( ',>,[<+>-]<.' );
$ perl cat.pl <<< 'Hello, world!'
Hello, world!
$ perl dup.pl <<< 'Hello, world!'
HHeelllloo,,  wwoorrlldd!!
$ perl add.pl <<< 'A '
a

I love it when a CG puzzle comes together

Finish it!

The CG puzzle made a few specific design choices that we have to take into account. Here’s the list; check out the stream for the actual implementations.

  • tape management
    The original used 30 000 looparound cells. A theoretical “strictly” Turing-complete one requires two-way infinite1 (hence non-looping) one. The norm is to loop, as that’s the easiest non-intrusive way to provide left-openness. The CG puzzle uses a fixed-size non-looping one, size given as an input, and makes overflow a verified error condition.
  • cell size
    Most implementations, including the original, use 8-bit wraparound bytes. The CG puzzle doesn’t wrap, and makes overflow and underflow a verified error condition.
  • EOF
    Many implementations return 0 on EOF. Not returning anything or returning -12 were part of the original distribution. The CG puzzle makes EOF a verified error condition.
  • input format
    Most implementations are simply byte-based: an input is a byte or EOF. The CG puzzle takes the most peculiar decision to feature ill-formed bytes3 that have to be detected and reported.

That about sums it up for compilation. +50 XP, ka-ching!

Interpreting

Claim: the core issue writing a brainfuck interpreter is how to handle loops.

The loop cycle

The tricky aspect of loops is that in brainfuck they’re what most languages would call “while” loops.

while (condition)
{
   block
}

These can run, on a lower level, as something like this:

100 IF NOT condition THEN 400
200 block
300 GOTO 100
400 ...

With peephole vision, this entails:

  • The opening bracket needs a pointer to the closing one: the 100→400 link.
  • The closing bracket needs a pointer to the opening one:the 300→100 link.

Take a while to understand how this is worse (harder to compile) than a “do”/“repeat” looping construct.

Yo, dawg! I heard you like loops, so I put loops in your loops so your interpreter is messed up.

The wart

This cycle is the root cause for why simple interpretation strategies will necessarily have a wart of some sort. Here are some coping strategies:

  • We can maintain a stack of the current loop start positions. Interpreting an opening bracket pushes the current position to the stack. Interpreting a closing bracket resumes interpretation from the point of the stack’s top.

    The wart is that the final, failing check of the condition will need to pop the stack and resume interpretation from the point of the closing bracket’s position, which we don’t have at the ready4. So we’ll need some way to skip to the matching bracket. It can be tackled as a parsing problem: move forward, counting the nesting level and stopping when it matches. It can be tackled as an interpretation problem: walk the code as usual, but in some kind of a “no-operation” mode.

    In a way, this is what I do in the first part of the interpreter’s implementation on the stream: the stack is the implicit call stack and the skip function counts the brackets.

  • We can do away with the stack and accept the “parsing” way of doing for both seeking directions.

  • We can duplicate the condition checking on the closing bracket. (That’s what the CG puzzle suggests we do.5) As the null loop case still has to be accounted for, that’s merely an optimisation; the wart remains.

  • We can parse the entire AST ahead of time. The wart here is that, for an interpreter, we’re stepping dangerously close to compiler territory. Still, that’s what I do6 in the second part of the interpreter’s implementation on the stream.

The stream expresses my dismay at the clunky situation the CG puzzle puts us in: we’re supposed to write an interpreter, but we have to detect malformed code statically before it’s noticeably bad. How un-interpretey!7 Well, that ship has sailed, no need to brood over it any longer.

Parsing

With that out of the way, let’s bite the bullet and write the parser. Haskell really shines in parser combinator technology, it’d be ridiculous not to use them.

A brainfuck program is a sequence of “actions”, an umbrella term I’m introducing to be able to split between the six atomic instructions and the loops. That’ll make for a simple AST.

data Program = Block [Action]
data Action = Simple Instruction | Loop Program
data Instruction = Fwd | Bwd | Inc | Dec | Out | In

The parser is then little more than expansion on that structure. With a bit of careful thinking to dodge the edge cases (why that satisfy (/= ']') is necessary for correctness, for instance—watch the stream for the details). And a bit more thinking to gracefully integrate the comments’ parsing8 (ditto).

import Text.Parsec

type Parser = Parsec String ()

program :: Parser Program
program = fmap (Block . catMaybes) $ many $
      Just <$> action
  <|> satisfy (/= ']') $> Nothing

action :: Parser Action
action = Simple <$> instruction
     <|> Loop <$> between (char '[') (char ']') program

instruction :: Parser Instruction
instruction = char '>' $> Fwd
          <|> char '<' $> Bwd
          <|> char '+' $> Inc
          <|> char '-' $> Dec
          <|> char '.' $> Out
          <|> char ',' $> In

It’s worth noting that handling comments takes a lot of space compared to the Perl-based compiler. Here we need to explicitly ignore them, and that’s the major cause of the program parser’s complexity.

Executing

Now the hard part is done, the implementation is just a simple9 fill-in of each instruction. And the definition of a brainfuck interpretation monad using the mtl.

type Data = Zipper Int
type Inputs = [Int]
data BfState = S { sData :: Data, sInputs :: Inputs }
type Output = [Char]
type BfInterpreter = RWS () Output BfState

interpretBf :: Program -> BfInterpreter ()
interpretBf (Block as) = traverse_ interpretA as

interpretA :: Action -> BfInterpreter ()
interpretA (Simple Fwd) = modify (onTape moveRight)
interpretA (Simple Bwd) = modify (onTape moveLeft)
interpretA (Simple Inc) = modify (onTape succ)
interpretA (Simple Dec) = modify (onTape pred)
interpretA (Simple Out) =
  tell . pure . chr =<< gets (zCur . sData)
interpretA (Simple In)  =
  gets (head . sInputs) >>= \i ->
  modify (onTape (const i) . onInputs tail)
interpretA (Loop p) = fix $ \loop ->
  gets (zCur . sData) >>= \case 0 -> pure ()
                                _ -> interpretBf p *> loop

I’m not expanding on the zipper data type, it’s not too relevant now when the stream has enough details. Same for onTape and onInputs, they’re simple ad-hoc10 lens over BfState.

Of notable interest to outsiders is how the Inputs are a part of the state instead of the “reader” part of RWS. In an immutable context, we couldn’t have a read operation return the next input each time using a simple reader11. So we make the inputs a part of the state, and explicitly consume them when executing the read operation.

So really, the complex part is just the looping. If you squint past my keystroke aversion, its implementation is just reading the tape, checking for zero, and either doing nothing or running one iteration before trying again.

And that’s all there is to it!

That's all Folks!

Wait, what?

Ok, ok, it’s not. We need to take care of the puzzle’s idiosyncratic error management. Fortunately, the mtl’s got our back covered.

type BfInterpreter = RWST () Output BfState (Except String)

We just insert an Except monad there12. This is akin to allowing our computation to return an Either error result type13. Given the way we handle errors, which side we insert it is mostly irrelevant14, but this one will make our life easier later on.15

We can then integrate error handling to the flow. For example instead of simply deferring the > instruction to the tape zipper, we’ll detect overshoot like this:

moveRight :: MonadError String m => Data -> Data
moveRight d = case zipRight d of
  Just d' -> pure d'
  Nothing -> throwError "POINTER OUT OF BOUNDS"

…at the cheap cost of making two of our helpers monadic. Details in the stream.

The advantage of using the common Except interface is that we can share the same error management between the runtime errors thrown during interpretation and the parse-time “syntax” errors. With a bit more fiddling, we can actually reduce the number of calls to putStr to a single one. I’m quite happy with how the toplevel function turns out.

main :: IO ()
main = do
  [l,s,_] <- map read . words <$> getLine
  code <- concat <$> replicateM l getLine
  inputs <- map read . words <$> getContents
  let tape = Z [] 0 (replicate (s-1) 0)
      Right output = runExcept $ flip catchError pure $ do
        pgm <- withExceptT (const "SYNTAX ERROR") $ ExceptT $
               runParserT (program <* eof) () "brainfuck" code
        snd <$> execRWST (interpret pgm) () (S tape inputs)
  putStr output

The only remaining infelicity, IMHO, is the partial match to Right output. It’s guaranteed to succeed since the code structure, runExcept (... `catchError` pure), can’t possibly return a Left. But I haven’t found a suitable way of shifting that knowledge to the code syntax. Yet.16

So there you have it. A full brainfuck interpreter in Haskell using nothing but standard libraries even CG has, and wacky error management to boot!

But why?

That’s a great question. It has multiple answers, depending on which aspect you’re interested in. And then some.

  • Brainfuck is a great language. The “mind-expanding” kind. You probably won’t code in it for a living17. Or have to read too much of others’ code. But writing anything non-trivial requires a drastic shift in perspective compared to more mainstream languages: a lot of the algorithm ends up encoded on the tape instead of plainly in the source. Understanding that deeply enough to write stuff takes some practice.

  • There’s a recurring myth that compilers are scary beasts, interpreters not that far behind. This really needs to be dispelled. The brainfuck case stands out with the compiler being typically easier to implement than the interpreter, but neither of them were complicated to write.

  • It helps that brainfuck is a simple language, though.

  • Perl rocks at string processing. But you already knew that.

  • Haskell rocks at parsing. But you already knew that.

  • Haskell also rocks at maintaining correctness at a high level. You already knew that, but hopefully seeing it live helped carve it in a bit deeper. IMHO the most remarkable occurrences in this stream were first moving from an IO/stdout-bound interpreter to a pure one, then adding error management without having to rewire the entire code.

  • Oh, and 50 XP.

Anyhoo

My currently published solutions in Perl and Haskell are subtly refined versions of the ones presented on stream and here. Drop a comment there or elsewhere if you notice anything wrong.

He done yet?

Yeah, this wall of text is long enough as is. Glad to have had you, hope you enjoyed the read and see you next time!


Thanks to @dbdr and @Astrobytes for the helpful corrections!


  1. I’m not quite sure what can be computed with a two-way infinite tape that couldn’t with a one-way infinite one. Let me know. 🧐 @dbdr confirmed my intuition that both are indeed equivalent in power. 🙏↩︎

  2. Did you need a reason for wraparound bytes? 🤣↩︎

  3. It sounds unbelievable until you read the input format specification. 🥴↩︎

  4. We don’t just have it from the previous iteration: while(false) is a legal construct. 😨↩︎

  5. But I won’t! 😈↩︎

  6. for different reasons 🤐↩︎

  7. Eww. 🤢↩︎

  8. Those cool $> operators were simple sequences of *> pure during the stream, but I’m trying to get my mind used to them in contexts more involved than simple container functors. Plus I get to trigger #Fr’s greatest Haskell operator fan. Who am I to resist? 😇↩︎

  9. seriously 🙈↩︎

  10. Because CG doesn’t have a single lens library available. 😢↩︎

  11. It is possible to pull this off using the reader, thanks to the local function in the MonadReader class. I’m not quite sure it performs well, but who knows. I am sure it makes the interpreter a whole lot messier, so that’s not the path I take for the stream. 💀↩︎

  12. I can never remember if this side is the top or bottom of the monad stack. 😕↩︎

  13. In this position, it’s better than akin, it’s an Identity away. But we’ll use it from the abstract interface later on, so Except it is. 🤓↩︎

  14. It would be if the puzzle was explicitly requiring errors to replace output or to be merged with it. It isn’t, which is ok as the validators propertly reflect that. 😌↩︎

  15. That’s way too high a footnote density for so small a paragraph. 😱↩︎

  16. Using vanilla Either doesn’t really cut it for lack of an available withExceptT alternative. 😞↩︎

  17. It’s been reported that some aspect of pentesting is getting code to match very strict and arbitrary constraints. Brainfuck is a gateway to that. 😎↩︎