Building Fizzbuzz in Fractran from the Bottom Up

In this post, I am going to show you how to write Fizzbuzz in the programming language Fractran. If you dont know, Fractran is an esoteric programming language. That means it is extraordinary difficult to write any program in Fractran. To mitigate this difficultly, instead of writing Fizzbuzz in raw Fractran, what we are going to do is build a language that compiles to Fractran, and then write Fizzbuzz in that language.

This post is broken up into three parts. The first part covers what Fractran is and a way of understanding what a Fractran program does. Part 2 will go over the foundation of the language we will build and how it will map to Fractran. Finally, in Part 3, we will keep adding new features to the language until it becomes easy to write Fizzbuzz in it.


Part 1: Understanding Fractran

Before we can start writing programs in Fractran, we have to first understand what Fractran is. A Fractran program is represented as just a list of fractions. To execute a Fractran program, you start with a variable N=2. You then go through the list of fractions until you find a fraction F, such that N*F is an integer. You then set N=N*F and go back to the beginning of the list of fractions. You keep repeating this process until there is no fraction F such that N*F is an integer.

Since there is no way to print anything with the regular Fractran rules, we are going to add one additional rule on top of the ordinary ones. In addition to the list of fractions, each program will have a mapping from numbers to characters representing the alphabet of the program. After multiplying N by F, whenever the new N is a multiple of one of the numbers in the alphabet, that will print the character that the number maps to. I have written a function, run-fractran, which implements this version of Fractran and included it here. It takes a list of fractions and an alphabet as an alist and executes the program.

Lets walk through a simple example. Lets say we have the following Fractran program:

9/2, 1/5, 5/3

with the alphabet 5->a. To run this program, we start with N=2. We then go through the list fractions until we find a fraction F such that N*F is an integer. On this first step, F becomes 9/2, since N*F = 2 * 9/2 = 9 which is an integer. We then set N to N*F so that N now becomes 9. Repeating this process again, we get F=5/3 and N=N*F=15. Since the number 5 is in the alphabet, and N is now a multiple of 5, we output the character that 5 maps to, a. If we keep repeating these steps, we eventually reach a point where N=1 and we have outputted the string aa. Since 1 times any of the fractions does not result in an integer, the program terminates with the output aa.

At this point, you may be thinking that writing any program in Fractran is nearly impossible. The truth is that there is a simple trick you can use that makes it much easier program Fractran. All you need to do is look at the prime factorization of all of the numbers. Lets see what the above Fractran program looks like if we convert every number into a tuple (a,b,c) where a is the how many times 2 divides the number, b is how many times 3 does, and c is how many times 5 does. The program then becomes:

(0, 2, 0) / (1, 0, 0)
(0, 0, 0) / (0, 0, 1)
(0, 0, 1) / (0, 1, 0)

We also have the tuple (0,0,1) mapping to a for our alphabet. We start with N = (1,0,0). If you don’t know, multiplying two numbers is the same as adding the counts of each prime factors, and division is the same as subtracting the counts. For example, 2 * 6 = (1,0,0) + (1,1,0) = (2,1,0) = 12. With this way of looking at the program, finding a fraction F such that N*F is an integer becomes finding a fraction F such that each element in the tuple N is greater than or equal to the corresponding element in the tuple in the denominator of F. Once we find such F, instead of multiplying N by it, you subtract from each element of N the corresponding value in the denominator of F (equivalent to dividing by the denominator), and add the corresponding value in the numerator (equivalent to multiplying by the numerator). Executing the program with this interpretation proceeds as follows.

We start with N = (1,0,0). Since every value in N is greater than or equal to their corresponding values in the denominator of the first fraction, we subtract every value in the first denominator and then add every value in the numerator to get N = (1,0,0) (1,0,0) + (0,2,0) = (0,2,0). Repeating this again, F becomes the third fraction. Subtracting the denominator and adding the numerator gets us N = (0,1,1). Then since every value in N is greater than or equal to their corresponding element in (0,0,1), we print a. The program continues, just like it did for the original Fractran program.

