A Schemer in Common Lisp Land

(updated 2023-10-06)

Basic functionality of Common Lisp (SBCL) seen from a Schemer's view. I list commands in lowercase, fields are UPPERCASE, {} are optional, ... are repeat.

Everything after ;; comments is translation into a sane language (R6RS Scheme).

General style notes: -p = -?.

CL does not mark mutating commands with !, beware that everything mutates everything, you can't really do FP in this.

There is no tail-call elimination, recursion fills the stack and crashes eventually (soon; CL's a fat piggy for memory).

Documentation:

REPL

I would like to use hashbang #!/usr/bin/env -S sbcl --script

And that works from shell, but SBCL doesn't let you (load) such a script from REPL. Because Common LISP pretends UNIX never happened, even tho UNIX is 14 years older than CL. Scheme is 9 years older than CL and almost all impls (not MIT-Scheme) allow hashbangs in included scripts.

% rlwrap sbcl ;; no builtin line/term editor. For fuck's sake, amateurs.

Long-ass startup banner:

This is SBCL 2.2.2, an implementation of ANSI Common Lisp.
More information about SBCL is available at <http://www.sbcl.org/>.

SBCL is free software, provided as is, with absolutely no warranty.
It is mostly in the public domain; some portions are provided under
BSD-style licenses.  See the CREDITS and COPYING files in the
distribution for more information.

Have later learned --noinform disables this, so now I have a script lol.zsh:

rlwrap sbcl --noinform "$@"

There is a startup file, ~/.sbclrc which can be given some library startup, like:

(load "~/Code/CodeLisp/marklib.lisp")
(prln "READY")

prompt is *, debugger is 0] etc. with this charming interaction:

debugger invoked on a SB-INT:SIMPLE-READER-ERROR in thread
#<THREAD "main thread" RUNNING {1001818003}>:
  no dispatch function defined for #\T
    Stream: #<SYNONYM-STREAM :SYMBOL SB-SYS:*STDIN* {1000023B83}>
Type HELP for debugger help, or (SB-EXT:EXIT) to exit from SBCL.
restarts (invokable by number or by possibly-abbreviated name):
  0: [ABORT] Exit debugger, returning to top level.
(SB-IMPL::READ-MAYBE-NOTHING #<SYNONYM-STREAM :SYMBOL SB-SYS:*STDIN* {1000023B83}> #\#)
0] 0

And can't just q out of the debugger, have to find the last item in the menu and type that.

Library

  • (load FILENAME) ;; include file
  • (require NAME FILENAME) ;; include file once

See Quicklisp for tutorial on setting up the package system.

To check that it's loaded, I add to my .sbclrc:

(prln "Quicklisp: " ql-info:*version*)

Function References

