(updated 2024-12-23)
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
- Land of Lisp - best comic book/music video on paren-based-programming ever.
- Practical Common Lisp
- SBCL Manual
- Common Lisp Hyperspec
- UIOP libraries
- format specifiers
- usable format specifiers cheatsheet!
- CL Cookbook
- Tutorialspoint Lisp Tutorial
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 lisp
:
#!/bin/zsh
if [[ $# -eq 0 ]]; then
# just use the thing
rlwrap sbcl --noinform
elif [[ "$1" == "--" ]]; then
# pass arguments to sbcl
shift
rlwrap sbcl --noinform "$@"
elif [[ $# -lt 2 ]]; then
# -? or whatever
echo "Usage: lisp -- [ARGS] || FILENAME EVAL [ARGS]"
exit 1
else
# load filename, eval command, like foo.lisp '(main)'
filename=$1
shift
cmd=$1
shift
# unlike script, allow userinit, sysinit, debugger
rlwrap sbcl --noinform --end-runtime-options --load $filename --eval $cmd --quit --end-toplevel-options "$@"
fi
But for a standalone program, I use this script, which calls the program, but leaves the debugger active, lets me load it from REPL without launching it:
rlwrap sbcl --noinform --end-runtime-options --no-sysinit --no-userinit --load WHATEVER.LISP --eval "(main)" --end-toplevel-options "$@"
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.
Help
- (apropos "TEXT") ;; find TEXT in all known function names/docstrings
- (documentation #'FUNCNAME T) ;; docstring for a function
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*)
To update Quicklisp, use:
(ql:update-client)
(ql:update-dist "quicklisp")
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
- (block NAME BODY) ;;
call/cc
but can't do time/space travel- (return-from NAME VALUE) ;; exit block. In a function, it has bare function name.
- (return { VALUE }) ;; same as (return-from NIL VALUE)
- (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
/namedlet
otherwise. - (flet ( (FUNCNAME (X...) FUNCBODY)... ) BODY) ;;
letrec
- (if TEST THEN ELSE)
- (labels ( (FUNCNAME (X...) FUNCBODY)... ) BODY) ;;
letrec
* - (loop CLAUSE... do BODY) ;; loops until
(return X)
, like a loop insidecall/cc
. Schemers would just write a named let and be done with it. CLAUSES are:- while COND, until COND ;; test COND to terminate
- when COND ;; skips elements when COND is true
- 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
- across VEC ;; over vector
- collecting X ;; push X into list, return value
- summing X ;; add X to total, return value
- finally EXPR ;; perform EXPR at end, often (return X)
- (progn BODY) ;;
begin
- (return-from FUNCNAME VALUE) ;; early return,
(call/cc (lambda (return) ... (return value)))
- (tagbody { TAG|BODY }...) ;; idiocy, randomly interspersed "tag" symbol/int can be reached with (go TAG). Use
labels
instead. - (when TEST BODY), (unless TEST BODY)
(defun early-return (x)
(when (minusp x)
(return-from early-return (- x)))
(prln "x:" x) x
)
(early-return 1) ;; prints x:1, returns 1
(early-return -3) ;; no print, returns 3
(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
- (setf (values VAR...) VALUES) ;; multiple values
- (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 - (values N...), (values-list LS) ;; values
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 - (random N) ;;
random
, 0..N-1 - (setf *random-state* (make-random-state T)) ;;
random-seed
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)
- (code-char C), (char-code N) ;;
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 :junk-allowed T) ;;
number->string
,string->number
, returns NIL on non-string
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
, inverseevery
,any
- (find VALUE SEQ ), (find-if #'FUNCNAME SEQ), (find-if-not #'FUNCNAME SEQ) ;;
find
,exists
, inverseexists
- (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) ;; mutating 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)
, SRFI-32/132(vector-sort! proc SEQ)
- (subseq SEQ X {Y}) ;;
substring
, SRFI-1(take (drop v X) (- Y X))
, SRFI-43(vector-copy SEQ X Y)
- (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 T ;; reverse order
- :count N ;; only N elements removed/subst'd
Lists
- (append LS ...), (reverse LS)
- (nconc LS ...), (nreverse LS) ;; mutating,
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 mutating - (maplist #'FUNCNAME LS), mapcon ;;
map
, FUNC gets pair, not car. mapcon is mutating - (member X LS :test #'equal), (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)
- ARGS can be as any function, or "destructuring", paren prototypes:
- (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))
OS Integration
These are not usefully specified in Common Lisp, which was built for Lisp Machines rather than Unix or that other thing. The QuickLisp/ASDF/UIOP "EIEIO" libraries collect most but not all of these in a single interface.
- (uiop:command-line-arguments) ;;
command-line-arguments
, see my Old Man in the Woods Way of Argument Parsing for my preferred way to read them. - (uiop:architecture) ;; (values :X64 :X86-64), chezscheme
machine-type
- (uiop:chdir DIR) ;; chezscheme
chdir
- (uiop:detect-os) ;; :OS-MACOSX
- (uiop:getcwd) ;; #P"/Users/mdh/Code/CodeLisp/"
- (uiop:getenv "HOME") ;; "/Users/mdh"
- (setf (uiop:setenv "FOO") VALUE) ;; chezscheme
putenv
- (uiop:hostname) ;; "Aegura.local"
- (uiop:implementation-type) ;; (values :SBCL :SBCL)
- (uiop:operating-system) ;; (values :MACOSX :MACOSX)
-
(uiop:run-program COMMAND ARGS...) ;;
system
orprocess
in Scheme, tho not standard, most every impl has it.- COMMAND can be string or list of strings
- ARGS are :ignore-error-status T or NIL
- :force-shell T or NIL
- :output :string || :interactive || T (stdout) || NIL (/dev/null) || filename
- :input :interactive || T (stdin) || NIL (/dev/null) || filename
- :error-output (as output)
- SBCL: (sb-ext:run-program PROGRAM ARGS …) ;; SBCL docs good grief.
- CLISP: ext:shell
- (sb-ext:exit :code RC) ;; chezscheme
exit
, SBCL-specific - (sb-posix:getpid) ;; process ID, SBCL-specific
- (get-universal-time) ;; time since 1900
Input/Output
Common Lisp calls a port a "stream".
- (finish-output {STREAM}) ;;
flush-output-port
- (format PORT PATTERN ARG...)
- PORT = T for stdout, NIL for string, else port/stream.
~(~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) or
integer->string
- (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
-
(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})
- name, type can be :wild for wildcard
- 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
, chezschemerename-file
- (user-homedir-pathname)
Peter Siebel makes paths & directories out to be a big cross-platform mess, which it probably is, but if you just use sbcl, it's verbose but tidy enough:
(defun directory-list (d)
(directory (make-pathname :directory (pathname-directory d) :name :wild :type :wild))
)
(loop for d in (directory-list ".") do
(if (pathname-name d)
(prln "FILE " (directory-namestring d) " : " (file-namestring d))
(prln "DIR " (directory-namestring d))
))
CLOS
Object System.
Common Lispers think "GF" means "Generic Function", they've never had girlfriends.
Base class is T, but not the same namespace as 'T which is true. User classes extend STANDARD-OBJECT.
- (defgeneric METHOD ((OBJ CLASS) ARGS...) (:documentation DOCS) ) ;; declares a GF, who lives in Canada, but doesn't actually exist/do anything.
- (defmethod METHOD { AUX... } ((OBJ CLASS) ARGS...) BODY) ;; implements METHOD for specific class
- CLASS can instead be (EQL SOMEOBJ), SOMEOBJ is evaluated at compile time
- AUX can be :before ARGS, :after ARGS ;; pre-, post- conditions
- AUX can be :around ARGS ;; wrapper, must (call-next-method)
- (call-next-method { ARGS... }) ;; super.method, call at end of method
- (defclass CLASS { (SUPERCLASS ...) } (SLOT...) ) ;; define a new class
- SLOT can be NAME, or (NAME :initarg :KEY { :initform DEFAULT } { :reader GETNAME } { :writer (setf SETNAME) } { :accessor GETSETNAME } )
:allocation :class
in slot makes it static (-ish.)- (defmethod initialize-instance :after ((OBJ CLASS) &key) BODY) ;; post-init setup
- (make-instance 'CLASS) ;; creates an instance, weirdly name is a symbol
- (slot-value OBJ 'SLOT) ;; accessor, setf to write
- (defmethod METHOD ((OBJ CLASS)) (slot-value OBJ 'SLOT)) ;; primitive getter
- (defmethod (setf METHOD) (VARNAME (OBJ CLASS)) (setf (slot-value OBJ 'SLOT) VARNAME)) ;; primitive setter
- but really just use
:accessor
in defclass, and then(foo OBJ)
and(setf (foo OBJ) X)
work. As in Scheme records, I prefer to put a prefix on all accessors, so a Player might have all player- or pl- methods.
- (with-slots (SLOT ...) OBJ BODY), with-accessors ;; treat slots as local variables
- SLOT can be (NAME ACTUALNAME)
- (defmethod initialize-instance :after ((OBJ CLASS) &key) BODY) ;; finish constructor, after :initarg.
Conditions
Most of this is just longing for GOTO by savages who don't understand structured programming and wouldn't like it if they did. There's no use for "restarts" that doesn't look like INTERCAL's "COME FROM" instruction.
- (define-condition CONDNAME (error) ( { SLOT... } )) ;; creates a condition type
- SLOT must be (NAME :initarg :KEY { :initform DEFAULT } :reader SLOTNAME)
- (error 'CONDNAME { ARGS... }) ;; make-instance of condition & raises it, Scheme: (error 'FUNC TEXT ARG...) or (raise (condition (make-CONDNAME) (make-message-condition msg)))
- (warn 'CONDNAME { ARGS... }) ;; make-instance of condition & raises it, but if handler returns, just prints message to *error-output*.
- (handler-case (progn BODY) { (CONDNAME (e) (recover e)) ... } ) ;; Scheme: (guard (ex [(CONDTEST? ex) ERRBODY]) BODY)
- (unwind-protect (progn BODY) AFTERBODY) ;;
dynamic-wind
but only has after, not before.
McCLIM
Common Lisp Interface Manager, generic GUI toolkit. Manual
On MacOS, run XQuartz (/Applications/Utilities/XQuartz.app) first, before starting Lisp. Start an xeyes and put it somewhere so you can find your cursor, and see that X11 is still running.
Similar to the sample application, with a big view frame up top, smaller command frame below. Each verb to be added will be given to the inspector, and output collected to be displayed.
got up to
https://mcclim.common-lisp.dev/static/manual/mcclim.html#Using-incremental-redisplay