Basically we can think of every prime number as having a register which can take on non-negative integer values. Each fraction is an instruction that operates on some of the registers. You can interpret a fraction as saying if the current value of each register is greater than or equal to the the value specified by the denominator (the number of times the prime for that register divides the denominator), you subtract from the registers all of the values in the denominator, add all the values specified in the numerator (the number of times the prime for each register divides the numerator), and then jump back to the first instruction. Otherwise, if any register is less than the value specified in the denominator, continue to the next fraction. For example, the fraction 9/2 can be translated into the following pseudocode:

;; If the register corresponding to the prime number 2 
;; is greater or equal to 1
if reg[2] >= 1
  ;; Decrement it by 1 and increment the register 
  ;; corresponding to 3 by 2. 
  reg[2] = reg[2] - 1
  reg[3] = reg[3] + 2
  goto the beginning of the program
;; Otherwise continue with the rest of the program.

Although programming Fractran is still difficult, this technique suddenly makes writing Fizzbuzz in Fractran tractable.


Part 2: Compiling to Fractran

For our compiler, we are going to need to generate a lot of primes. To do so, we will use a function, new-prime, which will generate a different prime each time it is called.1

(defun prime (n)
  "Is N a prime number?"
  (loop for i from 2 to (isqrt n)
        never (multiple n i)))
 
(defparameter *next-new-prime* nil)
 
(defun new-prime ()
  "Returns a new prime we haven't used yet."
  (prog1 *next-new-prime*
    (setf *next-new-prime*
          (loop for i from (+ *next-new-prime* 1)
                if (prime i)
                  return i))))

So now that we’ve got new-prime, we can start figuring out how we are going to compile to Fractran. The first detail we will need to figure out is how to express control flow in Fractran. In other words, we need a way to specify which fractions will execute after each other fractions. This is a problem because after a fraction executes, you always jump back to the first fraction.

Expressing control flow actually winds up being surprisingly easy. For each fraction we can designate a register. Then, we only execute a fraction if its register is set. It is easy to have a fraction conditionally execute depending on whether its register is set by using the trick we are using to interpret a Fractran program. All we need to do is multiply the denominator of each fraction by the prime for the register of that fraction. This way, we will pass over a fraction unless its register is set. Also, all we need to do to specify which fraction should execute after a given fraction is to multiply the numerator of the given fraction by the prime of the register for the next fraction. By doing this, after a fraction executes, it will set the register of the next fraction.

In order to keep track of the primes for the current fraction and for the next fraction, we will have two global variables. The first will be the prime number for the current instruction, and the second will be the prime number for the next instruction:

(defparameter *cur-inst-prime* nil)
(defparameter *next-inst-prime* nil)

We will also need a function advance which will advance the values of the variables once we move on to the next instruction.

(defun advance ()
  (setf *cur-inst-prime* *next-inst-prime*
        *next-inst-prime* (new-prime)))

Now that we’ve got a way of expressing control flow, we can start planning out what the language we will build will look like. From this point on, I am going to call the language we are building, Lisptran. An easy way we represent a Lisptran program is as just a list of expressions. We can have several different kinds of expressions each of which does something different.

The simplest kind of expression we will want is an inline fraction. If a Lisptran expression is just a fraction, we can just add that fraction to the Fractran program being generated.

Another kind of expression that would be useful are labels. Whenever a Lisptran expression is a Lisp symbol, we can interpret that as a label. Each label will be converted into that fraction that is the prime of the next instruction after the label divided by the prime of the label. This way we can jump to the instruction after the label by setting the register for the label. In order to make keeping track of the primes of labels easy, we are going to keep a hash-table, *lisptran-labels*, mapping from labels to the primes for those labels. We will also have a function prime-for-label, which will lookup the prime for a label or assign a new prime if one hasn’t been assigned yet:

(defparameter *lisptran-labels* nil)
 
