Thursday, February 20, 2025

Advent of Code 2024: Day 9

On Day 9 we are simulating defragging a disk. The input is a list of digits that alternate between a file size and a gap size. No file or gap is larger than 9 blocks.

The first part of the problem is to simply move the rightmost block that contains a file to the leftmost empty space. We repeat until there are no more empty spaces. Again, we could attempt to shoehorn this into a series approach, but it is straightforward to use an array to represent our disk and use side effects to simulate moving the blocks around.

Whenever you use an array, you’ll virtually always want to side effect the array contents, and you’ll virtually always iterate over the array. As a result, the do macro and its varaints such as dotimes will be useful interation constructs. The code will be definitely not be functional, but imperative in nature. There is just going to be state hanging out everywhere in this code.

The first thing we have to do is read the input:

;;; -*- Lisp -*-

(in-package "ADVENT2024/DAY9")

(defun read-input (input-file)
  (with-open-file (stream input-file :direction :input)
    (read-line stream nil nil)))

(defun read-layout (input-file)
  (let* ((line             (read-input input-file))
         (file-count       (/ (1+ (length line)) 2))
         (files            (make-simple-vector file-count))
         (free-block-count (1- file-count))
         (free-blocks      (make-simple-vector free-block-count)))
    (do ((input-index      0 (1+ input-index))
         (disk-loc         0 (+ disk-loc (char->decimal (schar line input-index))))
         (file-flag        t (not file-flag))
         (file-id          0 (if file-flag
                                 (1+ file-id)
                                 file-id))
         (free-block-index 0 (if file-flag
                                 free-block-index
                                 (1+ free-block-index))))
        ((>= input-index (length line)) (values files free-blocks))
      (if file-flag
          (setf (svref files file-id)
                (cons disk-loc (char->decimal (schar line input-index))))
          (setf (svref free-blocks free-block-index)
                (cons disk-loc (make-simple-vector (char->decimal (schar line input-index))
                                                   :initial-element nil)))))))

The main iteration alternates between reading a file block and a free block. The blocks are placed in a file array or a free-block array depending on the file-flag, which toggles on each pass through the loop. The disk-loc is updated with the size of the file or free block. File blocks are just the disk-loc consed to the file size, but free blocks are the disk-loc consed to an empty array that will be filled in later.

We’ll be required to compute a “checksum” of the disk, which will, for each block, the number of the block multplied by the file id of the file in the block. Since the files and the freelist are represented differently, we need a separate routine for each one and we’ll add them at the end.

(defun files-checksum (files)
  (collect-sum
    (#M(lambda (file-id)
         (let ((file-record (svref files file-id)))
           (collect-sum
             (#M(lambda (i)
                  (* file-id (+ (car file-record) i)))
              (scan-range :below (cdr file-record))))))
        (scan-range :below (length files)))))

The outer collect-sum loop iterates over each file summing the checksums. The inner collect-sum iterates over the blocks (stored in the cdr of the file record) in the file summing the product of the file-id and the offset of the block itself.

We handle freelist segments differently. They have an array into which we have moved file blocks, so we iterate over the array and multiply the file-id in the array (if there is one) by the freelist block offset and sum them:

(defun freelist-checksum (freelist)
  (collect-sum
   (#M(lambda (freelist-record)
        (let* ((segment-base (car freelist-record))
               (segment (cdr freelist-record)))
         (collect-sum
           (#M(lambda (offset-in-segment)
                (let ((file-id (or (svref segment offset-in-segment) 0)))
                  (* file-id (+ segment-base offset-in-segment))))
            (scan-range :below (length segment))))))
    (scan ’vector freelist))))

(defun filesystem-checksum (files freelist)
  (+ (files-checksum files)
     (freelist-checksum freelist)))

The two parts of the day’s puzzle involve two different strategies for “defragging” the disk. For part 1, we repeatedly move the rightmost file block to the leftmost free block. To find the rightmost occupied block, we iterate over the file list from right to left:

(defun source-block (files)
  (do ((file-id (1- (length files)) (1- file-id)))
      ((not (zerop (cdr (svref files file-id))))
       (values (+ (car (svref files file-id)) (cdr (svref files file-id)))
               (svref files file-id)
               file-id))))

To find the leftmost free block, we search the free blocks until we find one that is not fully occupied.

(defun target-block (freelist)
  (let* ((free-segment (find-if (lambda (segment)
                                  (position nil (cdr segment)))
                                freelist))
         (offset (position nil (cdr free-segment))))
    (values (+ (car free-segment) offset)
            (cdr free-segment)
            offset)))

These aren’t the most efficient because they forget the information from the previous search, but presumably a defragging process would be dominated by the disk reads and writes.

Once we have the source and target blocks, we move the source block to the target block:

(defun move-block! (files freelist)
  (multiple-value-bind (source-block source-record file-id) (source-block files)
    (multiple-value-bind (target-block target-segment target-offset) (target-block freelist)
      (when (< target-block source-block)
        (decf (cdr source-record))
        (setf (svref target-segment target-offset) file-id)
        t))))

We only move blocks to lower addresses and return NIL if we cannot move a block.

To defrag with this strategy, we just repeatedly call move-block! until it returns NIL:

(defun defrag1! (files freelist)
  (when (move-block! files freelist)
    (defrag1! files freelist)))

(defun puzzle (input-pathname defrag)
  (multiple-value-bind (files freelist) (read-layout input-pathname)
    (funcall defrag files freelist)
    (filesystem-checksum files freelist)))