This is the big pain in the ass to a Schemer. Lisp-2 (variable & function scopes) is a design error; unfortunately it's all thru CL, and will always be doing #'(lambda or #'funcname, or (funcall funcname).

  • #'FUNCNAME, (function FUNCNAME) ;; FUNCNAME for function references
  • (lambda (ARG...) BODY) ;; for invocation here, same! Hooray!
  • #'(lambda... ;; to return a reference to the lambda, ugh, never use this!
  • (complement #'FUNCNAME) ;; (λ (x) (not (FUNCNAME x)))

Control

  • (case ( ((X...) THEN)... { (otherwise ELSE) } )) ;; otherwise = else
  • (cond ( (TEST THEN)... { (T ELSE) } )) ;; no else keyword
  • (defun NAME (ARGS) BODY) ;; define
  • (do ( (NAME X0 UPDATEEXPR)... ) (TESTEXPR RETVAL) BODY) ;; uuuugh.
  • (dolist (NAME LS) BODY) ;; (for-each (λ (NAME) BODY) LS)
  • (dotimes (NAME X) BODY) ;; repeat macro if you have it, do/named let otherwise.
  • (flet ( (FUNCNAME (X...) FUNCBODY)... ) BODY) ;; letrec
  • (if TEST THEN ELSE)
  • (labels ( (FUNCNAME (X...) FUNCBODY)... ) BODY) ;; letrec*
  • (loop
    • when COND
    • for VARNAME
    • from X [to Y] ;; BASIC for loop
    • never EXPR ;; skipping elements matching EXPR
    • above X ;; skipping elements below X
    • below X ;; skipping elements above X
    • in LS ;; over list
    • collecting X ;; push X into list, return value
    • summing X ;; add X to total, return value
    • when EXPR BODY
    • finally EXPR ;; perform EXPR at end, often (return X)
    • do BODY) ;; loops until (return X), like a loop inside call/cc. Schemers would just write a named let and be done with it.
  • (progn BODY) ;; begin

  • (return-from FUNCNAME VALUE) ;; early return, (call/cc (lambda (return) ... (return value)))
  • (when TEST BODY), (unless TEST BODY)

 

(defun test-number (x)
    (cond
    ((not (numberp x))  "not a number")
    ((zerop x)  "0")
    ((plusp x)  "+")
    ((minusp x)  "-")
    (T  "?")
))

Function Args

  • (&optional d) ;; d is not required, given NIL (or use -p as above)
  • (&rest rest) ;; called with (1 2 3) giving rest=(1 2 3)
  • (&key akey bkey (ckey cval ckey-p)) ;; called with (:akey 1 :ckey T) giving akey=1, bkey=NIL, ckey=T, ckey-p=T.
  • (&key ((:akey a)) ((:bkey b) bval) ((:ckey c) cval ckey-p)) ;; same but has external keyword & internal variable name pairs.

Constants

  • NIL, () ;; #f false value, but also self-eval empty list '() = ()
  • (QUOTE x) ;; quote value of x
  • (QUASIQUOTE x) ;; backquote x, ,x inserts one item as-is, ,@x splices a list in place.
  • T ;; #t true value
  • #\newline (0x0A), #\space (0x20), #\tab (0x09), #\backspace (0x08), #\linefeed (0x0A), #\page (0x0C), #\return (0x0D), #\rubout (0x7F) ;; special chars
  • #\A ... #\Z ;; normal chars
  • *debug-io* ;; port for interactive debugging
  • *error-output* ;; port for stderr, warnings and non-interactive error messages
  • *query-io* ;; port for bidi stream, prompt/response
  • *standard-input* ;; port for stdin
  • *standard-output* ;; port for stdout
  • *trace-output* ;; port for traced functions & time

Vars

  • (defconstant NAME VALUE) ;; global constant +var+
  • (defparameter NAME VALUE) ;; global dynamic *var*
  • (defvar NAME VALUE) ;; global dynamic *var*, won't replace value if already exists
  • (destructuring-bind (NAME ...) LS BODY) ;; matches parameters like function call
  • (let ((NAME VALUE)...) BODY) ;; lexical scope. Note if you override a dynamic var, it applies within this scope!
  • (let* ((NAME VALUE)...) BODY)
  • (multiple-value-bind (VARNAME ...) EXPR) ;; let*-values
  • (multiple-value-list EXPR)
  • (multiple-value-setq (VARNAME ...) EXPR)
  • (pop PLACE) ;; (let [(y (car PLACE))] (set! PLACE (cdr PLACE)) y) - I use a list-pop! macro for this.
  • (push X PLACE) ;; (let [(ls (cons X PLACE))] (set! PLACE ls) ls) - I use a list-push! macro for this.
  • (setf PLACE VALUE) ;; set! - use this, allows accessors as PLACE. Returns assigned value.
    • (setf VARNAME VALUE) ;; variable
    • (setf (aref ARR IDX) VALUE) ;; array
    • (setf (getf PLIST KEY) VALUE) ;; plist
    • (setf (gethash 'KEY HASH) VALUE) ;; hashtable
    • (setf (FIELD OBJ) VALUE) ;; object slot
  • (setq NAME VALUE) ;; set!, NAME is auto-quoted
  • (set NAME VALUE) ;; set!, NAME is not auto-quoted
  • (incf VARNAME), (decf VARNAME) ;; (set! VARNAME (add1 VARNAME)), sub1

Math/Logic

  • (/= A B) ;; (not (= A B))
  • (1+ X), (1- X) ;; inc/add1, dec/sub1
  • (and X...), (or X...)
  • (ash X Y) ;; arithmetic-shift X << Y, positive = left, negative = right
  • (eq X Y), (eql X Y), (equal X Y), (equalp X Y) ;; eq?, eqv?, equal?, equal-ignore-case?
  • (evenp X), (oddp X), (zerop X), (plusp X), (minusp X) ;; last 2 are positive?, negative?
  • (floor X Y), (truncate X Y), (mod X Y), (rem X Y) ;; div-and-mod, div0-and-mod0, mod, mod0, note multiple values are silently dropped

Char/Strings

Strings have no escape codes except \\ and \". Can you believe that shit? AutoCAD & elisp do, and there's some quicklisp package I can't figure out how to install.

  • (alphanumericp C) ;; (or (char-alphabetic? c) (char-numeric? c))
  • (alpha-char-p C), (digit-char-p C), (graphic-char-p C) ;; char-alpha?, etc., "graphic" is all non control chars.
  • (char S X) ;; string-ref
  • (char= A B), (char-equal A B) ;; char=?, char-ci=?
  • (char/= A B), (char-not-equal A B) ;; (not char=?), (not char-ci=?)
  • (char> A B), (char-greaterp A B), (char-not-lessp A B) ;; char>?, char-ci>?, char-ci>=?
  • (char< A B), (char-lessp A B), (char-not-greaterp A B) ;; char<?, char-ci<?, char-ci<=?
  • (char-downcase S), (char-upcase S)
  • (char-code N), (code-char C) ;; integer->char, char->integer. there's also char-int, but they removed int-char!
  • (string-downcase S), (string-upcase S), (string-capitalize S)
  • (string-trim S), (string-right-trim S), (string-left-trim S)
  • (stringp S)
  • (string= A B), (string-equal A B) ;; string=?, string-ci=?
  • (string/= A B), (string-not-equal A B) ;; (not string=?), (not string-ci=?)
  • (string> A B), (string-greaterp A B), (string-not-lessp A B) ;; string>?, string-ci>?, string-ci>=?
  • (string< A B), (string-lessp A B), (string-not-greaterp A B) ;; string<?, string-ci<?, string-ci<=?
  • (write-to-string N), (parse-integer S) ;; number->string, string->number

Sequences

Strings, lists, vectors/arrays. In Scheme most of these are in SRFI-1 (lists), SRFI-13 (strings), SRFI-43 (vectors).

  • (length SEQ)
  • (elt SEQ X) ;; list-ref, vector-ref, etc.
  • (setf (elt SEQ X) VALUE) ;; (vector-set! SEQ X VALUE)
  • (concatenate TYPE X...) ;; TYPE is 'string, 'list, 'vector. append, vector-append, etc.
  • (count VALUE SEQ), (count-if #'FUNCNAME SEQ), (count-if-not #'FUNCNAME SEQ) ;; count
  • (every #'FUNCNAME SEQ), (some #'FUNCNAME SEQ), (notany #'FUNCNAME SEQ), (notevery #'FUNCNAME SEQ) ;; every, any, inverse every, any
  • (find VALUE SEQ ), (find-if #'FUNCNAME SEQ), (find-if-not #'FUNCNAME SEQ) ;; find, exists, inverse exists
  • (map TYPE #'FUNCNAME SEQ ...) ;; map, specify type as concatenate, any SEQ type
  • (position VALUE SEQ), (position-if #'FUNCNAME SEQ), (position-if-not #'FUNCNAME SEQ) ;; list-index, vector-index, etc.
  • (reduce #'FUNCNAME SEQ :initial-value VALUE) ;; fold
  • (remove VALUE SEQ), (remove-if #'FUNCNAME SEQ), (remove-if-not #'FUNCNAME SEQ) ;; remove, remp, filter
  • (delete VALUE SEQ), (delete-if #'FUNCNAME SEQ), (delete-if-not #'FUNCNAME SEQ) ;; non-consing remove
  • (remove-duplicates SEQ) ;; delete-duplicates
  • (reverse SEQ)
  • (search VALUE SEQ) ;; string-index, annoying function to write for list or vector.
  • (sort SEQ #'FUNCNAME), (stable-sort SEQ #'FUNCNAME) ;; (list-sort proc SEQ), (vector-sort! proc SEQ) from SRFI-32/132
  • (subseq SEQ X {Y}) ;; substring, list: (take (drop v X) (- Y X)), (vector-copy SEQ X Y) from SRFI-43
  • (substitute VALUE #'FUNCNAME SEQ), (substitute-if VALUE #'FUNCNAME SEQ), (substitute-if-not VALUE #'FUNCNAME SEQ) ;; map, string-map, etc.

Sequence functions (count, find, position, remove, substitute) take some named arguments:

  • :test #'FUNCNAME ;; instead of EQUAL, pred is (FUNCNAME X V)
  • :key #'FUNCNAME ;; evaluate (FUNCNAME V) before passing to test
  • :start X
  • :end X
  • :from-end FLAG ;; reverse order
  • :count N ;; only N elements removed/subst'd

Lists

  • (append LS ...), (reverse LS)
  • (nconc LS ...), (nreverse LS) ;; non-consing, reverse!
  • (apply #'FUNCNAME LS)
  • (assoc KEY LS :test #'equal), (acons KEY VALUE LS), (remf LS KEY) ;; SRFI-1 alist, assoc, alist-cons, alist-delete
  • (cons X Y), (list X...)
  • (consp X), (atom X), (listp X), (null X) ;; pair?, (not (pair? x)), list?, null?, inconsistent -p ness.
  • (copy-list LS), (copy-tree LS) ;; SRFI-1 list-copy does spine-only copy, copy-tree is deep copy
  • (first LS), (rest LS) ;; car, cdr
  • (butlast LS { N }), (nbutlast LS { N }) ;; list minus last N=1 items
  • (mapc #'FUNCNAME SEQ), mapl ;; for-each. mapl FUNC gets pair, not car
  • (mapcar #'FUNCNAME LS), mapcan ;; map, takes & returns list. mapcan is non-consing
  • (maplist #'FUNCNAME LS), mapcon ;; map, FUNC gets pair, not car. mapcon is non-consing
  • (member X LS), (getf LS KEY) ;; plist member, memq
  • (nth X LS), (nthcdr X LS) ;; elt but backwards
  • (rplaca LS X), (rplacd LS X) ;; set-car!, set-cdr!

Vectors

  • (vector A ...), #(A ...)
  • (make-array DIM :initial-element X ;; (make-vector DIM X), but DIM can be a list
    • :fill-pointer N :adjustable t ;; growable array, unlimited if adjustable
    • :element-type TYPE ;; 'character makes a string, 'bit makes a bit-vector
    • )
  • (vector-push VALUE ARR), (vector-push-extend VALUE ARR), (vector-pop ARR) ;; add/remove to growable array, -extend for adjustable

Hashtables

Or "hash-tables" as CL and R7RS philistines spell it. It's not a table for eating potatoes.

  • (make-hash-table :test #'FUNCNAME) ;; test must be EQL (default), EQ, EQUAL, EQUALP.
  • (gethash KEY HT) ;; hashtable-ref
  • (maphash #'FUNCNAME HT) ;; hashtable-walk, or loop over (hashtable-keys HT), or see below
  • (multiple-value-bind (value present) (gethash key hash-table) present) ;; hashtable-contains?
  • (setf (gethash KEY HT) VALUE) ;; hashtable-set!
    ;; Scheme maphash
    (let-values (((ks vs) (hashtable-entries ht)))
        (vector-for-each (λ (k v)   ;; In SRFI-43 vector-for-each, parameters are (i k v)
            (println k ":" v))  ;; do something here
            ks vs) )

Macros

  • (defmacro NAME (ARGS) BODY) ;; syntax-case, returns modified expression, NOT hygeinic.
    • ARGS can be as any function, or "destructuring", paren prototypes: ((var start end) &body body)
  • (macroexpand-1 NAME) ;; show one level of macro expansion

To sum up, the steps to writing a macro are as follows:
1. Write a sample call to the macro and the code it should expand into, or vice versa.
2. Write code that generates the handwritten expansion from the arguments in the sample call.
3. Make sure the macro abstraction doesn't "leak".
1. Unless there's a particular reason to do otherwise, include any subforms in the expansion in positions that will be evaluated in the same order as the subforms appear in the macro call.
2. Unless there's a particular reason to do otherwise, make sure subforms are evaluated only once by creating a variable in the expansion to hold the value of evaluating the argument form and then using that variable anywhere else the value is needed in the expansion.
3. Use GENSYM at macro expansion time to create variable names used in the expansion.
—Peter Siebel

(defmacro with-gensyms ((&rest names) &body body)
    `(let ,(loop for n in names collect `(,n (gensym)))
    ,@body))

Input/Output

Common Lisp calls a port a "stream".

  • (finish-output {STREAM}) ;; flush-output-port
  • (format OUTPUT PATTERN ARG...)
    • ~(~A~) prints lowercase, useful for symbols
    • ~:A prints () for NIL
    • ~{~A~^ ~} prints all values of a list, space-delimited, no trailing space
    • ~:[NO~;YES~] prints first part for 0/NIL, second for 1/T
  • (terpri), (fresh-line) ;; (newline), newline only if not at column 0
  • (prin1 X), (prin1-to-string X) ;; (write X)
  • (princ X), (princ-to-string X) ;; (display X) (display #\space)
  • (print X) ;; (newline) (display X) (display #\space)
  • (read {STREAM EOFVALUE}), (read-line {STREAM EOFVALUE}), (read-char {STREAM EOFVALUE}) ;; if EOFVALUE then returns that instead of erroring on EOF
  • (read-sequence SEQ STREAM {:start START} {:end END}) ;; returns bytes read. get-bytevector-n!
  • (write X :escape T :stream STREAM), (write-char C {STREAM}), (write-byte X {STREAM}) ;; write, write-char, put-u8
  • (write-sequence SEQ STREAM {:start START} {:end END}) ;; put-bytevector

All of the print commands suck, they add extra noise, there is no pure display, and they don't flush their buffers. print puts newline first! WTF. So:

    (defun fprint (port ls end)
        (assert (or (eq port T) (streamp port)))
        ;; ~:A prints () for nil
        (format port "~{~:A~}~A" (if (listp ls) ls (list ls)) end)
        (finish-output port)
    )
    (defun fpr (port &rest ls) (fprint port ls ""))
    (defun fprln (port &rest ls) (fprint port ls #\newline))
    (defun pr (&rest ls) (fprint T ls ""))
    (defun prln (&rest ls) (fprint T ls #\newline))
    (defparameter a 69)
    (defparameter b 3.14)
    (prln "a=" a ", b=" 3.14)
    a=69, b=3.14
  • (close STREAM)
  • (open FILESPEC {:direction DIR} {:element-type ELTYPE} {:if-exists IFEX} {:if-does-not-exist IFNEX}) ;; returns port
  • (with-open-file (VARNAME FILESPEC {:direction DIR} {:element-type ELTYPE} {:if-exists IFEX} {:if-does-not-exist IFNEX}) BODY) ;; overengineered open wrapper
    • VARNAME is dynamically assigned, so you can do *standard-output* and it'll capture all printing until BODY ends
    • DIR is :input (default), :output, :io, :probe
    • ELTYPE is 'character or subtype, 'integer, '(signed-byte 8), '(unsigned-byte 8), :default (character)
    • IFEX is :error, :new-version, :rename, :rename-and-delete, :overwrite, :append, :supersede, nil (default)
    • IFNEX is :error, :create, nil (default varies by DIR! UGH!)
  • (with-input-from-string (VARNAME S) BODY)

  • (with-output-to-string (VARNAME) BODY) ;; returns output string

  • (sb-ext:run-program PROGRAM ARGS …) ;; system or process in Scheme, tho not standard, most every impl has it.

    • LOL calls this ext:shell, SBCL docs good grief.
  • (pathname X) ;; creates path from string, port, etc., #p"FOO" literal; Scheme paths are just strings (possibly not UTF-8)

  • (pathname-directory P), (pathname-name P), (pathname-type P)
  • (namestring P), (directory-namestring P), (file-namestring P) ;; file-namestring is name & ext
  • (make-pathname {:device WINDOWSHIT} :directory DIRS :name NAME :type EXT {:defaults P})
    • DIRS is '(:absolute DIRS), '(:relative DIRS)
    • defaults extracts missing parts from another pathname
    • WARNING: dirs must be listed in dirs, not file name. #p"/foo/bar" is dir foo, name bar.
  • (merge-pathnames AP BP) ;; fills in AP with BP defaults, uses *DEFAULT-PATHNAME-DEFAULTS*
  • (probe-file P) ;; file-exists?
  • (directory P) ;; chezscheme directory-list
  • (ensure-directories-exist P) ;; chezscheme mkdir
  • (delete-file P), (rename-file P Q) ;; delete-file, chezscheme rename-file
EOF