(defun prime-for-label (label)
  (or (gethash label *lisptran-labels*)
      (setf (gethash label *lisptran-labels*)
            (new-prime))))

One last kind of expression that will be useful are macro calls. A macro call will be a list whose first element is the name of a macro followed by a list of arbitrary Lisp expressions (The expressions don’t have to be Fractran expressions. They can be interpreted however the macro wants them to be.). In order to compile a macro call, we will lookup the function associated with the macro, and call it on the expressions in the rest of the macro call. That function should then return a list of Lisptran expressions which will then be compiled in place of the macro call. After that we just continue compiling the new code generated by the macro expansion.

To keep track of the definitions of macros, we will keep a hash-table *lisptran-macros*, which will map from the name of the macro to the function for that macro. In order to make defining Lisptran macros easy, we can create a Lisp macro deftran, that works in a similar way to defmacro. When defining a macro with deftran, you are really just defining a function which will take the expressions in the macro call, and return a list of Lisptran instructions to be compiled in its place. Here is the definition for deftran:

(defparameter *lisptran-macros* (make-hash-table))
 
(defmacro deftran (name args &body body)
  "Define a Lisptran macro."
  <code>(setf (gethash ',name *lisptran-macros*)
         (lambda ,args ,@body)))

And that’s all of the different kinds of expressions we will need in Lisptran.

Although we now have all of the expressions we need, there are a few more pieces of the compiler we need to figure out. For example, we still haven’t figured out how we are going to represent variables yet. Ultimately this is trivial. We can just assign a register to every variable and keep a mapping from variable names to primes in the same way we have the mapping for labels:

(defparameter *lisptran-vars* nil)
 
(defun prime-for-var (var)
  (or (gethash var *lisptran-vars*)
      (setf (gethash var *lisptran-vars*)
            (new-prime))))

One last piece of the compiler we need to figure out is how we are going to represent the alphabet of the program. One way we can do this is just represent the characters in our alphabet as variables. The alphabet of a program could just be all of the variables that have characters for names and the primes of the registers for those variables. By doing it this way, we can print a character by just incrementing and then immediately decrementing a variable! Here is code that can be used to obtain the alphabet from *lisptran-vars*:

(defun alphabet (vars)
  "Given a hash-table of the Lisptran variables to primes, 
   returns an alist representing the alphabet."
  (loop for var being the hash-keys in vars 
        using (hash-value prime)
        if (characterp var)
          collect (cons var prime)))

Now that we can express control flow, variables, and macros, we have everything we need to write the actual Lisptran to Fractran compiler:

(defun assemble (insts)
  "Compile the given Lisptran program into Fractran. 
   Returns two values. The first is the Fractran program 
   and the second is the alphabet of the program."
  (let* ((*cur-prime* 2)
         (*cur-inst-prime* (new-prime))
         (*next-inst-prime* (new-prime))
         (*lisptran-labels* (make-hash-table))
         (*lisptran-vars* (make-hash-table)))
    (values (assemble-helper insts)
            (alphabet *lisptran-vars*))))
 
(defun assemble-helper (exprs)
  (if (null insts)
      '()
      (let ((expr (car exprs))
            (rest (cdr exprs)))
        (cond
          ;; If it's a number, we just add it to the 
          ;; Fractran  program and compile the rest 
          ;; of the Lisptran program
          ((numberp expr)
           (cons expr (assemble-helper rest)))
 
          ;; If it's a symbol, we divide the prime for 
          ;; the next instruction by the prime for the 
          ;; label.
          ((symbolp expr)
           (cons (/ *cur-inst-prime* 
                    (prime-for-label expr))
                 (assemble-helper rest)))
 
          ;; Otherwise it's a macro call. We look up the 
          ;; macro named by the first symbol in the 
          ;; expression and call it on the rest of the 
          ;; rest of the expressions in the macro call. 
          ;; We then append all of the instructions 
          ;; returned by it to the rest of the program 
          ;; and compile that.
          (:else
            (let ((macrofn (gethash (car inst)
                                    *lisptran-macros*)))
              (assemble-helper (append (apply macrofn
                                              (cdr inst))
                                       rest))))))))

The function assemble takes a Lisptran program and returns two values. It returns the generated Fractran program and the alphabet of that program. assemble first initializes all of the global variables for the program and then goes to assemble-helper which recursively processes the Lisptran program according to the specification above. Using the function run-fractran that I mentioned above, we can write a function that will execute a given Lisptran program as follows:

(defun run-lisptran (insts)
  "Run the given Lisptran program."
  (multiple-value-call #'run-fractran (assemble insts)))

Part 3: Building Lisptran

Now that we’ve completed the core compiler, we can start adding actual features to it. From here on out, we will not touch the core compiler. All we are going to do is define a couple Lisptran macros. Eventually we will have enough macros such that programming Lisptran seems like programming a high level assembly language.

The first operations we are going should define are basic arithmetic operations. For example, addition. In order to add addition to Lisptran, we can define a macro addi, which stands for add immediate. Immediate just means that we know what number we are adding at compile time. The macro addi will take a variable and a number, and will expand into a fraction which will add the given number to the register for the variable. In this case, the denominator for the fraction will just be the prime for the current instruction (execute this instruction when that register is set) and the numerator will be the prime for the next instruction (execute the next instruction after this one) times the prime for the variable raised to the power of the number we are adding (add the immediate to the register). Here is what the definition for addi looks like:

(deftran addi (x y)
  (prog1 (list (/ (* *next* (expt (prime-for-var x) y))
                  *cur*))
    (advance)))

With are also going to want an operation that performs subtraction. It’s a bit tricky, but we can implement a macro subi (subtract immediate) in terms of addi, since adding a number is the same as adding the negative of that number:2

(deftran subi (x y) </code>((addi x ,(- y))))

Now that we’ve got some macros for performing basic arithmetic, we can start focusing on macros that allow us to express control flow. The first control flow macro we will implement is >=i (jump if greater than or equal to immediate). In order to implement >=i, we will have it expand into three fractions. The first fraction will test if the variable is greater or equal to the immediate. If the test succeeds, we will then advance to the second fraction which will restore the variable (since when a test succeeds, all of the values from the denominator are decremented from the corresponding registers), and then jump to the label passed in to >=i. If the test fails, we will fall through to the third fraction which will just continue onto the next fraction after that.

The denominator of the first fraction will be the prime for current instruction (execute the instruction if that register is set) times the prime for the register raised to the power of the constant (how we test that the register is greater than or equal to the immediate) and the numerator will be the prime for the second instruction (so we go to the second instruction if the test succeeds). The second fraction is just the prime for the label passed into >=i (so we jump to wherever the label designates) divided the prime for that instruction. Lastly, the denominator of the third fraction is the prime for the current instruction (so we fall through to it if the test in the first fraction fails), and the numerator is just the prime for the next instruction so that we continue to that if the test fails:

(deftran >=i (var val label)
  (prog1 (let ((restore (new-prime)))
           (list (/ restore
                    (expt (prime-for-var var) val)
                    *cur-inst-prime*)
                 (/ (* (prime-for-label label)
                       (expt (prime-for-var var) val))
                    restore)
                 (/ *next-inst-prime* *cur-inst-prime*)))
    (advance)))

Believe it or not, but after this point, we wont need to even think about fractions anymore. Lisptran now has enough of a foundation that all of the further macros we will need can be expressed in terms of addi, subi and >=i. The only two functions that actually need to be implemented in terms of Fractran are addi and >=i. That means no more thinking about Fractran. From here on out, all we have is Lisptran!

We can easily define unconditional goto in terms of >=i. Since all of the registers start at 0, we can implement goto as greater than or equal to zero. We use the Lisp function gensym to generate a variable without a name so that the variable doesn’t conflict with any other Lisptran variables:

(deftran goto (label) <code>((&gt;=i ,(gensym) 0 ,label)))

Then through a combination of >=i and goto, we can define <=i:

(deftran &lt;=i (var val label)
  (let ((gskip (gensym))) 
    </code>((&gt;=i ,var (+ ,val 1) ,gskip)
      (goto ,label)
      ,gskip)))

Now that we have several macros for doing control flow, we can start building some utilities for printing. As mentioned previously printing a character is the same as incrementing the variable with the character as its name and then immediately decrementing it:

(deftran print-char (char)
  <code>((addi ,char 1)
    (subi ,char 1)))

Then if we want to write a macro that prints a string, it can just expand into a series of calls to print-char, each of which prints a single character in the string:

(deftran print-string (str)
  (loop for char across str
        collect </code>(print-char ,char)))

We are also going to need a function to print a number. Writing this with the current state of Lisptran is fairly difficult since we havent implemented several utilities such as mod yet, but we can start by implementing a macro print-digit that prints the value of a variable that is between 0 and 9. We can implement it, by having it expand into a series of conditions. The first one will check if the variable is less than or equal to zero. If so it will print the character zero and jump past the rest of the conditions. Otherwise it falls through to the next condition which tests if the variable is less than or equal to one and so on. We don’t have to manually write the code for print-digit because we can use Lisp to generate the code for us:

(deftran print-digit (var)
  (loop with gend = (gensym)
        for i from 0 to 9
        for gprint = (gensym)
        for gskip = (gensym)
        append <code>((&lt;=i ,var ,i ,gprint)
                 (goto ,gskip)
                 ,gprint
                 (print-char ,(digit-char i))
                 (goto ,gend)
                 ,gskip)
        into result
        finally (return </code>(,@result ,gend))))

At this point, now that we have macros for performing basic arithmetic, basic control flow, and printing, we can start writing some recognizable programs. For example here is a program that prints the numbers from zero to nine:

(start
 (>=i x 10 end)
 (print-digit x)
 (print-char #\newline)
 (addi x 1)
 (goto start)
 end)

If you are curious I have included the Fractran program generated by this Lisptran program here. It’s hard to believe that the above Lisptran program and the Fractran program are equivalent. They look completely different!

Now that we have a bunch of low level operations, we can start building some higher level ones. You may not have thought of it, but instructions don’t need to just have flat structure. For example, now that we have goto, we can use it to define while loops (just like in Loops in Lisp):

(deftran while (test &amp;rest body)
  (let ((gstart (gensym))
        (gend (gensym)))
    <code>((goto ,gend)
      ,gstart
      ,@body
      ,gend
      (,@test ,gstart))))

In order to implement while, we are assuming that all predicates take labels as their last argument which is where they will jump to if the predicate succeeds. Now that we have while loops, we can start writing some much more powerful macros around manipulating variables. Heres two useful ones, one that sets a variable to zero, and one that copies the value in one variable to another:

(deftran zero (var)
  </code>((while (&gt;=i ,var 1)
      (subi ,var 1))))
 
(deftran move (to from)
  (let ((gtemp (gensym)))
    <code>((zero ,to)
      (while (&gt;=i ,from 1)
        (addi ,gtemp 1)
        (subi ,from 1))
      (while (&gt;=i ,gtemp 1)
        (addi ,to 1)
        (addi ,from 1)
        (subi ,gvar 1)))))

For move, we first have to decrement the number we are moving from and increment a temporary variable. Than we restore both the original variable and the variable we are moving the value to at the same time.

With all of these macros, we can finally start focusing on macros that are actually relevant to Fizzbuzz. One operation that is absolutely going to be necessary for Fizzbuzz is mod. We can implement a macro modi by repeatedly subtracting the immediate until the variable is less than the immediate.

(deftran modi (var val)
  </code>((while (&gt;=i ,var ,val)
      (subi ,var ,val))))

We only need one more real feature before we can start writing Fizzbuzz. We are going to need a way of printing numbers. In order to print an arbitrary number, we are going to need a way of doing integer division. We can implement a macro divi by repeatedly subtracting the immediate until the variable is less than the immediate and keeping track of the number of times weve subtracted the immediate.

(deftran divi (x y)
  (let ((gresult (gensym)))
    <code>((zero ,gresult)
      (while (&gt;=i ,x ,y)
        (addi ,gresult 1)
        (subi ,x ,y))
      (move ,x ,gresult))))

Now for the final macro we will need. A macro for printing numbers. Actually, we are going to cheat a little. Printing numbers winds up being pretty difficult since you have to print the digits from left to right, but you can only look at the lowest digit at a time. To make things easier, we are only to write a macro that is able to print two digit numbers. We wont need to print 100 since buzz will be printed instead.

(deftran print-number (var)
  (let ((gtemp (gensym))
        (gskip (gensym)))
    </code>((move ,gtemp ,var)
      (divi ,gtemp 10)
      (&gt;=i ,gtemp 0 ,gskip)
      (print-digit ,gtemp)
      ,gskip
      (move ,gtemp ,var)
      (modi ,gtemp 10)
      (print-digit ,gtemp)
      (print-char #\newline))))

Now our language is sufficiently high enough that Fizzbuzz is going to be practically as easy as it will get. Here is an implementation of Fizzbuzz in Fractran.

((move x 1)
 (while (<=i x 100)
   (move rem x)
   (modi rem 15)
   (<=i rem 0 fizzbuzz)
 
   (move rem x)
   (modi rem 3)
   (<=i rem 0 fizz)
 
   (move rem x)
   (modi rem 5)
   (<=i rem 0 buzz)
 
   (print-number x)
   (goto end)
 
   fizzbuzz
   (print-string "fizzbuzz")
   (goto end)
 
   fizz
   (print-string "fizz")
   (goto end)
 
   buzz
   (print-string "buzz")
   (goto end)
 
   end
   (addi x 1)))

I’ve also included the generated Fractran program here and included all of the full source code for this blog post here.

I find it absolutely amazing that we were able to build a pretty decent language by repeatedly adding more and more features on top of what we already had. To recap, we implemented a basic arithmetic operation (addi) in terms of raw Fractran and then defined a second (subi) in terms of that. From there we defined three macros for doing control flow (>=i, goto, <=i), with the second two being defined in terms of the first. Then we were then able to define macros for printing (print-char, print-string, print-digit). At this point we had all of the low level operations we needed so we could start implement while loops (while), a high level control flow construct. With while loops, we were able to define several macros for manipulating variables (zero, move). With these new utilities for manipulating variables we could define more advanced arithmetic operations (modi, divi). Then with these new operations we were able to define a way to print an arbitrary two digit number (print-number). Finally, using everything we had up to this point, we were able to write Fizzbuzz. Its just incredible that we could make a language by always making slight abstractions on top of the operations we already had.

  1. If you are wondering why *next-new-prime* is initialized to nil, it’s because we are going to initialize all of the variables that don’t persist between runs of the compiler in the compiler. *next-new-prime* is an example of such a variable.
  2. We’ll just say that it results in undefined behavior if the immediate is greater than the variable.

2 thoughts on “Building Fizzbuzz in Fractran from the Bottom Up

  1. Very interresting! I like the idea. :)

    I wonder if printing a char could be made simpler, but after a bit of reflection it seem your idea to have a prime for each possible output char is not that bad. We don’t need that many chars to print interresting text after all! I was thibking about using only 8+1 primes to encode the ascii number plus a flag indicating when to print that ascii-char and clear the 8 primes and the flag, but it modifie the interpreter a bit “too much” with fixed registers/primes to my taste.

    May I propose as a next challenge? Can you write a fractran program to compute the mandelbrot set, just like this one in brainf*ck: https://www.nayuki.io/res/optimizing-brainfuck-compiler/mandelbrot.b.txt

Leave a Reply

Your email address will not be published. Required fields are marked *