(defun part-1 ()
  (puzzle (input-pathname) #’defrag1!))

Part 2 uses a different strategy to defrag the disk. Instead of blocks, we move entire files, and we move them to the leftmost block that they’ll fit. To find that leftmost block, we scan the freelist:

(defun defrag2-target (file freelist)
  (collect-first
   (choose-if
    (lambda (free-record)
      (and (< (car free-record) (car file))
           (<= (cdr file) (count nil (cdr free-record)))))
    (scan ’vector freelist))))

We iterate over the files from right to left:

(defun defrag2! (files freelist)
  (do ((file-id (1- (length files)) (- file-id 1)))
      ((zerop file-id))
    (let* ((file (svef files file-id))
           (target (defrag2-target file freelist)))
      (when target
        (let* ((start (position nil (cdr target)))
               (end (+ start (cdr file))))
          (fill (cdr target) file-id :start start :end end)
          (setf (cdr file) 0))))))

(defun part-2 ()
  (puzzle (input-pathname) #’defrag2!))

Wednesday, February 19, 2025

FOLD and NAMED-LET implementations

An anonymous reader requested an implementation of FOLD-LEFT, FOLD-RIGHT and NAMED-LET. Here they are:

https://github.com/jrm-code-project/fold
https://github.com/jrm-code-project/named-let

MIT license, developed and tested under SBCL, but should be portable. Implementation does not depend on tail recursion.

Advent of Code 2024: Day 8

Day 8 is another grid puzzle. We are given a map of antennas. Two antennas operate on the same frequency have the same ASCII character on the map. A “node” is a location on the map that is in line with two antennas of the same frequency and is twice as far from one antenna as the other. We are to count the nodes.

We can create an alist from antenna frequency to antenna locations by inverting the map:

(defun read-grid (pathname)
  (read-file-into-grid
    (char-interner #’identity (find-package "ADVENT2024/DAY8"))
    pathname))

(defun grid->antenna-list (grid)
  (hash-table-alist (invert-grid grid ’|.|)))

This solution makes use of first class functions. antinode-answer takes a function that produces an answer on one side of an antenna pair and applies it to the pair and swapped pair to produce answers on both sides.

(defun antinode-answer (antinode-half-answer)
  (lambda (grid left right)
    (append (funcall antinode-half-answer grid left right)
            (funcall antinode-half-answer grid right left))))

antinode-list takes a function that produces an answer for pair a single pair of antennas and maps it over all pairs of antennas on a frequency.

(defun antinode-list (antinode-answer)
  (lambda (grid node-list)
    (map-pairs (lambda (left right)
                 (funcall antinode-answer grid left right))
               node-list)))

All the antinodes can be obtained by invoking an antinode-list-generator over a set of node lists and appending the results.

(defun antinodes (antinode-list-generator)
  (lambda (grid node-list)
    (fold-left #’append nil
               (funcall antinode-list-generator grid node-list))))

So to solve the puzzle, we call an antinode generator on all the antennas.

(defun puzzle (grid antinode-generator)
  (length
   (remove-duplicates
    (fold-left (lambda (antinodes entry)
                 (append antinodes (funcall antinode-generator grid (cdr entry))))
               nil
               (grid->antenna-list grid))
    :test #’equal)))

In part 1, there is one node to the left and right of each pair, twice the distance from one antenna to the other.

(defun antinode (grid left right)
  (let* ((delta (2v- right left))
         (antinode (2v- left delta)))
    (when (on-grid? grid antinode)
      (list antinode))))

(defun part-1 ()
  (puzzle (read-grid (input-pathname))
          (antinodes (antinode-list (antinode-answer #’antinode)))))

For part two, the antinodes are at “resonant” points, i.e., spaced out equidistantly beyond the antenna pairs.

(defun resonant-antinodes (grid left right)
  (let* ((delta (2v- right left)))
    (do ((antinode left (2v- antinode delta))
         (answer ’() (cons antinode answer)))
        ((not (on-grid? grid antinode)) answer))))

(defun part-2 ()
  (puzzle (read-grid (input-pathname))
          (antinodes (antinode-list (antinode-answer #’resonant-antinodes)))))

Lisp was the first computer language to have first-class functions and lambda expressions.

Tuesday, February 18, 2025

Advent of Code 2024: Day 7

You don’t have to use named-lets for tail recursive loops. You can use them for any recursive function. Here is an example of a named let that computes the factorial of 5:

(let fact ((n 5))
  (if (= n 0)
      1
      (* n (fact (- n 1)))))

Day 7 is an unremarkable puzzle. On each line of input we are given a target number and some terms. We work on the terms from left to right and we can add the next term or multiply by it. We are to sum the target numbers which can be identified as a result of some combination of adding and multiplying.

;;; -*- Lisp -*-

(in-package "ADVENT2024/DAY7")

(defun can-satisfy? (target ops terms)
  (let recur ((accum (first terms))
              (terms (rest terms)))
       (cond ((and (> accum target)
                   (not (find-if #’zerop terms)))
              nil)
             ((consp terms)
              (find-if
               (lambda (op)
                 (recur (funcall op accum (first terms)) (rest terms)))
               ops))
             ((null terms) (= target accum))
             (t (error "Dotted list.")))))

(defun parse-integer-list (str)
  (map ’list #’parse-integer (str:split #\Space str :omit-nulls t)))

(defun parse-line (str)
  (let ((key+value (str:split #\: str)))
    (cons (parse-integer (first key+value))
          (parse-integer-list (second key+value)))))

(defun puzzle (ops)
  (collect-sum
    (let* ((equations
             (#Mparse-line
              (scan-file (input-pathname) #’read-line)))
           (satisfied (#M(lambda (equation)
                           (can-satisfy? (car equation) ops (cdr equation)))
                         equations)))
      (#Mcar (choose satisfied equations)))))

(defun part-1 ()
  (puzzle (list #’+ #’*)))

Part two allows us to concatenate the digits in addition to muliplying or adding.

(defun concatenate-digits (left right)
  (+ (* left (expt 10 (1+ (integer-log right 10))))
     right))

(defun part-2 ()
  (puzzle (list #’+ #’* #’concatenate-digits)))

Monday, February 17, 2025

Advent of Code 2024: Day 6

A named-lambda is a lambda expression that has a name bound to it only within the scope of the lambda expression. You can use the name to refer to the lambda expression from within the body of the lambda expression. This allows you to recursively call the lambda expression. Named-lambdas are easily created with a macro that expands into a labels form.

Named-lambdas are an alternative to using the Y operator to create recursive lambda expressions. Named-lambdas are a special form, so if you are uncomfortable with adding new special forms to the language, you’ll probably prefer to use the Y operator.

Recall that let expressions are just syntactic sugar for lambda expressions. If you expand a let expression using a named-lambda, you get a named-let expression. The name is bound to the lambda that binds the let variables. Invoking the name will re-invoke the let expression with different values for the bound variables.

Named lets take a moment to get used to, but once you get the hang of them, they are incredibly handy. They are especially useful when you use them for tail recursive loops. Here is an example where we use a named let to partition a list with a predicate:

(let next ((tail list)
           (yes ’())
           (no  ’()))
  (cond ((consp tail) 
         (if (predicate (car tail))
             (next (cdr tail) (cons (car tail) yes) no)
             (next (cdr tail) yes (cons (car tail) no))))
        ((null? tail) (values yes no))
        (t (error "Improper list."))))

When we invoke the name next, we re-invoke the let expression with the new values for the bound variables. In this example, the calls to next are in tail position, so the compiler turns them into jumps, making this a tail recursive loop.

The named-let syntax, with the name being the symbol before the bindings, is borrowed from MIT-Scheme. This syntax is easily implemented with a macro that expands into a labels form if the name is present, but expands into a cl:let if it is absent. You shadowing-import the let symbol into your package so that the macro will override the standard binding of let.



For day 6, we have a guard patrolling a warehouse. The guard moves in straight lines unless he encounters an obstacle, where he will turn clockwise 90 degrees. If he moves off the grid, he goes home for the evening.

First, we’ll read the grid and find the initial position of the guard:

(defun read-input (pathname)
  (read-file-into-grid 
    (char-interner #’char-upcase (find-package "ADVENT2024/DAY6"))
    pathname))

(defun get-initial-position (grid)
  (let ((coord (collect-first
                (choose-if
                 (lambda (coord) (member (grid-ref grid coord) ’(^ < > v)))
                 (scan-grid-coords grid)))))
    (ocoord coord
           (ecase (grid-ref grid coord)
             (^ +north+)
             (> +east+)
             (v +south+)
             (< +west+)))))

In the second part of the problem, we’ll be allowed to place a single additional obstacle in the grid. patrol-step attempts to move the guard one step forward, and turns him clockwise if he cannot move forward. obstacle-coord is the additional obstacle or nil:

(defun patrol-step (grid obstacle-coord oriented-position)
  (let ((next-ocoord (ocoord-advance oriented-position)))
    (cond ((not (on-grid? grid (ocoord-coord next-ocoord))) nil)
          ((or (eq (grid-ref grid (ocoord-coord next-ocoord)) ’|#|)
               (equal (ocoord-coord next-ocoord) obstacle-coord))
           (ocoord-cw oriented-position))
          (t next-ocoord))))

patrol places the guard at his initial position and repeatedly calls patrol-step until the guard either walks off the grid or returns to an ocoord he has visited before (with the same orientation). We keep the history of visited ocoords in two ways: as a list and a hash table. The list gives us the history in order, while the hash table allows us to quickly check if we have visited an ocoord before (otherwise we’d have an O(n^2) algorithm). If the guard walks off the grid, we return the history list. If the guard returns to a previously visited ocoord, we return the symbol :loop. Note the use of a named-let to loop the patrol steps.

(defun patrol (grid obstacle-coord start-opos)
  (let ((history-hash (make-hash-table :test ’equal)))
    (setf (gethash start-opos history-hash) t)
    (let iter ((opos start-opos)
               (history (list start-opos)))
      (let ((next (patrol-step grid obstacle-coord opos)))
        (cond ((null next) history)
              ((gethash next history-hash nil) :loop)
              (t (setf (gethash next history-hash) t)
                 (iter next (cons next history))))))))

For part 1, we simply call patrol with the initial position and nil as the obstacle:

(defun unique-cells (history)
  (length (remove-duplicates (map ’list #’ocoord-coord history) :test #’equal)))

(defun part-1 ()
  (let* ((grid (read-input (input-pathname)))
         (initial-position (get-initial-position grid)))
    (unique-cells (patrol grid nil initial-position))))

For part 2, we iterate over the cells in the paths and see what happens if we place an obstacle there. We accumulate the locations that result in a loop:

(defun part-2 ()
  (let* ((grid (read-input (input-pathname)))
         (initial-position (get-initial-position grid))
         (unmodified-path (patrol grid nil initial-position))
         (answer nil))
    (dolist (obstacle (remove-duplicates (map ’list #’ocoord-coord unmodified-path) :test #’equal)
                      (length (remove-duplicates answer :test #’equal)))
      (unless (and obstacle
                   (equal obstacle (ocoord-coord initial-position)))
        (when (eq (patrol grid obstacle initial-position) :loop)
          (pushnew obstacle answer :test #’equal))))))

Sunday, February 16, 2025

Advent of Code 2024: Day 5

For day 5, the input comes in two parts: There are rules of the form n|m, where n and m are numbers, and there are “updates” which are lists of numbers separated by commas. The rules are used to determine which updates are valid. An update is valid if it passes all applicable rules. A rule is applicable if the two numbers in the rule appear in the update. An update passes an applicable rule if the two numbers in the rule appear in the update in the same order as they appear in the rule.

To read the input, we read the lines and collect them into two lists. The rule list is all the lines that contain a pipe character, and the updates list is all the lines that contain a comma:

(defun read-input (input-file)
  (let ((lines (scan-file input-file #'read-line)))
    (let ((is-rule (#M(lambda (line) (find #\| line)) lines))
          (is-update (#M(lambda (line) (find #\, line)) lines)))
      (values (collect ’list (#M(lambda (rule)
                                  (map ’list #’parse-integer (str:split #\| rule)))
                                (choose is-rule lines)))
              (collect ’list (#M(lambda (update)
                                  (map ’list #’parse-integer (str:split #\, update)))
                                (choose is-update lines)))))))

To test a rule, we find the location of the two numbers in the update and check that they are in the same order as they appear in the rule. If either number is not found, the rule is not applicable and trivially passes.

(defun test-rule (rule update)
  (let ((left-position (position (first rule) update))
        (right-position (position (second rule) update)))
    (or (null left-position)
        (null right-position)
        (< left-position right-position))))

(defun test-rules (rules update)
  (collect-and
   (#Mtest-rule
    (scan ’list rules)
    (series update))))

Part 1 is to sum the middle numbers of all the updates that pass all the rules:

(defun middle-number (list)
  (elt list (/ (1- (length list)) 2)))

(defun part-1 ()
  (multiple-value-bind (rules updates) (read-input (input-pathname))
    (collect-sum
     (#Mmiddle-number
      (choose-if
       (lambda (update) (test-rules rules update))
       (scan ’list updates))))))

For part 2, we select the updates that fail the rules. We repair the update by sorting it using the rules as a sort predicate, then we sum the middle numbers of the repaired updates:

(defun sort-using-rules (rules list)
  (sort list (lambda (left right)
               (find (list left right) rules :test #’equal))))

(defun part-2 ()
  (multiple-value-bind (rules updates) (read-input (input-pathname))
    (collect-sum
     (#Mmiddle-number
      (#M(lambda (update) (sort-using-rules rules update))
       (choose-if
        (lambda (update) (not (test-rules rules update)))
        (scan ’list updates)))))))

Friday, February 14, 2025

Advent of Code 2024: Day 4

Day 4 part 1 is your standard word search. First we read the grid of letters:

(defun read-input (input-pathname)
  (read-file-into-grid
    (char-interner #'char-upcase (find-package "ADVENT2024/DAY4"))
    input-pathname))

A “trace” is a row, column, or diagonal of letters. To search a trace for the word, we examine each suffix of the trace to see if starts with the word. We also check the reverse of the word:

(defun search-trace (trace target)
  (let ((rev (reverse target)))
    (collect-sum
     (#M(lambda (suffix)
          (if (or (starts-with-subseq target suffix)
                  (starts-with-subseq rev suffix))
              1
              0))
        (scan-suffixes trace)))))

Then we search all the traces:

(defun search-trace-list (trace-list target)
  (collect-sum
   (#M(lambda (trace)
        (search-trace trace target))
    (scan 'list trace-list))))

(defun search-grid (grid target)
  (collect-sum
   (#M(lambda (get-trace-list)
        (search-trace-list (funcall get-trace-list grid) target))
      (scan ’list
         (list (lambda (grid) (collect ’list (scan-rows grid)))
               (lambda (grid) (collect ’list (scan-columns grid)))
               (lambda (grid) (collect ’list (scan-falling-diagonals grid)))
               (lambda (grid) (collect ’list (scan-rising-diagonals grid))))))))

(defun part-1 ()
  (search-grid (read-input (input-pathname)) #(X M A S)))

Note that since scan-rows etc. and collect are macros, so we cannot pass them as first class functions. Instead we pass lambdas that call them so that the full macro expression is visible to the compiler.

For part 2, we are searching for Xs of “MAS” in the grid. We search for As, then check for M and S in the diagonals.

m-s1? is a helper function that checks if a pair of coords contains an M and an S.

(defun m-s1? (grid coord1 coord2)
  (and (on-grid? grid coord1)
       (on-grid? grid coord2)
       (eql (grid-ref grid coord1) 'M)
       (eql (grid-ref grid coord2) 'S)))

m-s? checks if a pair of coords contains an M and an S in any order.

(defun m-s? (grid coord1 coord2)
  (or (m-s1? grid coord1 coord2)
      (m-s1? grid coord2 coord1)))

x-mas? checks whether an A is surrounded by an M and an S.

(defun x-mas? (grid coord)
  (and (on-grid? grid coord)
       (eql (grid-ref grid coord) 'A)
       (and (m-s? grid (coord-northwest coord) (coord-southeast coord))
            (m-s? grid (coord-northeast coord) (coord-southwest coord)))))

Then we just count the occurrances:

(defun search-x-mas (grid)
  (collect-sum
   (#M(lambda (coord)
        (if (x-mas? grid coord)
            1
            0))
      (scan-grid-coords grid))))

(defun part-2 ()
  (search-x-mas (read-input (input-pathname))))

Wednesday, February 12, 2025

Advent of Code 2024: Day 3

For Day 3, we are given a “corrupted” block of memory as a string. We are to find the “uncorrupted instructions” in the block and emulate them.

For this problem, we don’t attempt to force things into the series paradigm. The cl-ppcre library provides a bunch of functions for working with regular expressions, and the do-register-groups macro is ideal for this problem. It iterates over all the matches of a regular expression, binding submatches to some variables, with some optional processing of the submatch. (If the cl-ppcre library offered a function that returned a series of matches, we could use that, but it offers a do macro.)

First, we read the input:

(defun read-input (input-pathname)
  (read-file-into-string input-pathname))

Next, we define a regular expression to match the instructions:

(defparameter *mul-instruction* "(mul\\((\\d{1,3}),(\\d{1,3})\\))")

Now we just iterate over all the matches:

(defun part-1 ()
  (let ((answer 0))
    (cl-ppcre:do-register-groups (whole (#’parse-integer left) (#’parse-integer right))
        (*mul-instruction* (read-input (input-pathname)))
      (declare (ignore whole))
      (incf answer (* left right)))
    answer))

do-register-groups is an example of a macro where the parenthesized subexpressions do not indicate function calls. The first parenthesized subgroup is a variable list, and within the variable list, a parenthesized subgroup indicates a transformer to be applied before binding the variable. So in this case, we are binding the variables whole, left, and right, and we run the matching subgroup through parse-integer before binding the left and right variables.

The second parenthesized subgroup is a list of the regular expression to match and the string to match within. After these irregular parenthesized subgroups, the remaining is a body of code that is executed for each match.

In the body of the code, we ignore the whole variable (which is the whole match) and increment the answer by the product of the left and right variables. As is usual for a do macro, we transport the data out of the loop by side effecting a lexically scoped variable.

For part 2, we have additional instructions to emulate. Our loop will now have some state to it, and we will side effect the state as we iterate over the matches. We can just extend the regular expression and add a cond to the body of the do-register-groups to handle the new instructions. As we iterate over the matches, we side effect the emulation state:

(defparameter *do-mul-instruction* "(do\\(\\))|(don’t\\(\\))|(mul\\((\\d{1,3}),(\\d{1,3})\\))")

(defun part-2 ()
  (let ((answer 0)
        (on t))
    (cl-ppcre:do-register-groups (turn-on turn-off whole (#’parse-integer left) (#’parse-integer right))
        (*do-mul-instruction* (read-input (input-pathname)))
      (declare (ignore whole))
      (cond (turn-on (setq on t))
            (turn-off (setq on nil))
            (on (incf answer (* left right)))
            (t nil)))
    answer))

Strictly speaking, we don’t need to use side effects. We could rework this to be purely functional, but this seems unnatural. Yes, there is a bit of cognitive overhead in remembering that there is a state variable that determines whether or not we are executing an instruction, but the code is quite understandable.

“Do” macros usually need some side effects, but we can localize the side effects by using a let to lexically bind the state variables and then side effecting them from within the loop. This is an effective compromise between the functional and imperative programming paradigms.

Advent of Code 2024: Day 2

For Day 2 in the Advent of Code, we are given a file where each line in the file contains a list of integers separated by spaces. We will be performing some manipulations on these lists.

First, we need to read the file. We make a function to read a line as a string, then read the integers from the string and collect the result into a list.

(defun read-levels (stream eof-error-p eof-value)
  (let ((line (read-line stream eof-error-p eof-value)))
    (if (eq line eof-value)
        eof-value
        (with-input-from-string (stream line)
          (collect ’list (scan-stream stream))))))

We use this function to read the entire file into a list of lists of integers.

(defun read-input (input-pathname)
  (collect ’list (scan-file input-pathname #’read-levels)))

We are concerned with the deltas between adjacent elements in a series of integers. We make a function to calculate the deltas. This will be an optimizable-series-function because it returns a series of deltas. We declare the argument to be an “off-line” input series as well. This code will be transformed into the equivalent loop code where we consume the deltas.

chunk is a series function that takes a series and produces n series of chunks that are offset by a specified amount. We produce chunks of size 2, offset by 1. This returns two series, the left number of each pair of numbers and the right number of each pair of numbers. By mapping #’- over these series, we get the series of deltas between adjacent numbers.

(defun deltas (series)
  (declare (optimizable-series-function)
           (off-line-port series))
  (multiple-value-bind (left right) (chunk 2 1 series)
    (#M- right left)))

As per the puzzle, a series of deltas is considered “safe” if it is strictly ascending or descending, and each step by which it ascends or descends is between 1 and 3 inclusive. We get the series of deltas, map #’plusp to get a series of booleans indicating whether each delta is positive, and collect-and on the series of booleans. Likewise with #’minusp for descending. Finally, we create a series of booleans indicating whether the absolute value of the delta is <= 3 and collect-and this as well. Whether the deltas are considered “safe” is just a boolean operation on these three boolean values:

(defun safe-levels? (list)
  (let ((deltas (deltas (scan list))))
    (let ((ascending (collect-and (#Mplusp deltas)))
          (descending (collect-and (#Mminusp deltas)))
          (small (collect-and (#M<= (Mmabs deltas) (series 3)))))
      (and small
           (or ascending descending)))))

The first part of the puzzle asks us to count the number of lines considered “safe”:

(defun part-1 ()
  (count-if #’safe-levels? (read-input (input-pathname))))

The second part of the puzzle relaxes the safety restriction by saying that you are allowed to ‘dampen’ the list by removing a single outlier before checking for safety.

(defun safe-dampened-levels? (levels)
  (find-if #’safe-levels? (remove-one-element levels)))

(defun part-2 ()
  (count-if #’safe-dampened-levels? (read-input (input-pathname))))

Advent of Code 2024: Day 1

Half the problem of solving an Advent of Code puzzle is dealing with the puzzle input. It is generally in some ad hoc format that requires a bespoke parser. There are a few approches you can take.

  • Read the input as a string and directly call string manipulation functions to extract the data.
  • Read the input as a string and use regular expressions to extract the data.
  • Use the lisp reader to read the input as a lisp data structure. This requires that the input looks like lisp objects.
  • Tweak the Lisp reader to read the data in a custom format. This works if the input looks a lot like lisp objects.

For Day 1, the input is two columns of numbers. If we just scan the file with the lisp reader, we'll get a single list of numbers. We can convert this into two lists with the series chunk function:

(defun read-input (input-pathname)
  (multiple-value-bind (left-column right-column)
      (chunk 2 2 (scan-file input-pathname))
    (values (collect ’list left-column)
            (collect ’list right-column))))

For part 1 of the puzzle, we sort both columns and then walk through them in parallel finding the absolute difference between the columns and summing that.

(defun part-1 ()
  (multiple-value-bind (left-column right-column)
      (read-input (input-pathname))
    (collect-sum
     (#Mabs
      (#M-
       (scan (sort left-column #’<))
       (scan (sort right-column #’<)))))))

For part 2, we look at each number in the left column and multiply it by how many times it appears in the right column. We sum these quantities.

(defun part-2 ()
  (multiple-value-bind (left-column right-column)
      (read-input (input-pathname))
    (collect-sum
     (#M(lambda (item) (* item (count item right-column)))
        (scan left-column)))))

These examples show how we can use series and built-in sequence functions to eliminate loops.

Tuesday, February 11, 2025

Advent of Code 2024: Day 0

I wanted to write some blog posts, but I was short of material. For the fun of it, I’ve decided to write a series of posts about solving the 2024 Advent of Code problems in Common Lisp. I see that other people were doing this in real time, but it is too late for that. Besides, I didn’t want the stress of trying to solve the problems as part of a competition. I wanted to take my time and focus on code quality rather than on how fast I can write it.

I noticed that some programmers were less experienced in Common Lisp. They tended to code up solutions that used low-level Common Lisp operations instead of using one of Common Lisp’s powerful sequence operations. For example, they might use a loop to iterate over a list and incf a counter instead of just using a call to count. I want to show how to effectively use the rich set of Common Lisp library functions to write concise, readable, and efficient code.

I’m trying to decide what I think of the series package that provides a more functional approach to iteration without sacrificing performance. For a lot of iterations, it is easy to write series code, but it for other iterations it isn’t so obvious. I wanted a little practice in using series and seeing its limitations.

Conventions

One of the features of Common Lisp is that you can tailor the language to fit the problem space. The first step in solving the problem suite is to configure the language. Since I wanted to explore using the series package, I set up my Lisp so that series was available in all the packages. I also installed the alexandria library, which is a collection of utilities that flesh out the Common Lisp standard library with some obvious “missing” functions.

The series package includes an optional #M reader macro that gives you a shorthand for writing mapping expressions. I added the “named” let syntax which attaches a name to the binding lambda of a let expression allowing you to invoke the reinvoke the let as a recursive function. The default delarations were set to ensure that the compiler could would generate tail recursive code. Tail recursion coupled with named-let is a powerful iteration facility.

I set up the directory structure to have a subdirectory for each day. Each problem in the entire Advent of Code could fit in its own solution.lisp file, so each subdirectory had files input.txt and solution.lisp, and usually sample-input.txt and maybe one or more sample-input-n.txt

The parent directory had an advent2024.asd file, a package.lisp file that defined all the packages, an initialize.lisp file that customized Common Lisp and installed some bootstrap values in each package, and a misc.lisp file that contained some common definitions that were exported to all the packages.

I set up my Lisp to have a separate package for each day. The package definition file contained 25 package definitions, each one virtually identical, e.g.:

(defpackage "ADVENT2024/DAY16"
  (:shadow "VALIDATE")
  (:import-from "ALEXANDRIA"
                "FLATTEN"
                "HASH-TABLE-ALIST"
                "HASH-TABLE-KEYS"
                "HASH-TABLE-VALUES"
                "LENGTH="
                "MAPPEND"
                "MAP-PERMUTATIONS"
                "MAP-PRODUCT"
                "READ-FILE-INTO-STRING"
                "STARTS-WITH-SUBSTRING"
                )
  (:shadowing-import-from "NAMED-LET" "LET")
  (:shadowing-import-from "SERIES"
                          "DEFUN"
                          "FUNCALL"
                          "LET*"
                          "MULTIPLE-VALUE-BIND"
                          )
  (:export "PART-1" "PART-2" "+SOLUTION-1+" "+SOLUTION-2+" "VALIDATE")
  (:use "ADVENT2024" "COMMON-LISP" "FOLD" "FUNCTION" "NAMED-LET" "SERIES"))

This basically set up Lisp to have series available, and imported a few symbols from alexandria.

Each day’s puzzle has two parts, so each package exports the symbols PART-1 and PART-2 to be defined as zero argument functions that compute and return the solution to the respective parts. The symbols +SOLUTION-1+ and +SOLUTION-2+ are defined as defparameter values. The initialization function installs a validate function checks that (part-1) returns +SOLUTION-1+ and (part-2) returns +SOLUTION-2+ in each package.

misc.lisp

The misc.lisp file contains code that is common to more than one puzzle.

The grid abstraction

The problem space of many of the puzzles is two dimensional, and it is natural to use a two-dimensional lisp array for the representation. I enhance this with a lightweight abstraction called a grid.

A grid is adressed by a coord, which is an ordered pair of column and row. These are simply the car and cdr of a cons cell. The functions that construct and select from a coord are all given compiler-macro definitions. In the 99% of the cases where you simply call the constructor or selector, the compiler macro will expand the code. In the 1% case, where you pass the constructor or selector as a first-class function, the function definition is passed.

(deftype grid-index ()
  ‘(integer ,(- array-dimension-limit) (,array-dimension-limit)))

(deftype coord ()
  ’(cons (grid-index) (grid-index)))

(eval-when (:compile-toplevel :load-toplevel :execute)
(defun coord (column row)
  (check-type column grid-index)
  (check-type row grid-index)
  (cons column row))
)

(define-compiler-macro coord (column row)
  ‘(cons ,column ,row))

(defun column (coord)
  (check-type coord coord)
  (car coord))

(define-compiler-macro column (coord)
  ‘(car ,coord ))

(defun row (coord)
  (check-type coord coord)
  (cdr coord))

(define-compiler-macro row (coord)
  ‘(cdr ,coord))

(defun scan-coords (row-count col-count)
  (declare (optimizable-series-function))
  (multiple-value-bind (rows cols)
      (map-fn ’(values grid-index grid-index)
              #’floor
              (scan-range :below (* row-count col-count))
              (series col-count))
    (declare (type (series grid-index) rows cols))
    (map-fn ’coord #’coord cols rows)))

A grid is just a two-dimensional array of atoms:

(deftype grid () ‘(array atom 2))

(defun make-grid (height width &rest keys)
  (apply #’make-array (list height width) keys))

(defun row-list->grid (row-list)
  (make-grid (length row-list) (length (first row-list)) :initial-contents row-list))

(defun grid-height (grid)
  (check-type grid grid)
  (array-dimension grid 0))

(define-compiler-macro grid-height (grid)
  ‘(array-dimension ,grid 0))

(defun grid-width (grid)
  (check-type grid grid)
  (array-dimension grid 1))

(define-compiler-macro grid-width (grid)
  ‘(array-dimension ,grid 1))

A coord is on a grid if it is within the bounds of the grid:

(defun on-grid? (grid coord)
  (and (>= (column coord) 0)
       (< (column coord) (grid-width grid))
       (>= (row coord) 0)
       (< (row coord) (grid-height grid))))

You may want to check if the coord is on the grid before calling grid-ref.

(defun grid-ref (grid coord)
  (check-type grid grid)
  (check-type coord coord)
  (aref grid (row coord) (column coord)))

(define-compiler-macro grid-ref (grid coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (aref ,grid (row ,coord-var) (column ,coord-var)))))

(defsetf grid-ref (grid coord) (value)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (setf (aref ,grid (row ,coord-var) (column ,coord-var)) ,value))))

(defun scan-grid-coords (grid)
  (declare (optimizable-series-function))
  (scan-coords (grid-height grid) (grid-width grid)))

(defun scan-grid (grid)
  (declare (optimizable-series-function 2))
  (#2m(lambda (grid coord)
        (values coord (grid-ref grid coord)))
      (series grid)
      (scan-coords (grid-height grid) (grid-width grid))))

You can invert a grid. This will give you a hash table that maps the atoms in the grid to a list of their coords.

(defun invert-grid (grid &optional initial-value)
  (if initial-value
      (multiple-value-bind (coords vals) (scan-grid grid)
        (collect-hash-push-except vals coords (list initial-value)))
      (multiple-value-bind (coords vals) (scan-grid grid)
        (collect-hash-push vals coords))))

You can extract a row, column, or diagonal from a grid:

(defun grid-row (grid row-number)
  (check-type grid grid)
  (make-array (list (grid-width grid))
              :displaced-to grid
              :displaced-index-offset (array-row-major-index grid row-number 0)))

(defun grid-column (grid columm-number)
  (check-type grid grid)
  (let ((answer (make-array (grid-height grid))))
    (dotimes (row (grid-height grid) answer)
      (setf (svref answer row)
            (grid-ref grid (coord columm-number row))))))

(defun grid-falling-diagonal (grid diagonal-number)
  (check-type grid grid)
  (let ((start-column (if (minusp diagonal-number)
                          0
                          diagonal-number))
        (start-row (if (minusp diagonal-number)
                       (- diagonal-number)
                       0)))
    (let ((limit (min (- (grid-width grid) start-column)
                      (- (grid-height grid) start-row))))
      (let ((answer (make-array (list limit))))
        (do ((row    start-row    (+ row 1))
             (column start-column (+ column 1))
             (index 0 (+ index 1)))
            ((>= index limit) answer)
          (setf (svref answer index)
                (grid-ref grid (coord column row))))))))

(defun grid-rising-diagonal (grid diagonal-number)
  (check-type grid grid)
  (let ((start-column (if (minusp diagonal-number)
                          (- diagonal-number)
                          0))
        (start-row (if (minusp diagonal-number)
                       (1- (grid-height grid))
                       (- (grid-height grid) diagonal-number 1))))
    (let ((limit (min (- (grid-width grid) start-column)
                      (1+ start-row))))
      (let ((answer (make-array (list limit))))
        (do ((row    start-row    (- row 1))
             (column start-column (+ column 1))
             (index 0 (+ index 1)))
            ((>= index limit) answer)
          (setf (svref answer index)
                (grid-ref grid (coord column row))))))))

Given a grid, you can get the series of rows, columns, or diagonals:

(defun scan-rows (grid)
  (declare (optimizable-series-function))
  (map-fn ’vector #’grid-row (series grid) (scan-range :below (grid-height grid))))

(defun scan-columns (grid)
  (declare (optimizable-series-function))
  (map-fn ’vector #’grid-column (series grid) (scan-range :below (grid-width grid))))

(defun scan-falling-diagonals (grid)
  (declare (optimizable-series-function))
  (map-fn ’vector
          #’grid-falling-diagonal
          (series grid)
          (scan-range :from (1+ (- (grid-height grid))) :below (grid-width grid))))

(defun scan-rising-diagonals (grid)
  (declare (optimizable-series-function))
  (map-fn ’vector
          #’grid-rising-diagonal
          (series grid)
          (scan-range :from (- 1 (grid-width grid)) :below (grid-height grid))))

An orientation is a unit coord.

(deftype unit ()
  ‘(integer -1 1))

(deftype orientation ()
  ’(cons (unit) (unit)))

(defun unit-vector (column row)
  (check-type column unit)
  (check-type row unit)
  (cons column row))

(defparameter +north+ (unit-vector 0 -1))
(defparameter +northeast+ (unit-vector 1 -1))
(defparameter +east+  (unit-vector 1 0))
(defparameter +southeast+ (unit-vector 1 1))
(defparameter +south+ (unit-vector 0 1))
(defparameter +southwest+ (unit-vector -1 1))
(defparameter +west+  (unit-vector -1 0))
(defparameter +northwest+ (unit-vector -1 -1))

You can do 2d-vector arithmetic on a coord

(defun 2v+ (left right)
  (coord (+ (column left) (column right))
         (+ (row left) (row right))))

(defun 2v- (left right)
  (coord (- (column left) (column right))
         (- (row left) (row right))))

Given a coord, you can get the coord of the adjacent cell in a given orientation. Note that the new coord might not be on the grid if you’re at the edge.

(defun coord-north (coord)
  (check-type coord coord)
  (2v+ coord +north+))

(define-compiler-macro coord-north (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (column ,coord-var) (1- (row ,coord-var))))))

(defun coord-northeast (coord)
  (check-type coord coord)
  (2v+ coord +northeast+))

(define-compiler-macro coord-northeast (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1+ (column ,coord-var)) (1- (row ,coord-var))))))

(defun coord-east (coord)
  (check-type coord coord)
  (2v+ coord +east+))

(define-compiler-macro coord-east (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1+ (column ,coord-var)) (row ,coord-var)))))

(defun coord-southeast (coord)
  (check-type coord coord)
  (2v+ coord +southeast+))

(define-compiler-macro coord-southeast (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1+ (column ,coord-var)) (1+ (row ,coord-var))))))

(defun coord-south (coord)
  (check-type coord coord)
  (2v+ coord +south+))

(define-compiler-macro coord-south (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (column ,coord-var) (1+ (row ,coord-var))))))

(defun coord-southwest (coord)
  (check-type coord coord)
  (2v+ coord +southwest+))

(define-compiler-macro coord-southwest (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1- (column ,coord-var)) (1+ (row ,coord-var))))))

(defun coord-west (coord)
  (check-type coord coord)
  (2v+ coord +west+))

(define-compiler-macro coord-west (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1- (column ,coord-var)) (row ,coord-var)))))

(defun coord-northwest (coord)
  (check-type coord coord)
  (2v+ coord +northwest+))

(define-compiler-macro coord-northwest (coord)
  (let ((coord-var (gensym "COORD-")))
    ‘(let ((,coord-var ,coord))
       (coord (1- (column ,coord-var)) (1- (row ,coord-var))))))

An ocoord is a coord that has a direction associated with it. It is a coord plus an orientation.

(deftype ocoord ()
  ’(cons coord orientation))

(defun ocoord (coord orientation)
  (check-type coord coord)
  (check-type orientation orientation)
  (cons coord orientation))

(define-compiler-macro ocoord (coord orientation)
  ‘(cons ,coord ,orientation))

(defun ocoord-coord (ocoord)
  (check-type ocoord ocoord)
  (car ocoord))

(define-compiler-macro ocoord-coord (ocoord)
  ‘(car ,ocoord))

(defun ocoord-orientation (ocoord)
  (check-type ocoord ocoord)
  (cdr ocoord))

(define-compiler-macro ocoord-orientation (ocoord)
  ‘(cdr ,ocoord))

The point of an ocoord is to be able to take a step forward in the direction of the orientation, or to turn clockwise or counterclockwise.

(defun ocoord-advance (ocoord)
  (check-type ocoord ocoord)
  (ocoord (2v+ (ocoord-coord ocoord) (ocoord-orientation ocoord))
          (ocoord-orientation ocoord)))

(define-compiler-macro ocoord-advance (ocoord)
  (let ((ocoord-var (gensym "OCOORD-")))
    ‘(let ((,ocoord-var ,ocoord))
       (ocoord (2v+ (ocoord-coord ,ocoord-var) (ocoord-orientation ,ocoord-var))
               (ocoord-orientation ,ocoord-var)))))

(defun ocoord-cw (ocoord)
  (check-type ocoord ocoord)
  (ocoord (ocoord-coord ocoord)
          (cond ((equal (ocoord-orientation ocoord) +north+) +east+)
                ((equal (ocoord-orientation ocoord) +east+) +south+)
                ((equal (ocoord-orientation ocoord) +south+) +west+)
                ((equal (ocoord-orientation ocoord) +west+) +north+))))

(defun ocoord-ccw (ocoord)
  (check-type ocoord ocoord)
  (ocoord (ocoord-coord ocoord)
          (cond ((equal (ocoord-orientation ocoord) +north+) +west+)
                ((equal (ocoord-orientation ocoord) +east+) +north+)
                ((equal (ocoord-orientation ocoord) +south+) +east+)
                ((equal (ocoord-orientation ocoord) +west+) +south+))))

The grid input to many of the puzzles is presented as “ASCII art” characters in a file. For example, the input might look like this:

....#.....
.........#
..........
..#.......
.......#..
..........
.#..^.....
........#.
#.........
......#...

To read this into a grid, we’ll need a function that converts a string into a list of atoms. We’ll need a function that converts a char to an atom:

(defun string-mapper (char-fn)
  "Returns a function that maps strings to lists."
  (lambda (line)
    (collect ’list
      (map-fn ’t
        char-fn
        (scan ’string line)))))

We can use this to read the input file into a grid:

(defun read-file-into-grid (char-fn filename)
  "Returns the contents of the file as a two-dimensional array."
  (row-list->grid
   (collect ’list
     (map-fn ’list
             (string-mapper char-fn)
             (scan-file filename #’read-line)))))

char-fn is called on each character in the file. If it is #’identity, then the grid will be a grid of characters. However, we usually want a grid of atoms, so we supply a function that converts a character to an atom.

(defun char->decimal (char)
  (- (char-code char) (char-code #\0)))

(defun char-interner (char-folder package)
  (lambda (char)
    (if (digit-char-p char)
        (char->decimal char)
        (intern (string (funcall char-folder char)) package))))

We can use this to read the input file into a grid:

;; Case folding
(read-file-into-grid (char-interner #’char-upcase *package*) "input.txt")

;; Case preserving
(read-file-into-grid (char-interner #’identity *package*) "input.txt")

Other miscellaneous functions

advent-pathname converts a relative pathname to an absolute pathname in the advent2024 directory. advent-pathname is used to find the input files.

(defun advent-pathname (pathname)
  (merge-pathnames pathname
                   (asdf/system:system-source-directory "advent2024")))

cartesian-product-list takes a list of lists and returns a list of lists that are the cartesian product of the input lists. For example, (cartesian-product-list ’((1 2) (3 4))) returns ((1 3) (1 4) (2 3) (2 4)).

(defun map-cons (car cdrs)
  (map ’list (lambda (cdr) (cons car cdr)) cdrs))

(defun cartesian-product (&rest lists)
  (cartesian-product-list lists))

(defun cartesian-product-list (lists)
  (fold-left (lambda (tails terms)
               (mappend (lambda (term)
                          (map-cons term tails))
                        terms))
             (list nil)
             (reverse lists)))

integer-log is used to find the number of digits an integer has in a given base.

(defun integer-log (n base)
  "Returns two values, the integer-log of <n> in <base>, and the leftmost digit
in <base>."
  (if (< n base)
      (values 0 n)
      (multiple-value-bind (ilog l) (integer-log n (* base base))
        (if (< l base)
            (values (* ilog 2) l)
            (values (+ (* ilog 2) 1) (/ l base))))))

Miscellaneous list functions

I gave the miscellaneous list functions as a puzzle in a previous post. I’ll repeat them here for convenience.

map-pairs takes a list of items and maps a function over all pairs of items. For example:

(map-pairs #’list ’(1 2 3))

((1 2) (1 3) (1 4) (2 3) (2 4) (3 4))

revmap is like map, but it returns a list in reverse order.

revmap-cons, given a car and list of cdrs, returns a list of lists where each list has the car and one of the cdrs. The lists are returned in reverse order.

revmappend is like mappend, but it returns the list in reverse order.

remove-one-element returns a list of lists. Each sublist is the input list with one element removed.

Miscellaneous scanner

scan-suffixes takes a sequence and returns a series of the suffixes of the sequence. If include-empty? is true (the default), then the empty sequence is the last suffix. If proper? is true (default false), then the original full sequence is omitted from the series.


Armed with these miscellaneous functions, we can tackle the puzzles. I’ll write up some solutions in the next few posts.

Monday, February 10, 2025

Out of Practice List-fu

How is your list-fu? Mine gets rusty when I don’t manipulate lists for a while. Here are some simple puzzles to get the rust out.

1. Write a function that takes a list of items and maps a function over the pairs of items in the list, in the following way: The first argument to the function is taken from one of the elements in the list. The second argument is taken from one of the subsequent elements in the list. E.g., if the list is (a b c d), then

(map-pairs (lambda (x y) ‘(F ,x ,y)) ’(a b c d))

((F A B) (F A C) (F A D) (F B C) (F B D) (F C D))

2. Write a function revmap that is like mapcar, but the result is in reverse order.

3. Write a function map-cons that takes a car and a list of cdrs, and returns a list of the car consed on each of the cdrs.

4. Write a function revmappend that is like alexandria:mappend but is more efficient because it doesn’t try to preserve the order of the elements.

5. Write a function remove-one-element that takes a list of n elements and returns n lists of n-1 elements, where each sublist has one element removed from the original list.

Friday, January 17, 2025

Valid Use Case for Copilot

Our compay proides us with GitHub copilot, which is yet another example of an “AI” engine. I’ve reviewed it before and I wasn’t particulary impressed. It writes mediocre code.

However, I found a use case where it really shines. I was setting up the blank project repositories for our upcoming hackathon. This involved creating a bunch of otherwise empty repositories with a customize README.md file. The simple solution was to automate this with an ad hoc shell script.

I don’t make a practice of writing shell scripts. I write a few every now and then, but I don’t live and breathe bash. It takes me a while because I forget the flags. I have to look up the exact syntax for things like the find command. Then I have to fight with the shell to get the quoting and escaping right. It’s a tedious chore. No doubt I would become adept at it if it were something I did daily, but it’s not.

So I decided to ask GitHub copilot to write some scripts for me. I gave it my problem statement: start with a file with a list of repository and description pairs. For each pair, look for the subdirectory with that name and descend into it. Use the sed command to modify the README.md file in the subdirectory to add the repository discription. Then use git to commit and push the change.

Copilot gave this a couple of seconds thought and came up with this script:

while IFS= read -r line; do
  dir_name=$(echo "$line" | cut -d' ' -f1)
  description=$(echo "$line" | cut -d' ' -f2-)
  if [ -d "$dir_name" ]; then
    sed -i "s/\[\[github_repo_description\]\]/$description/g" "$dir_name/README.md"
  else
    echo "Directory $dir_name does not exist."
  fi
done < descriptions.txt

find . -type d -name "hack*" -exec sh -c '
  cd "$0"
  if [ -f README.md ]; then
    git add README.md
    git commit -m "Update description."
    git push
  fi
' {} \;       

It isn’t a script that’d I’d write home about, but it got the job done. I ran the script and had the repositories set up in couple of minutes. I could have written the script myself, but it would have take me longer. I had forgotten the options to the find command. I had forgotten the arguments to the cut command. I would have had to look them up. Copilot saved me that time.

A co-worker of mine questioned the engineering tradeoff of using a resource hog like generative AI to write crappy, throwaway shell scripts. From the standpoint of an indiviual developer, though, this is the first use case for copilot that I’ve where it actualy saved me time and effort.

Iteration

Iteration is simply that special case of recursion that doesn’t accumulate storage in the long term. It’s a notable special case because computer storage is finite, and you want to be able to write agorithms that are bound by constant space.

There are two common strategies that computer languages use to approach iteration. Functional languages like Scheme and Haskell make sure that normal function calls do not accumulate storage per se. Function calls can be used to direct the control flow, and if they direct the control flow in a loop, you will iterate. Most other languages achieve iteration via special iteration constructs that you must use if you want to iterate. Each of these approaches has its own advantages and disadvantages.

The advantage of using special iteration constructs are these:

  • It is clear that you are iterating.
  • Special constructs are usually optimized for iteration and have particular compiler support to make them efficient.
  • Special constructs are constrained so that you cannot accidentally write non-iterative code.

The disadvantage of using special iteration constructs are these:

  • Special constructs are drawn from a fixed set of constructs that are built in to the language. If you want to iterate differently, you are out of luck.
  • Special constructs usually do not cross function boundaries. Iteration must reside in a single function.
  • You have to decide beforehand that you want to iterate and choose an iteration construct.
  • Special constructs are usually imperative in nature and operate via side effects.

The alternative approach used by functional languages is to make the language implementation tail recursive. This has these advantages:

  • Iteration is automatic. You don’t have to decide that you want to iterate, it just happens when it can.
  • Iteration can cross function boundaries.
  • You can write your own iteration constructs and build them out of ordinary functions.
  • Iteration can be done purely functionally, without side effects.

The disadvantages of using tail recursion for iteration are these:

  • It is not obvious that you are iterating or intended to.
  • You have to be careful to place all the iteration in tail position or you will blow the stack. Beginner programmers often have difficulty recognizing which calls are tail calls and can find it hard to avoid blowing the stack.
  • Small, innocent looking changes in the code can change its behavior to be non tail recursive, again blowing the stack.
  • The stack no longer contains a complete call history. If you rely on the stack as a call history buffer for debugging, you may find debugging more difficult.

The code in an iteration can be classified as being part of the machinery of iteration — the part that sets up the itertion, tests the ending conditional, and advances to the next iteration — or part of the logic of the iteration — the specific part that you are repeating. The machinery of the iteration is usually the same across many iterations, while the logic of the iteration is idiomatic to the specific instance of iteration. For example, all iterations over a list will have a null test, a call to CDR to walk down the list, and a call to CAR to fetch the current element, but each specific iteration over a list will do something different to the current element.

There are several goals in writing iterative code. One is to have efficient code that performs well. Another is to have clear code that is easy to understand, debug, and maintain. You choose how to iterate based on these considerations. For the highest performing code, you will want detailed control over what the code is doing. You may wish to resort to using individual assignments and GOTO statements to squeeze the last clock cycles out of an inner loop. For the clearest code, you will want to use a high degree of abstraction. A clever compiler can generate efficient code from highly abstracted code, and experienced programmers know how to write abstract code that can be compiled to efficient code.

Here are some examples of iteration strategies Lisp. To make these examples easy to compare I chose a simple problem to solve: given a list of numbers, return both a list of the squares of the numbers and the sum of the squares. This is a simple problem that can be solved in many ways.

Tagbody and Go

A tagbody is a block of code that is labeled with tags. You can jump to a tag with a go statement. This is a very low level form of iteration that is not used much in modern Lisp programming. Here is an example of a tagbody:

(defun iteration-example-with-tagbody (numbers)
  (let ((squares ’())
        (total 0)
        (nums numbers))
    (tagbody
     start
       (if (null nums)
           (go end))
       (let ((square (* (car nums) (car nums))))
         (setq squares (cons square squares))
         (incf total square))
       (setq nums (cdr nums))
       (go start)
     end
       (values (nreverse squares) total))))

This is like programming in assembly code. The go instructions turn into jumps. This code is very efficient, but it is not particularly clear. The machinery of the iteration is mixed in with the logic of the iteration, making it hard to see what is going on. The code is not very abstract.

State Machine via Mutual Tail Recursion

Here we use tail recursion to iterate. The compiler will turn the tail recursive call into a jump and the variable rebinding into assignments, so this code will be about as efficient as the tagbody code above.

(defun iteration-example-tail-recursive (numbers &optional (squares ’()) (total 0))
  (if (null numbers)
      (values (nreverse squares) total)
      (let ((square (* (car numbers) (car numbers))))
        (iteration-example-tail-recursive
         (cdr numbers)
         (cons square squares)
         (+ total square)))))

This state machine only has one state, so it is not a very interesting state machine. The ultimate in iteration control is to write an iterative state machine using mutually tail recursive functions. The compiler will generate very efficient code for this, and you can write the code in a very abstract way. Here is an example of a state machine that simulates the action of a turnstile:

(defun turnstile (actions)
  "State machine to simulate a turnstile with actions ‘push’, ‘coin’, and ‘slug’."
  (locked-state actions ’() ’()))

(defun locked-state (actions collected return-bucket)
  (cond ((null actions) (list collected return-bucket))
        ((eql (car actions) ’coin)
         (unlocked-state (cdr actions) collected return-bucket))
        ((eql (car actions) ’push)
         (locked-state (cdr actions) collected return-bucket))  ;; Ignore push in locked state
        ((eql (car actions) ’slug)
         (locked-state (cdr actions) collected (append return-bucket ’(slug)))) ;; Return slug
        (t (locked-state (cdr actions) collected return-bucket))))

(defun unlocked-state (actions collected return-bucket)
  (cond ((null actions) (list collected return-bucket))
        ((eql (car actions) ’push)
         (locked-state (cdr actions) (append collected ’(coin)) return-bucket))
        ((eql (car actions) ’coin)
         (unlocked-state (cdr actions) collected (append return-bucket ’(coin)))) ;; Return coin
        ((eql (car actions) ’slug)
         (unlocked-state (cdr actions) collected (append return-bucket ’(slug)))) ;; Return slug
        (t (unlocked-state (cdr actions) collected return-bucket))))

;; Example usage:
(turnstile ’(coin push coin push))  ;; => ((coin coin) ())
(turnstile ’(push coin push))       ;; => ((coin) ())
(turnstile ’(coin coin push push))  ;; => ((coin) (coin))
(turnstile ’(push))                 ;; => (NIL NIL)
(turnstile ’(coin push push))       ;; => ((coin) ())
(turnstile ’(coin coin coin push))  ;; => ((coin) (coin coin))
(turnstile ’(slug coin push))       ;; => ((coin) (slug))
(turnstile ’(coin slug push))       ;; => ((coin) (slug))
(turnstile ’(slug slug push coin push)) ;; => ((coin) (slug slug))

The iteration machinery is still interwoven with the logic of the code. We’re still finding calls to null and cdr sprinkled around the code. Nonetheless, structuring iterative code this way is a big step up from using a tagbody and go. This is my go-to method for compex iterations that cannot easily be expressed as a map or reduce.

Loop Macro

Common Lisp’s loop macro is a very powerful iteration construct that can be used to express a wide variety of iteration patterns.

defun loop-iteration-example (numbers)
  (loop for num in numbers
        for square = (* num num)
        collect square into squares
        sum square into total
        finally (return (values squares total))))

Call me a knee-jerk anti-loopist, but this doesn’t look like Lisp to me. It has some major problems:

  • It is highly imperative. To understand what is going on, you have to follow the code in the order it is written. You need to have a mental model of the state of the loop at each point in the iteration. Running into a loop when reading functional code takes you out of the zen of functional programming.
  • The bound variables are not lexical, they are scattered around the code. You have to carefully examine each clause to figure out what variables are being bound.
  • You need a parser to walk the code. There is nothing that delimits the clauses of the loop; it is a flat list of random symbols and forms. You couldn’t easily write a program that takes a loop form and transforms it in some way.

Do and Friends

The do macro, and its friends dolist, dotimes, and do*, etc., are the most common iteration constructs in Common Lisp.

(defun iteration-example-with-do (numbers)
  (let ((squares ’())
        (total 0))
    (do ((nums numbers (cdr nums)))
        ((null nums) (values (nreverse squares) total))
      (let ((square (* (car nums) (car nums))))
        (setq squares (cons square squares))
        (incf total square)))))

The do macros have some drawbacks:

  • They are imperative. The body of a do loop ultimately must have some sort of side effect or non-local exit to “get a value out”. Notice how we bind accumulator variables in an outer scope and assign them in the inner one. This is a common pattern in a do loop.
  • They do not compose. You can nest a dotimes inside a dolist, e.g., but you cannot run a dotimes in parallel with a dolist.
  • They are incomplete. There is no do-array or do-string, for example.

But at least you can parse them and transform them. They are structured, and you can write a program that walks the clauses of a do loop and does something with them.

Map and Reduce

Map and reduce abstract the machinery of iteration away from the logic of the iteration through use of a monoid (a higher order function). The resulting code is clear and concise:

(defun iteration-example-with-map-reduce (numbers)
  (let* ((squares (map ’list (lambda (num) (* num num)) numbers))
         (total (reduce #’+ squares)))
    (values squares total)))

The looping is implicit in the mapcar and reduce functions. You can usually make the assumption that the language implemetors have optimized these functions to be reasonably efficient.

I often see programmers writing looping code when a perfectly good library function exists that does the same thing. For example, it is common to want to count the number of items in a sequence, and Commmon Lisp supplies the count function just for this purpose. There is no need to write a loop.

Common Lisp provides a filter function, but it is called remove-if-not.

The drawback of using these functions is that large intermediate sequences can be created. In our example code, the entire list of squares is constructed prior to reducing it with #’+. Of course the entire list is one of the return values, so you need it anyway, but if you only needed the sum of the squares, you would prefer to sum it incrementally as you go along rather than constructing a list of squares and then summing it. For small sequences, it doesn’t make a difference.

Series

The series macro suite attempt to bring you best of both worlds. You write series expressions that look like sequence functions, but the macro recognizes that you are iterating and generates efficient incremental code.

(defun iteration-example-with-series (numbers)
  (let ((squares (map-fn ’integer (lambda (n) (* n n)) (scan ’list numbers)))
    (values (collect ’list squares)
            (collect-sum squares))))

This code is very similar to the sequence case, but the series macro will generate code that does not construct the entire list of squares before summing them. It will sum them incrementally as it goes along.

Series will expand into a tagboy. For example, the above code will expand into something like this:

(COMMON-LISP:LET* ((#:OUT-1015 NUMBERS))
  (COMMON-LISP:LET (#:ELEMENTS-1012
                    (#:LISTPTR-1013 #:OUT-1015)
                    (SQUARES 0)
                    #:SEQ-1018
                    (#:LIMIT-1019
                     (COMMON-LISP:MULTIPLE-VALUE-BIND (SERIES::X SERIES::Y)
                         (SERIES::DECODE-SEQ-TYPE (LIST ’QUOTE ’LISTS))
                       (DECLARE (IGNORE SERIES::X))
                       SERIES::Y))
                    (#:LST-1020 NIL)
                    (#:SUM-1023 0))
    (DECLARE (TYPE LIST #:LISTPTR-1013)
             (TYPE INTEGER SQUARES)
             (TYPE (SERIES::NULL-OR SERIES::NONNEGATIVE-INTEGER) #:LIMIT-1019)
             (TYPE LIST #:LST-1020)
             (TYPE NUMBER #:SUM-1023))
    (TAGBODY
     #:LL-1026
      (IF (ENDP #:LISTPTR-1013)
          (GO SERIES::END))
      (SETQ #:ELEMENTS-1012 (CAR #:LISTPTR-1013))
      (SETQ #:LISTPTR-1013 (CDR #:LISTPTR-1013))
      (SETQ SQUARES ((LAMBDA (N) (* N N)) #:ELEMENTS-1012))
      (SETQ #:LST-1020 (CONS SQUARES #:LST-1020))
      (SETQ #:SUM-1023 (+ #:SUM-1023 SQUARES))
      (GO #:LL-1026)
     SERIES::END)
    (COMMON-LISP:LET ((SERIES::NUM (LENGTH #:LST-1020)))
      (DECLARE (TYPE SERIES::NONNEGATIVE-INTEGER SERIES::NUM))
      (SETQ #:SEQ-1018 (MAKE-SEQUENCE ’LISTS (OR #:LIMIT-1019 SERIES::NUM)))
      (DO ((SERIES::I (1- SERIES::NUM) (1- SERIES::I)))
          ((MINUSP SERIES::I))
        (SETF (ELT #:SEQ-1018 SERIES::I) (POP #:LST-1020))))
    (VALUES #:SEQ-1018 #:SUM-1023)))

90% of the time, the series macro will produce very efficient code, but 10% of the time the macro loses its lunch. It takes a little practice to get use to when the series macro will work and to write code that the series macro can handle.

Conclusion

There are many ways to iterate in Lisp, some are more efficient than others, some are more abstrac than others. You choose the way that suits your needs. I like the abstraction of the series macro, but I will also use a library function like count when it is appropriate. When I need tight control, I’ll write a state machine.

Tuesday, January 14, 2025

λ Calculus

A lambda calculus is a set of rules and strategies for manipulating logical expressions. As Church defined them, these logical expressions are linear lists of symbols. A symbol is effectively a variable. Two expressions in sequence indicate a function application. The special symbol λ is just a marker to indicate a function. Parenthesis can be used to group expressions.

McCarthy’s S-expressions are an alternative representation of a logical expression that is more suitable for a computer. Rather than a linear list of symbols, S-expressions use a tree structure of linked lists in memory. Symbols are still variables, lists represent function application, the special symbol lambda at the beginning of a list indicates a function, and grouping is achieved by nesting a list within another.

When McCarthy invented S-expressions, he wanted to show that the nested list structure of S-expressions could faithfully represent the logical expressions from lambda calculus. (It can.) A lambda calculus can be restated as a set of rules and strategies for manipulating S-expressions. This makes it easier for a computer to do lambda calculus. As a Lisp hacker, I find it also makes it easier for me to think about lambda calculus.

Your basic lambda calculus just has symbols, lists, and λ expressions. That’s it. But let us introduce one more element. Recall that we can think of a LET expression as syntactic sugar for a list (function call) where the first element (the operator) is a lambda expression. We’ll keep our S-expressions fully sugared and write all such lists as LET expressions. So now our S-expressions have symbols, lists, λ expressions, and LET expressions.

The two basic rules for manipulating S-expressions are α, which is a recursive rule for renaming a symbol in an S-expression, and β, which gets rid of a selected LET expression. A basic lambda calculus consists of these two rules and a strategy for selecting which LET expressions to get rid of. β reduces a LET expession by substituting the variables for their bindings in the body of the LET. α is used as needed to avoid unwanted variable capture during β-reduction. β eliminates one LET expression, but it can introduce more if you end up substituting a λ expression into operator position.

If an expression contains no LET expressions, we say it is in “normal form”. A common task in lambda calculus is to try to reduce an expression to normal form by attempting to eliminate all the LET expressions. Sometimes you cannot achieve this goal because every time you apply the β rule to eliminate a LET expression, it ends up introducing further LET expressions.

There are many strategies for selecting LET expressions to eliminate. Not all strategies will necessarily end up getting you to a normal form, but all strategies that do end up at a normal form end up at the same normal form (modulo the variable names). One strategy is of note: selecting the leftmost, outermost LET expression and reducing it first is called “normal order”. It is notable because if any strategy converges to normal form, then the normal order strategy will, too. However, the normal order strategy can lead to an exponential explosion of intermediate expressions. There are other strategies that avoid the exponential explosion, but they don’t always converge to normal form. Pick your poison.

α and β are the only rules we need to compute with S-expressions. The simple lambda calculus with α and β is universal — it can compute anything that can be computed. It is Turing complete.

I don’t know about you, but I find it quite remarkable that this can compute anything, let alone everything. Nothing is going on here. α just renames symbols. Using α-conversion to rename all the foos to bars doesn’t change anything but the symbol names. We define expression equivalence modulo α, so the actual names of the symbols isn’t important. Apparently β-reduction does computation, but it is hard to say how, exactly. It is just simplifying LET expressions by replacing variables with what they are bound to. But a variable is simply a name for a binding. When you replace a variable with what it is bound to, you don’t change any values. The resulting expression may be simpler, but it means the same thing as the original.

We use β reduction as a model of subroutine (function) calls. In a subroutine call, the values of the arguments are bound to the names of the arguments before evaluating the body of the subroutine. In β reduction, the body of the expression is substituted with the names bound to the value expressions. The lambda calculus model of a computer program will have a β reduction wherever the program has a subroutine call. A lambda calculus expression with opportunities for β reduction can be translated into a computer program with subroutine calls at those locations. It’s a one-to-one mapping. Since we can compute anything using just the α and β rules, we can likewise compute anything with just function calls. I think that’s pretty remarkable, too.

Turing’s machine formalism was designed to be understandable as a physical machine. Turing was particular that his machine could be realized as a mechanical object or electronically. It is far less clear how to make a lambda calculus into a physical machine. Once we recognize that β can be realized as a subroutine in software, we can see that Church’s lambda calculus formalism can be understable as a virtual machine.

Church’s Calculi of Lambda Conversion is a cool book where he lays out the principals of lambda calculus. It is pretty accessible if you have experience in Lisp, and the examples in the book will run in a Scheme interpreter if you translate them.

Monday, January 6, 2025

Substitution vs. State Transition

With a traditional curly-brace language, you have a model of a machine. A program specifies a sequence of state transitions that the machine should go through. When all the state transitions have taken place, the machine is in a final state, and the program is done.

As a programmer, you have to keep a mental model of the state of the machine at various points in the program. Your mental model has to include a temporal element — you have to remember what instruction you are working on, and what comes next. For each instruction, you have to consider the state before and after executing the instruction.

Lisp is very different from this. A Lisp program isn't a series of instructions, it is a tree of symbols. If you don’t use side effects, you can think of the Lisp interpreter as a simple substitution engine that operates on this tree. The interpreter just substitutes symbols with their values. You don’t have to consider any state before and after substitution because substitution doesn’t change anything.

Even if you do use side effects, you can still think of the interpreter as a substitution engine, but the substitution algorithm is more complicated. You will need a mental model that includes state and a temporal component, but it is still basically a substitution model.

Substitution models are easier to reason about than state transition models. This is why Lisp is so powerful. It takes a little practice to get used to programming with a simple substitution model. That’s why Lisp has a learning curve, especially for people who expect, and are used to, a state transition model.

You can also reason about a Lisp program using a state transition model. You can switch between the two models and use whatever mental model is most appropriate for the problem at hand.

You can impose a substitution model on curly-brace language, but it is more difficult. Curly-brace languages are designed to make you think about state transitions — indeed, many such languages force you to use a state transition to accomplish even the most simple conditionals and iterations — and the language doesn’t make it easy to ignore them and focus on the final value.

If Lisp is your first computer language, you learn the simple substitution model first. You’ll eventually have to learn about state transitions because they are needed to explain side effects. But you’ll mostly want to write programs that you can reason about using a substitution model. If you learn a curly-brace language first, you’ll have to think beyond the state transition model you have been taught and are using to reason about programs.

Many people find it difficult to learn how to reason with a new model. After all, the old model should work — it is universal. “Just assign the variable, don’t make me jump through hoops.” People who have a hard time wrapping their heads around substitution will probably find Lisp confusing and frustrating. But some people are able to embrace the substitution model and learn how it relates to the state transition model. These people will find Lisp to be a mind-expanding, powerful, expressive language.

Sunday, January 5, 2025

GitHub glitch bites hard (and update)

Update: Possible rogue process

GitHub reports that the call that removed the users was not the Copilot API but rather a call to the org membership API made by one of our bots.

We have a cron job that runs daily and keeps GitHub in sync with our internal databases. When GitHub and our internal databases disagree, the cron job makes API calls to reconcile the difference. It has the ability to remove users if it think they are no longer supposed to be members of the org.

It seems to have erroneously removed a large number of members. It was purely coincidence that I was editing copilot licenses at or around the time.

The question now is why? My hypothesis is that a query to our internal database only produced a partial result. The number of people determined to be valid users was far fewer than it should have been, and the cron job acted (correctly) and removed the users that were not verified by the database query. But it is hard to say for sure. I’ll need to check the cron job logs to see if I can determine what went wrong. It is very unusual, though. I’ve been here for years and I’ve never seen the cron job glitch out before. This is my working hypothesis for the moment. Perhaps it was some other error that made it think that the membership was greatly reduced.


I got bit hard by a GitHub bug last week.

Now GitHub has “organizations” which are owners of groups of repositories. GitHub carefully handles organization membership. You cannot directly join an organization, you must be invited by the organization. This gives the organization control over who can join the organization. But an organization also cannot directly add you as a member. It can invite you to join, but you must choose to accept the invitation. This gives you control over which organizations you are associated with. Membership in an organization is jointly controlled by the organization and the member. There is no way to bypass this.

This is source of friction in the onboarding process in our company. We have a few repositories on GitHub that are owned by the company. When a new hire joins the company, we want to make them members of the organization. GitHub does not provide any way to automate this. Instead, we direct new hires to an internal web site that will authenticate and authorize them and then let them issue an invitation to join the organization. GitHub won’t give them access until they accept the invitation. This is a manual process that is error prone and places the burden of doing it correctly on the new hire. We often have to intervene and walk them through the process.

Keep this in mind.

Our company provides GitHub Copilot to our developers. Some developers like it, but many of our developers choose not to use it. While Copilot licenses are cheap, there is no point in paying for a license that is not used. The UI for GitHub Copilot will display the last time a person used Copilot. It is easy to see a small set of our users who have never logged on to Copilot. We decided to save a few bucks by revoking unused Copilot licenses. We reasoned that we could always turn it back on for them if they wanted to use it.

To test this out, I selected a few of the users who had never logged in to Copilot. I turned off the checkbox next to their names in the Copilot UI and clicked the save button. It appeared to work.

Within an hour I started getting complaints. People who claimed to be active Copilot users were getting messages that their Copilot access was revoked. It seems that the UI had listed several active users as “never logged in” and I had just revoked their access.

It got worse. I had only revoked a few licenses, but dozens of people had had their access revoked. It seems that GitHub had eagerly revoked the licenses of far more people than I had selected.

It got even worse. I have a list of everyone who should have access, so I know who to re-enable. But I cannot re-enable them. It seems that in addition to revoking their Copilot access, GitHub had taken the extra step of removing their membership in the organization. I cannot restore their membership because of the way GitHub handles organization membership, so until they visit our internal web site and re-issue the invitation to the organization, I cannot restore their Copilot access. This has been a monumental headache.

I’ve spent the week trying to explain to people why their Copilot access and organization membership was revoked, what steps they need to take to restore it, and why I cannot restore it for them.

It looks like I’m going to be spending a lot of time on this next week as well.


GitHub has an enterprize offering that allows you to automate account creation and organization membership. We've been considering this for a while. Unfortunately, you cannot mix legacy accounts with enterprize accounts, so we would have to atomically migrate the entire company and all the accounts to the enterprize offering. This would be a risky endeavor for only a little gain in convenience.

Saturday, January 4, 2025

fold-… and monoids

Suppose you satisfy these axioms:

  • you have a binary function • and a set that • is closed over (i.e. for all x, y in the set, xy is in the set)
  • • is associative, ((a • b) • c) = (a • (b • c))
  • There is an an identity element I: a • I = I • a = a

Then • is called a semigroup or “monoid”.

Monoids come from abstract algebra, but they are ubiquitous in computer science. Here are some monoids: string-append over strings, addition over integers, state transition over machine states, compose over unary functions.

Alternatively, we can define a monoid as a binary function • that is closed under folds fold-left or fold-right. That is, (fold-left #’• I list-of-set-elements) is an element of the set. Folds abstract the processing lists of set elements. The walk through the list, the end test, and the accumulation of the result are all taken care of by the implementation of fold. You get to focus on the monoid that acts on each element.

Folds come in two flavors: fold-left and fold-right. fold-left has an obvious iterative implementation, but the result is accumulated left to right, which can come out backwards. fold-right has an obvious recursive implementation which accumulates right to left, The result comes out in the right order, but the recursion can cause problems if the stack space is limited.

Here are some stupid tricks you can do with folds and monoids.

Create n-ary functions

If we curry the call to fold, we extend the binary function of two arguments to an n-ary function of a list of arguments. For example, n-ary addition is just a fold over binary addition. (fold-left #’+ 0 list-of-integers). Likewise, n-ary compose is just a fold over binary compose.

Fold-… is self documenting

If I haven’t used fold-left or fold-right in a while, I sometimes forget which one computes what. But fold-left and fold-right can document themselves: use a combining function that returns the list (F a b) to indicate a call to F:

> (fold-left (lambda (a b) (list ’F a b)) ’|...| ’(c b a))
(F (F (F |...| C) B) A)

> (fold-right (lambda (a b) (list ’F a b)) ’(a b c) ’|...|)
(F A (F B (F C |...|)))

You can see the structure of the recursion by using list as the combining function:

> (fold-left #’list ’|...| ’(c b a))
(((|...| C) B) A)

> (fold-right #’list ’(a b c) ’|...|)
(A (B (C |...|)))

fold-… works on groups

A group is a special case of a monoid where the combining function is also invertible. fold-… can be used on a group as well. For example, fold-left can be used on linear fractional transformations, which are a group under function composition.

fold-… as an accumulator

The combining function in fold-left must be at least semi-closed: the output type is the same as the type of the left input. (In fold-right, the output type is the same as the type of the right input.) This is so we can use the output of the prior call as the input to the next call. In effect, we set up a feedback loop between the output to one of the inputs of the binary function. This feedback loop has a curious property: it behaves as if it has state. This is happens even though both fold-… and the combining functions are pure functions. The state appears to arise from the feedback loop.

We can use fold-… to accumulate a value. For fold-left, at each iteration, the accumulator is passed as the first (left) argument to the combining function while the next element of the list is the second (right) argument. The combining function returns a new value for the accumulator (it can return the old value if nothing is to be accumulated on this step). The result of the fold-left is the final value of the accumulator.

Note that because the accumulated value is passed as the first argument, you cannot use cons as the combining function to accumulate a list. This is unfortunate because it seems obvious to write (fold-left #’cons ’() ...) to accumulate a list, but that isn’t how it works. However, if you swap the arguments to cons you’ll accumulate a list:

(defun xcons (cdr car) (cons car cdr))

(defun revappend (elements base)
  (fold-left #’xcons base elements))

fold-… as a state machine

Although fold-left is commonly used to accumulate results, it is more general than that. We can use fold-left as a driver for a state machine. The second argument to fold-left is the initial state, and the combining function is the state transition function. The list argument provides a single input to the state machine on each state transition.

For example, suppose you have a data structure that is a made out of nested plists. You want to navigate down through the plists to reach a final leaf value. We set up a state machine where the state is the location in the nested plists and the state transition is navigation to a deeper plist.

(defun getf* (nested-plists path)
  (fold-left #’getf nested-plists path))

Alternatively, we could drive a state machine by calling fold-left with an initial state and list of state transtion functions:

(defun run-state-machine (initial-state transitions)
  (fold-left (lambda (state transition)
               (funcall transition state))
             initial-state
             transitions))

Visualizing fold-left

If we unroll the recursion in fold-left, and introduce a temp variable to hold the intermediate result, we see the following:

(fold-left F init ’(c b a))

temp ← init
temp ← F(temp, c)
temp ← F(temp, b)  
temp ← F(temp, a)

I often find it easier to write the combining function in a fold-… by visualizing a chain of combining functions wired together like this.

Generating pipelines

Now let’s partially apply F to its right argument. We do this by currying F and immediately supplying an argument:

(defun curry-left (f)
  (lambda (l)
    (lambda (r)
      (funcall f l r))))

(defun curry-right (f)
  (lambda (r)
    (lambda (l)
      (funcall f l r))))

(defun partially-apply-left (f l)
  (funcall (curry-left f) l))

(defun partially-apply-right (f r)
  (funcall (curry-right f) r))

We can partially apply the combining function to the elements in the list. This gives us a list of one argument functions. In fact, for each set element in the set associated with our monoid, we can associate a one-argument function. We can draw from this set of one-argument functions to create pipelines through function composition. So our visualization

temp ← init
temp ← F(temp, c)
temp ← F(temp, b)  
temp ← F(temp, a)

becomes

temp ← init
temp ← Fc(temp)
temp ← Fb(temp)  
temp ← Fa(temp)

We can write this pipeline this way:

result ← Fa ← Fb ← Fc ← init

or this way:

result ← (compose Fa Fb Fc) ← init

We can pretend that the elements of the set associated with monoid are pipeline stages. We can treat lists of set elements as though they are pipelines.

Notice how we never write a loop. We don’t have the typical list loop boilerplate

(if (null list)
         ... base case ...
  (let ((element (car list))
        (tail (cdr list)))
    ... ad hoc per element code ...
    (iter tail)))

Instead, we have a function that processes one element at a time and we “lift” that function up to process lists of elements.

Pipelines are easier to reason about than loops. fold-… converts loops into pipelines.

It takes a little practice to use fold-… in the less obvious ways. Once you get used to it, you’ll see them everywhere. You can eliminate many loops by replacing them with fold-….

Monoids vs. Monads

A monad is a monoid over a set of curried functions. You use a variant of compose to combine the curried functions. Monads force sequential processing because you set up a pipeline and the earlier stages of the pipeline naturally must run first. That is why monads are used in lazy languages to embed imperative subroutines.