How to use SBCL?

  1. To run a .lisp or .lsp file:

    sbcl --script <filename>


  2. To load a .lisp or .lsp file:

    sbcl --load <filename>


  3. To load a .lisp or .lsp file inside the SBCL prompt:

    * (load "hello.lisp")


  4. To quit inside the SBCL prompt:

    * (quit)
    * (sb-ext:quit)



Hello World in Common Lisp

  1. Genre 1:

    (write-line "Hello World!")


  2. Genre 2:
    (defun hello-world()
        (format t "Hello World!"))
    
    (hello-world)
    



Lisp Uses Prefix Notation

  1. In prefix notation, operators are written before their operands.
  2. a * (b + c) / d
    (/ (* a (+ b c)) d)
    



Basic Building Blocks in Lisp

  1. Lisp programs are made of three basic building blocks.



  2. An atom is a number or a string of contiguous characters.
  3. hello-from-lisp
    12300009
    *hello*
    block#123
    abc123
    


  4. A list is a sequence of atoms and other lists enclosed in parentheses.
  5. (this is a list)
    (a (a b c) d e f)
    (Sun Mon Tue Wed Thu Fri Sat)
    ( )
    


  6. A string is a group of characters enclosed in double quotation mark ( " )
  7. "here is a string"
    "hello"
    "Please enter a number:"
    " "
    



Comments

  1. The semicolon ; indicates a line-comment.



Variables

  1. Global variables are generally declared using the DEFVAR construct.
  2. ; Define a global variable x with a value of `100`
    (defvar x 100)
    ; Print the value of `x`
    (print x)
    


  3. If there is no type declaration for variables in Lisp, you can directly specify a value for a symbol with the SETQ construct.


  4. There are two constructs: LET and PROG (no longer commonly used) for creating local variables.


  5. The LET construct has the following syntax.
    If you did NOT include an initial value for a variable, it is assigned NIL.
  6. (let ((var-1 val-1) (var-2 val-2) ... (var-n val-n))
      <s-expression>
      <s-expression>
      ...)
    


  7. The PROG construct has the following syntax.
  8. (prog (var-1 var-2 ... var-n)
      <s-expression>
      <s-expression>
      ...)
    


  9. Common Lisp supports variable shadowing.


  10. Common Lisp provides two ways to create global variables: DEFVAR and DEFPARAMETER.
    Both forms take a variable name, an initial value, and an optional documentation string.


  11. Global variables are conventionally named with names that start and end with * (e.g., *db*).
  12. (defvar *count* 0
      "Count of widgets made so far.")
    
    (defparameter *gap-tolerance* 0.001
      "Tolerance to be allowed in widget gaps.")
    


  13. DEFCONSTANT defines a named global constant.
  14. (sbcl) (defconstant +pi+ 3.1415926 "Approximation of PI")
    (sbcl) +pi+
        3.1415926
    


  15. SETF is the general-purpose assignment operator in Common Lisp.
    It is used to set or update the value of variables, places (like array elements, object fields, etc.), and more.

    (setf place value)


  16. SETF can also assign to multiple places in sequence.
  17. (setf x 1)
    (setf y 1)
    
    (setf x 1 y 2)
    


  18. SETF returns the newly assigned value,
    so you can also nest calls to SETF as in the following expression, which assigns both x and y the same random value: (setf x (setf y (random 10)))


  19. You could increment / decrement a number with SETF:
  20. (setf x (+ x 1));   (incf x)
    (setf x (+ x 10));  (incf x 10)
    (setf x (- x 1));   (decf x)
    


  21. ROTATEF: swaps values in-place by rotating them left-wise, returns NIL.
    NOTE: All places (variables, array elements, etc.) must be writable with SETF.
  22. (rotatef <place1> <place2> ... <placeN>)
    
    place1 <- place2
    place2 <- place3
    ...
    placeN <- original place1
    
    (let ((a 1) (b 2) (c 3))
      (rotatef a b c)
      (list a b c))
    
    (2 3 1)
    


  23. SHIFTF shifts values left-wise and returns the original first value.
  24. (shiftf <place1> <place2> ... <placeN> <new-value>)
    
    place1 <- place2
    place2 <- place3
    ...
    placeN <- new-value
    return <- original place1
    
    (let ((a 1) (b 2) (c 3))
      (shiftf a b c 100))       ;; returns 1
    



Difference between LET and LET*

  1. LET: All variables are initialized in parallel.


  2. LET*: Variables are initialized one by one in sequence, left to right, and each one can use the previous ones.
  3. (let* ((a 2)
           (b (+ a 3))      ; b = 2 + 3 = 5
           (c (* b 4)))     ; c = 5 * 4 = 20
      (list a b c))         ; (2 5 20)
    



Difference between DEFVAR and DEFPARAMETER

  1. DEFVAR: re-decl does not overwrite an existing value (can be later changed with assignment).
  2. (sbcl) (defvar *x* 10)
    (sbcl) (defvar *x* 20)
    (sbcl) *x*
        10
    


  3. DEFPARAMETER: re-decl always resets the value.
  4. (sbcl) (defparameter *x* 10)
    (sbcl) (defparameter *x* 20)
    (sbcl) *x*
        20
    



Escape Character

  1. A backslash ( \ ) escapes the next character, causing it to be included in the string regardless of what it is.
  2. "foo"       ; foo
    "f\oo"      ; foo,  because `\o` escapes `o`, treating it iterally like the character `o`.
    "fo\\o"     ; fo\o
    "fo\'o"     ; fo'o
    "fo\"o"     ; fo"o
    


Basics about Symbol

  1. There are 10 characters that serve other syntactic purposes can NOT appear in names:


  2. If you really want to use those character, try to escape them with a backslash ( \ )
    or surround the part of the name containing characters that need escaping with vertical bars ( | ).
  3. 
        (defun test\,-lisp ()
          (write-line "Hello, world!"))
        (test\,-lisp)
    
        (defun |test,-lisp| ()
          (write-line "Hello, world!"))
        (|test,-lisp|)
    
        (defun | test,-lisp | ()
          (write-line "Hello, world!"))
        (| test,-lisp |)
    


  4. NOTE: The symbol names are case-insensitive, it converts all unescaped characters to upper case, like foo, Foo, and FOO are the same.
    However, the f\o\o and |foo| will preserve the case, they are read as foo.



Keyword Symbols

  1. Keyword symbols are prefixed with a colon (e.g., :name, :id).

    This prefix automatically makes them part of the KEYWORD package.


  2. Unlike regular symbols, keyword symbols evaluate to themselves.
  3. > :example
    :EXAMPLE
    
    > :EXample
    :EXAMPLE
    
    > :\example
    :|eXAMPLE|
    
    > :a\,b
    :|A,B|
    
    > :123
    :|123|
    
    > :123abc
    :123ABC
    
    > :abc123
    :ABC123
    
    > :|xyz|
    :|xyz|
    


  4. Keyword symbols are often used as keys in property list.
  5. > (setq person '(:name "Alice" :age 20))
    > (getf person :name)
    "Alice"
    ; Btw, (setq person (:name "Alice" :age 20)) is invalid, because Lisp will tru to eval as if :name were a function.
    ; You can also use (setq person (list :name "Alice" :age 20)) instead.
    


  6. Many libraries use keyword symbols for configuration settings.
  7. (open "settings.conf", :direction :output)



if Statement

  1. Syntax: (if <cond> <then> [<else>])



  2. Basic Example:
  3. (if (> 10 5)
      (write-line "10 > 5")
      (write-line "10 <= 5"))
    

  4. Without else expression:
  5. (if (= 1 1) (write-line "1 equals 1"))


  6. Nested if:
  7. (if (> 10 5)
      (if (< 3 4)
        (write-line "10 > 5 and 3 < 4")
        (write-line "10 > 5 and 3 >= 4"))
      (write-line "10 <= 5"))
    


  8. The if expression returns the result of the evaluated then or else form.
  9. (let ((x 10))
      (if (> x 5) (+ x 10) (- x 10)))
    


Basics about quote

  1. It is used to prevent an expression from being evaluated.


  2. Syntax: (quote <expr>) or shorthandly '<expr>


  3. Example Usage:
  4. > (quote (+ 1 2))
    (+ 1 2)
    > '(+ 1 2)
    (+ 1 2)
    > (+ 1 2)
    3
    
    > 'a
    A
    > '\a
    |a|
    
    
    > (setq a 100)
    100
    > a
    100
    > 'a
    A
    > (symbol-value 'a)
    100
    
    
    > (setq a 'b)   ; a holds the symbol B
    B
    > (set a 100)   ; same as (set 'b 100)
    100
    > b
    100
    


  5. (setq a 100) and (setq 'a 100) are NOT the same (SETQ expects an unquoted symbol in the variable position).


  6. If you want to assign to a variable by a symbol at runtime, use the symbol's value cell: (setf (symbol-value 'a) 100) or (set 'a 100)


  7. 'a is a symbol ONLY when evaluated, normally it is treated as an quoted expression (quote A).


  8. Quick contrasts:



True, False and Equality

  1. The symbol t or T is conventionally treated as true in Common Lisp.

    (if t "True" "False") ; returns "True"


  2. The expressions nil, 'nil, () and '() are considered false in Common Lisp.

    (if nil "T" "F") ; returns "F"
    (if () "T" "F") ; returns "F"


  3. EQ checks whether two values are literally the same object: the same address, same identity.
  4. (eq 1000 1000)   ;; might be NIL on some Lisps
    (eq 'foo 'foo)   ;; always T (same interned symbol)
    


  5. EQL is just like EQ, but slightly stronger: it also considers numbers and characters with the same value as equal.
  6. (eql 1000 1000)  ;; always T
    (eql 1.0 1)      ;; NIL (different types)
    (eql #\A #\A)    ;; T
    


  7. EQUAL compares structural lists and strings (and bit-vectors).
  8. (equal '(a (b)) '(a (b)))   ;; T
    (equal "Foo" "Foo")         ;; T
    (equal "Foo" "foo")         ;; NIL (case-sensitive)
    (equal 1 1.0)               ;; NIL (numbers must be EQL)
    (equal #\A #\a)             ;; NIL
    


  9. EQUALP is more forgiving: case-insensitive for strings and characters, and value comparison for numbers.
  10. (equalp "Foo" "foo")        ;; T
    (equalp #\A #\a)            ;; T
    (equalp 1 1.0)              ;; T
    (equalp '(1 "A") #(1 "a"))  ;; T (list vs vector ok; string case ignored)
    



Basics about cond

  1. cond is a versatile conditional construcy used for multi-branch descision-making. It is preferred over nested if.


  2. Syntax:
  3. (cond
      (<cond-1> <form-1-1> <form-1-2> ...)
      (<cond-2> <form-2-1> <form-2-2> ...)
      ...
      (t <default-form-1> <default-form-2> ...))
    


  4. Example Usage:
  5. (defun categorize-number (x)
      (cond
        ((< x 0) "negative")
        ((> x 0) "positive")
        ((= x 0) "zero")))
    
    (categorize-number 10)
    (categorize-number -7)
    (categorize-number 0)
    
    (defun analyze-number (x)
      (cond
        ((< x 0) (format t "~a < 0~%" x) "negative")
        ((> x 0) (format t "~a > 0~%" x) "positive")
        ((= x 0) (format t "x = 0~%") "zero")))
    
    (analyze-number -3)
    ; it will "-3 < 0" and return "negative"
    



Basics about Functions

  1. Defining functions with DEFUN

  2. (defun <function-name> (<parameter-list>)
      "Optional documentation string."
      <function-body>)
    

    (defun verbose-sum (x y)
      "Sum two numbers after printing a message."
      (format t "Summing ~D and ~D.~%" x y)
      (+ x y))
    

    (verbose-sum 2 3)
    ;; Prints: Summing 2 and 3.
    ;; Returns: 5
    


  3. Documentation strings

  4. (documentation 'verbose-sum 'function)
    ;; => "Sum two numbers after printing a message."
    


  5. Required parameters

  6. (defun add-two (a b)
      (+ a b))
    
    (add-two 3 4)  ; => 7
    (add-two 3)    ; => Error: too few arguments
    


  7. Optional parameters (&optional)

  8. (defun foo (a b &optional c d)
      (list a b c d))
    
    (foo 1 2)      ; => (1 2 NIL NIL)
    (foo 1 2 3)    ; => (1 2 3 NIL)
    (foo 1 2 3 4)  ; => (1 2 3 4)
    

    (defun bar (a &optional (b 10) (c 20 c-supplied-p))
      (list a b c c-supplied-p))
    
    (bar 1)        ; => (1 10 20 NIL)
    (bar 1 2)      ; => (1 2 20 NIL)
    (bar 1 2 30)   ; => (1 2 30 T)
    

    (defun make-rectangle (width &optional (height width))
      (list :width width :height height))
    
    (make-rectangle 10)   ; => (:WIDTH 10 :HEIGHT 10)
    (make-rectangle 10 5) ; => (:WIDTH 10 :HEIGHT 5)
    


  9. Rest parameters (&rest)

  10. (defun sum (&rest nums)
      (reduce #'+ nums :initial-value 0))
    
    (sum)             ; => 0
    (sum 1 2 3 4 5)   ; => 15
    



  11. Keyword parameters (&key)

  12. (defun configure (&key a b c)
      (list a b c))
    
    (configure)                ; => (NIL NIL NIL)
    (configure :a 1)           ; => (1 NIL NIL)
    (configure :b 2)           ; => (NIL 2 NIL)
    (configure :a 1 :c 3)      ; => (1 NIL 3)
    

    (defun foo (&key (a 0) (b 0 b-supplied-p) (c (+ a b)))
      (list a b c b-supplied-p))
    
    (foo)                ; => (0 0 0 NIL)
    (foo :a 1)           ; => (1 0 1 NIL)
    (foo :b 1)           ; => (0 1 1 T)
    (foo :a 2 :b 1 :c 4) ; => (2 1 4 T)
    

    (defun fruit (&key ((:apple a)) ((:banana b) 0) ((:cherry c) 0 c-supplied-p))
      (list a b c c-supplied-p))
    
    (fruit :apple 10 :banana 20 :cherry 30)
    ;; => (10 20 30 T)
    


  13. Combining &rest and &key

  14. (defun foo (&rest args &key a b c)
      (list args a b c))
    
    (foo :a 1 :b 2 :c 3)
    ;; => ((:A 1 :B 2 :C 3) 1 2 3)
    


  15. Returning values

  16. (defun check (x)
      (if (minusp x)
          (return-from check "negative")
          "non-negative"))
    
    (check 5)   ; => "non-negative"
    (check -2)  ; => "negative"
    



  17. Local functions: FLET and LABELS

  18. (defun example (n)
      (labels ((square (x) (* x x))
               (sum-up (m) (if (zerop m) 0 (+ (square m) (sum-up (1- m))))))
        (sum-up n)))
    
    (example 3) ; => 14  (1² + 2² + 3²)
    


  19. Inspecting and redefining functions

  20. (symbol-function 'verbose-sum)
    ;; => #<FUNCTION VERBOSE-SUM>
    

    (setf (documentation 'verbose-sum 'function)
          "Add two numbers and print a friendly message.")
    



  21. Functions vs variables: separate namespaces

  22. (defun foo (x) (+ x 1))
    (setq foo 42)
    
    foo        ; => 42       (variable)
    (foo 10)   ; => 11       (function)
    


  23. Pure vs impure functions

  24. (defun pure-add (x y) (+ x y))
    
    (defvar *count* 0)
    (defun impure-add (x y) (incf *count*) (+ x y))
    



Function Return Values

  1. Returning from a function

  2. (defun absolute-value (x)
      (if (minusp x)
          (return-from absolute-value (- x))
          x))
    
    (absolute-value -10) ; => 10
    (absolute-value  10) ; => 10
    


  3. RETURN-FROM and BLOCK

  4. (block my-block
      (format t "Before~%")
      (return-from my-block 42)
      (format t "After~%")) ; never executed
    ;; => 42
    



  5. How DEFUN uses BLOCK

  6. (defun first-positive (xs)
      (dolist (x xs)
        (when (plusp x)
          (return-from first-positive x)))
      nil)
    
    (first-positive '(-3 -2 0 4 -1))
    ;; => 4
    



  7. The RETURN shorthand

  8. (dolist (x '(3 2 1 0 -1))
      (when (zerop x)
        (return 'done))
      (format t "x=~A~%" x))
    ;; Prints:
    ;; x=3
    ;; x=2
    ;; x=1
    ;; => DONE
    



  9. RETURN-FROM vs RETURN

  10. Form Returns from Typical use
    (return-from name value) Explicitly named block (or function body) Used in defun or custom block
    (return value) Nearest implicit block (like dolist, do, etc.) Quick exit inside iteration


  11. Early exits in complex logic

  12. (defun safe-divide (a b)
      (if (zerop b)
          (return-from safe-divide :divide-by-zero)
          (/ a b)))
    
    (safe-divide 10 2) ; => 5
    (safe-divide 10 0) ; => :DIVIDE-BY-ZERO
    


  13. Multiple values and RETURN-FROM

  14. (defun divide-with-remainder (a b)
      (if (zerop b)
          (return-from divide-with-remainder (values nil nil))
          (return-from divide-with-remainder (values (floor (/ a b)) (mod a b)))))
    
    (multiple-value-bind (q r) (divide-with-remainder 10 3)
      (list q r))
    ;; => (3 1)
    



Functions as Data (Higher-Order Functions)

  1. Functions are first-class values

  2. (defun foo (x) (* 2 x))
    
    (function foo)
    ;; => #<FUNCTION FOO>
    
    #'foo
    ;; => #<FUNCTION FOO>
    




  3. Calling functions dynamically: FUNCALL

  4. (defun add3 (a b c)
      (+ a b c))
    
    (funcall #'add3 1 2 3)
    ;; => 6
    

    (defun apply-twice (fn x)
      (funcall fn (funcall fn x)))
    
    (apply-twice #'1+ 10)
    ;; => 12
    


  5. Variable-function application: APPLY

  6. (apply #'+ 1 2 '(3 4 5))
    ;; Equivalent to: (+ 1 2 3 4 5)
    ;; => 15
    
    (apply #'max '(1 9 3 5 7))
    ;; => 9
    



  7. Example: ASCII plotter using FUNCALL

  8. (defun plot (fn min max step)
      (loop for i from min to max by step do
        (loop repeat (funcall fn i) do (format t "*"))
        (format t "~%")))
    
    (plot #'exp 0 4 0.5)
    *
    *
    **
    ****
    *******
    ************
    ********************
    *********************************
    ******************************************************
    



  9. Combining lists with REDUCE

  10. (reduce #'+ '(1 2 3 4) :initial-value 0)
    ;; => (+ (+ (+ (+ 0 1) 2) 3) 4)
    ;; => 10
    
    (reduce #'max '(1 4 2 9 3))
    ;; => 9
    



  11. Anonymous functions with LAMBDA

  12. (funcall #'(lambda (x y) (+ x y)) 3 4)
    ;; => 7
    
    (apply #'(lambda (&rest xs) (reduce #'+ xs)) '(1 2 3 4))
    ;; => 10
    

    (mapcar #'(lambda (x) (* x x)) '(1 2 3 4))
    ;; => (1 4 9 16)
    


  13. Closures: functions that capture variables

  14. (defun make-counter (&optional (start 0))
      (let ((n start))
        #'(lambda ()
            (incf n))))
    
    (let ((next (make-counter 10)))
      (list (funcall next)
            (funcall next)
            (funcall next)))
    ;; => (11 12 13)
    



  15. Functions as arguments and return values

  16. (defun make-adder (n)
      #'(lambda (x) (+ x n)))
    
    (setq add5 (make-adder 5))
    (funcall add5 10)
    ;; => 15
    



  17. Mapping functions over lists

  18. (mapcar #'1+ '(1 2 3 4))                    ; => (2 3 4 5)
    (mapcar #'(lambda (x) (* x 10)) '(1 2 3))   ; => (10 20 30)
    (mapcar #'+ '(1 2 3) '(10 20 30))           ; => (11 22 33)
    



  19. Summary



The difference between (3 4 5) and '(3 4 5)

  1. (3 4 5) is a function call.

    In Lisp, anything inside parentheses is treated as a function call unless you explicitly prevent evaluation.



  2. '(3 4 5) is a quoted list: a literal value.

    The single quote ( ' ) is shorthand for (quote ...).



Macro

  1. What is a macro?



  2. Basic DEFMACRO syntax

  3. (defmacro <macro-name> (<lambda-list>)
      "Optional documentation string."
      <body-forms...>)
    



  4. Macro parameters and &body

  5. (defmacro my-when (test &body body)
      "If TEST is true, execute BODY like (progn ...)."
      ...)
    



  6. Backquote, comma, and comma-at


  7. Backquote Syntax Equivalent List-Building Code Result
    `(a (+ 1 2) c) (list 'a '(+ 1 2) 'c) (a (+ 1 2) c)
    `(a ,(+ 1 2) c) (list 'a (+ 1 2) 'c) (a 3 c)
    `(a (list 1 2) c) (list 'a '(list 1 2) 'c) (a (list 1 2) c)
    `(a ,(list 1 2) c) (list 'a (list 1 2) 'c) (a (1 2) c)
    `(a ,@(list 1 2) c) (append (list 'a) (list 1 2) (list 'c)) (a 1 2 c)


  8. Full DEFMACRO form

  9. General syntax (simplified):

    (defmacro macro-name (lambda-list
                           &optional doc-string
                           &rest body)
      "doc-string"
      ;; declarations (optional)
      ;; body must compute and return code
      ...)
    



  10. A simple macro: MY-WHEN

  11. (defmacro my-when (test &body body)
      "If TEST is true, execute BODY like (progn ...)."
      `(if ,test
           (progn ,@body)))
    
    (my-when (> x 10)
      (print "positive")
      (incf x))
    

    (if (> x 10)
        (progn
          (print "positive")
          (incf x)))
    



  12. Inspecting macro expansion

  13. (macroexpand-1 '(my-when (> x 10)
                      (print "positive")
                      (incf x)))
    ;; => (IF (> X 10)
    ;;        (PROGN (PRINT "positive") (INCF X)))
    ;;    T
    



  14. More advanced examples

  15. Example 1: macro with keyword options trailing after body.

    (defmacro echo-times (&body body &key (times 1) (prefix "=> "))
      ;; Remove trailing keyword/value pairs from BODY so we only keep real forms.
      (let* ((rev (reverse body))
             (pure-rev
               (loop with lst = rev
                     ;; While the reversed list starts with a keyword/value pair,
                     ;; drop those two cells.
                     while (and (consp lst) (consp (cdr lst)) (keywordp (car lst)))
                     do (setf lst (cddr lst))
                     finally (return lst)))
             (pure-body (reverse pure-rev)))
        `(dotimes (i ,times)
           (format t "~A" ,prefix)
           (progn ,@pure-body))))
    
    (echo-times
      (format t "Hello~%")
      (format t "World~%")
      :times 2
      :prefix "[*] ")
    


    Example 2: macro with a keyword argument list grouped in one parameter.

    (defmacro with-prefix ((&key (prefix "=> ") (times 1)) &body body)
      `(dotimes (i ,times)
         (format t "~A" ,prefix)
         (progn ,@body)))
    
    (with-prefix (:prefix "[*] " :times 2)
      (format t "Hello~%")
      (format t "World~%"))
    



  16. Macro vs function

  17. Aspect Function Macro
    Arguments Evaluated before call Passed as raw code (unevaluated forms)
    Runs at Runtime Compile-time / macro-expansion-time
    Returns Final value A form (code) that will later be evaluated
    Use when You just need computation You need to change syntax or control evaluation



  18. Common pitfalls: variable capture and GENSYM

  19. (defmacro with-temp ((var value) &body body)
      (let ((tmp (gensym "TMP-")))
        `(let ((,tmp ,value))
           (let ((,var ,tmp))
             ,@body))))
    



  20. The declaration part of DEFMACRO

  21. (defmacro example (x)
      "Example macro with declaration."
      (declare (ignorable x)) ; tell the compiler it's okay if X is unused
      `(list ,x))
    



  22. Summary



Destructured Keyword and Parameter Lists in Macros: Clean DSL Design

  1. Introduction



  2. Why destructured parameters?

  3. (defmacro naive-prefix (&body body)
      ;; manual keyword cleanup required...
      ...)
    

    (defmacro with-prefix ((&key (prefix "=> ") (times 1)) &body body)
      `(dotimes (i ,times)
         (format t "~A" ,prefix)
         (progn ,@body)))
    



  4. Example: keyword-based DSL
  5. (with-prefix (:prefix "[*] " :times 2)
      (format t "Hello~%")
      (format t "World~%"))
    
    ;; =>
    ;; [*] Hello
    ;; [*] World
    ;; [*] Hello
    ;; [*] World
    



  6. Combining destructuring with required and optional parameters

  7. (defmacro styled-print (title
                            (&key (color "green") (times 1) (prefix "=> "))
                            &optional (uppercase nil)
                            &body body)
      "Print TITLE and BODY multiple times with options and optional uppercase."
      `(dotimes (i ,times)
         (format t "~%~A[~A] " ,prefix ,color)
         (format t "~A~%" ,(if uppercase `(string-upcase ,title) title))
         (progn ,@body)))
    



  8. Example usage
  9. (styled-print "Hello Lisp!"
                  (:prefix "[*] " :times 2 :color "cyan")
                  t
      (format t "Nested body here.~%"))
    
    ;; Output:
    ;; [*] [cyan] HELLO LISP!
    ;; Nested body here.
    ;; [*] [cyan] HELLO LISP!
    ;; Nested body here.
    



  10. What happens internally
  11. (macroexpand-1
     '(styled-print "Hi"
                    (:prefix "[*] " :color "red" :times 2)
                    nil
        (format t "Body~%")))
    
    ;; =>
    ;; (DOTIMES (I 2)
    ;;   (FORMAT T "~%~A[~A] " "[*] " "red")
    ;;   (FORMAT T "~A~%" "Hi")
    ;;   (PROGN (FORMAT T "Body~%")))
    



  12. Mixing parameter types more generally

  13. You can also use this structure to build macros that accept:

    (defmacro do-labeled-range ((start end &key (step 1) (label "Range:"))
                                &optional (prefix "=> ")
                                &body body)
      "Iterate from START to END printing LABEL and executing BODY each step."
      `(do ((i ,start (+ i ,step)))
           ((> i ,end) 'done)
         (format t "~A ~A ~A~%" ,prefix ,label i)
         (progn ,@body)))
    



  14. Usage example
  15. (do-labeled-range (1 5 :step 2 :label "Odd numbers:")
                      "[*] "
      (format t "i squared = ~A~%" (* i i)))
    
    ;; Output:
    ;; [*] Odd numbers: 1
    ;; i squared = 1
    ;; [*] Odd numbers: 3
    ;; i squared = 9
    ;; [*] Odd numbers: 5
    ;; i squared = 25
    ;; => DONE
    



  16. Why this design is powerful




'(a b c) VS (list a b c)

  1. They are NOT the same thing!


  2. '(...) is a quoted list (no evaluation).


  3. (list a b c) calls the function list, after evaluating of each argument.


  4. Comparison with a real-life example:
  5. (setq a 10 b 20 c 30)
    (list a b c)            ;; (10 20 30)
    '(a b c)                ;; (A B C)
    



PROGN

  1. PROGN is a special operator in Common Lisp that evaluates multiple expressions in sequence and returns the value of the last one.


  2. Syntax: (progn <expr1> <expr2> ... <exprN>)


  3. Example:
  4. (progn
      (format t "Step 1~%")
      (format t "Step 2~%")
      (+ 2 3))   ;; last expression
    
    ;; Output:
    ;; Step 1
    ;; Step 2
    ;; 5
    



WHEN

  1. WHEN is a simplified IF that only has a then branch (no else).
    It checks a condition, and if the result is true (non-NIL), it evaluates one or more expressions in sequence.
    The return value of WHEN is the result of the last expression in its body, if the condition is false, it returns NIL.

  2. (let ((x 5))
      (when (> x 0)
        (format t "x is positive~%")
        (* x 2)))
    ;; prints: x is positive
    ;; returns: 10
    


  3. Equivalent form: WHEN is essentially shorthand for an IF with an implicit PROGN inside its then branch.
  4. (if (> x 0)
        (progn
          (format t "x is positive~%")
          (* x 2)))


  5. The opposite of WHEN is UNLESS, which executes its body when the condition is false.



UNLESS

  1. UNLESS is the logical opposite of WHEN.
    It evaluates its body only if the test condition is NIL (false).
    The return value of UNLESS is the result of the last expression in its body, if the condition is true, it returns NIL without executing the body.

  2. (let ((x 0))
      (unless (> x 0)
        (format t "x is not positive~%")
        "Did something"))
    ;; prints: x is not positive
    ;; returns: "Did something"
    


  3. Equivalent form: UNLESS is simply shorthand for an IF where the condition is negated and the else branch is omitted.

  4. (if (not (> x 0))
        (progn
          (format t "x is not positive~%")
          "Did something"))



AND, OR, and NOT

  1. AND evaluates the arguments from left to right. (and <expr1> <expr2> ... <exprN>)
    It returns:


  2. OR evaluates the arguments from left to right. (or <expr1> <expr2> ... <exprN>)
    It returns:


  3. NOT returns T if the argument is NIL, and NIL otherwise.


  4. Examples:
  5. (and t 42 "hello")      ;; "hello"
    (and t nil "oops")      ;; NIL
    (and)                   ;; T
    
    (or nil 0 "yes")        ;; 0
    (or nil nil nil)        ;; NIL
    (or)                    ;; NIL
    
    (not nil)               ;; T
    (not t)                 ;; NIL
    (not 42)                ;; NIL (42 is truthy)
    



Basics on DOLIST

  1. Purpose



  2. Syntax

  3. (dolist (<var> <list> &optional <result-form>)
      <body>)
    



  4. Basic example
  5. (dolist (x '(a b c))
      (format t "Element: ~A~%" x))
    ;; Element: A
    ;; Element: B
    ;; Element: C
    ;; => NIL
    



  6. Specifying a result value
  7. (dolist (x '(1 2 3) "Loop Finished")
      (print x))
    ;; 1
    ;; 2
    ;; 3
    ;; => "Loop Finished"
    



  8. Accumulating a result

  9. (let ((sum 0))
      (dolist (x '(1 2 3 4 5) sum)
        (incf sum x)))
    ;; => 15
    



  10. Early exit using RETURN

  11. (dolist (x '(3 -1 4 -2 5))
      (when (minusp x)
        (return (format nil "Found a negative: ~A" x)))
      (format t "Checked: ~A~%" x))
    ;; => "Found a negative: -1"
    



  12. Nesting DOLIST loops

  13. (dolist (row '((1 2 3) (4 5 6)))
      (dolist (x row)
        (format t "~A " x))
      (format t "~%"))
    ;; 1 2 3
    ;; 4 5 6
    



  14. Advanced usage: collecting transformed elements

  15. (let ((result '()))
      (dolist (x '(1 2 3 4) (nreverse result))
        (push (* x x) result)))
    ;; => (1 4 9 16)
    




Basics on DOTIMES

  1. Purpose



  2. Syntax

  3. (dotimes (<var> <count> &optional <result-form>)
      <body>)
    



  4. Basic example
  5. (dotimes (i 5)
      (format t "i = ~A~%" i))
    ;; i = 0
    ;; i = 1
    ;; i = 2
    ;; i = 3
    ;; i = 4
    ;; => NIL
    



  6. Custom return value
  7. (dotimes (i 3 "Loop done")
      (print i))
    ;; 0
    ;; 1
    ;; 2
    ;; => "Loop done"
    



  8. Early exit with RETURN

  9. (dotimes (i 10 "completed")
      (when (> i 4)
        (return (format nil "Stopped early at ~A" i)))
      (format t "i = ~A~%" i))
    ;; => "Stopped early at 5"
    



  10. Accumulating values
  11. (let ((sum 0))
      (dotimes (i 5 sum)
        (incf sum (* i 2))))
    ;; => 20
    



  12. Building lists inside DOTIMES
  13. (let ((squares '()))
      (dotimes (i 6 (nreverse squares))
        (push (* i i) squares)))
    ;; => (0 1 4 9 16 25)
    



  14. Nested DOTIMES loops
  15. (dotimes (x 3)
      (dotimes (y 3)
        (format t "(~A,~A) " x y))
      (format t "~%"))
    ;; (0,0) (0,1) (0,2)
    ;; (1,0) (1,1) (1,2)
    ;; (2,0) (2,1) (2,2)
    




Basics on DO

  1. Purpose



  2. Syntax
  3. (do ((<var1> <init1> [<step1>])
         (<var2> <init2> [<step2>])
         ...
         (<varN> <initN> [<stepN>]))
        (<end-test> [<result-form>])
      <body>)
    



  4. Evaluation order

    1. All init forms are evaluated first, once, from left to right.
    2. All variables are bound to their init values.
    3. Before each iteration:
      • end-test is evaluated.
      • If true → loop stops, returning result-form (or NIL if omitted).
      • If false → executes the body.
    4. After each iteration:
      • Each step expression (if any) is evaluated and assigned to its corresponding variable.
    5. Then control goes back to the start, repeating the process.


  5. Basic Example
  6. (do ((i 0 (+ i 1)))   ; i starts at 0, increases by 1
        ((>= i 5) 'done)  ; stop when i >= 5, return 'done
      (format t "i = ~A~%" i))
    
    ;; i = 0
    ;; i = 1
    ;; i = 2
    ;; i = 3
    ;; i = 4
    ;; => DONE
    



  7. Multiple iteration variables
  8. (do ((i 0 (+ i 1))          ; i increments
         (j 10 (- j 2)))        ; j decrements
        ((> i 3) (list i j)) ; stop when i > 3, return (i j)
      (format t "i=~A, j=~A~%" i j))
    
    ;; i=0, j=10
    ;; i=1, j=8
    ;; i=2, j=6
    ;; i=3, j=4
    ;; => (4 2)
    



  9. Accumulating results
  10. (do ((i 1 (+ i 1))
         (sum 0 (+ sum i)))
        ((> i 5) sum))
    ;; => 15
    



  11. Creating infinite loops
  12. (do ((x 5))     ; x is initialized once, never updated
        ((<= x 0))  ; condition never becomes true
      (print x))
    



  13. Early exit using RETURN
  14. (do ((i 0 (+ i 1)))
        (nil)             ; end-test = NIL means infinite unless we RETURN
      (when (= i 3)
        (return 'early))  ; break manually
      (print i))
    
    ;; 0
    ;; 1
    ;; 2
    ;; => EARLY
    



  15. Combining DO with complex updates
  16. (do ((x 1 (* x 2))           ; doubles each time
         (y 10 (- y 3))          ; decreases by 3
         (acc '() (cons (* x y) acc))) ; collect products
        ((or (> x 10) (< y 0)) (nreverse acc))
      (format t "x=~A, y=~A~%" x y))
    
    ;; x=1, y=10
    ;; x=2, y=7
    ;; x=4, y=4
    ;; x=8, y=1
    ;; => (10 14 16 8)
    



  17. DO vs DOTIMES vs DOLIST

  18. Feature DOLIST DOTIMES DO
    Purpose Iterate over list elements Fixed number of times Fully manual control (multi-variable)
    End condition End of list Counter reaches limit Custom logical test
    Return value Optional result-form Optional result-form Optional result-form
    Updates Automatic (next element) Automatic (i++) Manual via step expressions
    Multiple variables No No Yes
    Use case Traverse lists Simple numeric loops Parallel iteration, accumulations, complex logic



LOOP

  1. LOOP is a macro in Common Lisp that provides a declarative, English-like syntax for performing iterations and collecting results.


  2. Basic syntax: (loop [<loop-clauses>])


  3. A loop is composed of clauses like:


  4. NOTE: LOOP syntax is non-Lispy: it doesn't follow S-expression style.


  5. Examples:

  6. (loop for x in '(a b c ) do
      (print x))
    ;; A
    ;; B
    ;; C
    
    (loop as i from 1 to 3 do (print i))
    ;; 1
    ;; 2
    ;; 3
    
    (loop for i from 1 to 3 do (print i))           ;; 1 2 3
    (loop for i from 3 downto 1 do (print i))       ;; 3 2 1
    (loop for i from 1 upto 3 do (print i))         ;; 1 2 3
    (loop for i from 1 below 4 do (print i))        ;; 1 2 3
    (loop for i from 5 above 2 do (print i))        ;; 5 4 3
    (loop for i from 0 to 10 by 2 do (print i))     ;; 0 2 4 6 8 10
    
    (loop repeat 3 do
      (print "Hello"))
    ;; "Hello"
    ;; "Hello"
    ;; "Hello"
    
    (loop named my-loop
      for i from 1 to 10 do
        (when (= i 5) (return-from my-loop 'stopped)))
    ;; 'STOPPED
    
    (loop
      initially (format t "Start~%")
      for i from 1 to 2 do (print i))
    
    (loop
      for i from 1 to 2 do (print i)
      finally (format t "Done~%"))
    
    (loop for x in '(a b c) collect x)                  ;; (A B C)
    (loop for tail on '(1 2 3) collect tail)            ;; ((1 2 3) (2 3) (3))
    (loop for x across #(10 20 30) collect (* x 2))     ;; (20 40 60)
    
    (loop
      for i from 1 to 3
        if (evenp i)
          collect i
        else
          collect (- i)
        end)
    ;; (-1 2 -3)
    
    (loop for i from 1 to 3 collect (* i i))            ;; (1 4 9)
    (loop for x in '((a b) (c) (d e)) append x)         ;; (A B C D E)
    (loop for i from 1 to 5 sum i)                      ;; 15
    (loop for i in '(1 2 3 4 5) count (evenp i))        ;; 2
    (loop for x in '(3 7 2 9 5) maximize x)             ;; 9
    (loop for x in '(3 7 2 9 5) minimize x)             ;; 2
    



Quote vs. Backquote

  1. Quote (' or (quote ...)): Don't evaluate, take it as data (prevents the usual evaluation of lists/symbols.).

  2. 'foo            ;; FOO            ; a symbol, not the value of variable FOO
    (quote foo)     ;; same as above
    
    '(1 2 3)        ;; (1 2 3)        ; a literal list (don't evaluate it)
    '(+ 1 2)        ;; (+ 1 2)        ; code-as-data, not 3
    

  3. Backquote / Quasiquote (` or (quasiquote ...)): Make a template, selectively evaluate with commas.
  4. (let ((a 10) (b '(x y)))
      `(+ ,a 20)                ;; (+ 10 20)    NOTE: it evals a template to a list (not 30 that no further evaluation by far!).
      `(1 2 ,a ,@b 99))         ;; (1 2 10 X Y 99)
    
    (let ((xs '(a b)))
      `(x ,xs y))   ;;  (X (A B) Y)
      `(x ,@xs y))  ;;  (X A B Y)
    



Destructing Parameter in DEFMACRO

  1. When you define a macro, you tell Lisp how to map the call form into symbols that you can use inside the macro body.
  2. (defmacro simple (x y)
      `(list ,x ,y))
    
    (simple 10 20)
    ;; expands to (LIST 10 20) and will be evaluated when using it.
    


  3. In a DEFMACRO, your lambda list doesn't just bind symbols to arguments: it can pattern-match the entire shape of the call form.
  4. (defmacro swap! ((a b))
      `(let ((temp ,a))
         (setf ,a ,b
               ,b temp)))
    
    (swap! (x y))
    ;; expands to:
    ;; (LET ((TEMP X)) (SETF X Y Y TEMP))
    
    
    
    (defmacro let1 ((var val) &body body)
      `(let ((,var ,val))
         ,@body))
    
    (let1 (x (+ 1 2))
      (print x))
    ;; expands to (LET ((X (+ 1 2))) (PRINT X))
    
    
    
    (defmacro bind2 ((a &optional (b 10)) &body body)
      `(let ((,a ,b))
         ,@body))
    
    (bind2 (x 5) (print x)) ;; (LET ((X 5)) (PRINT X))
    (bind2 (x) (print x))   ;; (LET ((X 10)) (PRINT X))
    
    
    
    (defmacro with-options ((&key (a 1) (b 2)) &body body)
      `(let ((x ,a) (y ,b))
         ,@body))
    
    (with-options (:a 10)
      (print (+ x y)))
    ;; expands to:
    ;; (LET ((X 10) (Y 2)) (PRINT (+ X Y)))
    


  5. All in all, what I understood it, in the language I could understand, is that:
    normally because &body acts like &rest, so this caused the body would very frequently also include the leter key parameters if given,
    using this pattern-matching, we can promote the key parameters before the body, so it very much eases our work to remove the key parameters from the macro call.



Collections

  1. Vectors are Common Lisp's basic integer-indexed collection, and they come in two flavors: fixed-size vectors and resizable vectors.


  2. Simplest way to construct a fixed-size vector with existing elements, is to use either (vector [<elements>]) or #(<elements>) syntax:
  3. (vector)
    #()
    
    (vector 1)
    #(1)
    
    (vector 1 2)
    #(1 2)
    


  4. MAKE-ARRAY is much more vesatile;
  5. (make-array 5 :initial-element nil);    #(NIL NIL NIL NIL NIL)
    
    
    
    ;; `fill-pointer` stores the number of elements inside the vector.
    (make-array 5 :fill-pointer 0);         #()
    
    
    
    (defparameter *x* (make-array 5 :fill-pointer 0))
    
    (vector-push 'a *x*);                   0
    *x*                 ;					#(A)
    (vector-push 'b *x*);					1
    *x*                 ;					#(A B)
    (vector-push 'c *x*);					2
    *x*                 ;					#(A B C)
    (vector-pop *x*)    ;					C
    *x*                 ;					#(A B)
    (vector-pop *x*)    ;					B
    *x*                 ;					#(A)
    (vector-pop *x*)    ;					A
    *x*                 ;					#()
    
    
    
    ;; To make an arbitrarily resizable vector, you need to pass MAKE-ARRAY another keyword argument: `:adjustable`.
    (make-array 5 :fill-pointer 0 :adjustable t); #()
    
    
    
    ;; You can also specify that a vector only contains certain types of elements (if non-specified, then it could take different kinds of elements).
    (make-array 5 :fill-pointer 0 :adjustable t :element-type 'character)
    


  6. Vector as sequence:
  7. (sbcl)    (defparameter *x* (vector 1 2 3))
    
    (sbcl)    (length *x*); 3
    (sbcl)    (elt *x* 0) ; 1
    (sbcl)    (elt *x* 1) ; 2
    (sbcl)    (elt *x* 2) ; 3
    (sbcl)    (elt *x* 3) ; error
    
    (sbcl)    (setf (elt *x* 0) 10)
    (sbcl)    *x*; #(10 2 3)
    


  8. Basic Sequence Functions

  9. Name Required Arguments Returns
    COUNT Item and sequence. Number of times item appear in sequence.
    FIND Item and sequence. Item or NIL
    POSITION Item and sequence. Index into sequence or NIL (0-indexed).
    REMOVE Item and sequence. Sequence with instances of item removed.
    SUBSTITUTE New-Item, item, and sequence. Sequence with instances of item replaced.

    (count 1 #(1 2 1 2 3 1 2 3 4))        ;		3
    (remove 1 #(1 2 1 2 3 1 2 3 4))       ;		#(2 2 3 2 3 4)
    (remove 1 '(1 2 1 2 3 1 2 3 4))       ;		(2 2 3 2 3 4)
    (remove #\a "foobarbaz")              ;		"foobrbz"
    (substitute 10 1 #(1 2 1 2 3 1 2 3 4));		#(10 2 10 2 3 10 2 3 4)
    (substitute 10 1 '(1 2 1 2 3 1 2 3 4));		(10 2 10 2 3 10 2 3 4)
    (substitute #\x #\b "foobarbaz")      ;		"fooxarxaz"
    (find 1 #(1 2 1 2 3 1 2 3 4))         ;		1
    (find 10 #(1 2 1 2 3 1 2 3 4))        ;		NIL
    (position 1 #(1 2 1 2 3 1 2 3 4))     ;		0
    
    (count "foo" #("foo" "bar" "baz") :test #'string=)   ; 1
    (find 'c #((a 10) (b 20) (c 30) (d 40)) :key #'first); (C 30)
    
    (find 'a #((a 10) (b 20) (a 30) (b 40)) :key #'first)            ; (A 10)
    (find 'a #((a 10) (b 20) (a 30) (b 40)) :key #'first :from-end t); (A 30)
    
    (remove #\a "foobarbaz" :count 1)            ; "foobrbaz"
    (remove #\a "foobarbaz" :count 1 :from-end t); "foobarbz"
    
    (count-if #'evenp #(1 2 3 4 5))        ; 2
    
    (count-if-not #'evenp #(1 2 3 4 5))    ; 3
    
    (position-if #'digit-char-p "abcd0001"); 4
    
    (remove-if-not #'(lambda (x) (char= (elt x 0) #\f))
      #("foo" "bar" "baz" "foom"))
    ;; #("foo" "foom")
    
    (remove-duplicates #(1 2 1 2 3 1 2 3 4))    ; #(1 2 3 4)
    
    (concatenate 'vector #(1 2 3) '(4 5 6))     ; #(1 2 3 4 5 6)
    (concatenate 'list #(1 2 3) '(4 5 6))       ; (1 2 3 4 5 6)
    (concatenate 'string "abc" '(#\d #\e #\f))  ; "abcdef"
    
    (merge 'vector #(1 3 5) #(2 4 6) #'<)    ; #(1 2 3 4 5 6)
    (merge 'list #(1 3 5) #(2 4 6) #'<)      ; (1 2 3 4 5 6)
    
    (subseq "foobarbaz" 3)                      ; "barbaz"
    (subseq "foobarbaz" 3 6)                    ; "bar"
    
    
    
    (defparameter *x* (copy-seq "foobarbaz"))
    
    (setf (subseq *x* 3 6) "xxx")  ; subsequence and new value are same length
    *x*
    ;; "fooxxxbaz"
    
    (setf (subseq *x* 3 6) "abcd") ; new value too long, extra character ignored.
    *x*
    ;; "fooabcbaz"
    
    (setf (subseq *x* 3 6) "xx")   ; new value too short, only two characters changed
    *x*
    ;; "fooxxcbaz"
    
    
    
    (every #'evenp #(1 2 3 4 5))   ; NIL
    (some #'evenp #(1 2 3 4 5))    ; T
    (notany #'evenp #(1 2 3 4 5))  ; NIL
    (notevery #'evenp #(1 2 3 4 5)); T
    
    
    
    (map 'vector #'* #(1 2 3 4 5) #(10 9 8 7 6)); #(10 18 24 28 30)
    (reduce #'+ #(1 2 3 4 5 6 7 8 9 10)); 55
    


  10. Standard Sequence Function Keyword Arguments

  11. Argument Meaning Default
    :test Two-argument function used to compare item (or value extracted by :key function) to element. EQL
    :key One-argument function to extract key value from actual sequence element.
    NIL means use element as is.
    NIL
    :start Starting index (inclusive) of subsequence. 0
    :end Ending index (exclusive) of subsequence.
    NIL indicates end of sequence.
    NIL
    :from-end If true, the sequence will be traversed in reverse order, from end to start. NIL
    :count Number indicating the number of elements to remove or substitute or NIL to indicate all (REMOVE and SUBSTITUTE only). NIL



CONS

  1. A cons cell is the fundamental 2-slot building block of Lisp lists.


  2. (cons a d) allocates a new cons cell whose CAR is a and CDR is d.
  3. (cons 1 2)          ; (1 . 2)   ;; an *improper* (dotted) pair
    (cons 1 '(2 3))     ; (1 2 3)   ;; a proper list
    (cons 'a 'b)        ; (A . B)
    (cons '(a b) '(c d)); ((A B) C D)
    


  4. Proper vs. improper lists:



  5. Basic access: CAR and CDR
  6. (car '(10 20 30)) ; 10
    (cdr '(10 20 30)) ; (20 30)
    (first '(10 20))  ; 10      ; synonyms: FIRST = CAR, REST = CDR
    (rest  '(10 20))  ; (20)
    
    (cadr  '(a b c))  ; B   ; = (car (cdr ...))
    (caddr '(a b c d)); C
    
    
    
    (cons 0 '(1 2 3))       ; (0 1 2 3)   ; O(1) prepend
    (list 1 2 3)            ; (1 2 3)     ; constructs a fresh proper list
    (list* 1 2 3)           ; (1 2 . 3)   ; last arg becomes the final CDR (can make improper)
    (append '(1 2) '(3 4))  ; (1 2 3 4)   ; copies all but last list; O(n) in first arg
    
    
    
    (let ((x (list 1 2 3)))
      (setf (car x) 99)     ; x => (99 2 3)
      (setf (cdr x) '(7))   ; x => (99 7)
      x)
    




SET, SEQ and SETF

  1. Overview

  2. Operator Type Evaluates 1st arg? Assigns to Works for Notes
    SETQ Special operator No Lexical or special variables Variables only Fastest
    SETF Macro Partially (place-specific) Generalized places Variables, array slots, struct slots, hash entries, accessors, ... Most general
    SET Function Yes Global / special value cell of a symbol Symbols only Dynamic only; NEVER lexical


  3. SETQ does not evaluate the variable name, and works on lexical variables (from let) and special/global variables.

  4. (let ((a 1))
      (setq a 2)   ; modifies lexical A
      a)
    ;; 2
    


  5. SETF is designed to be the general assignment operator, and works on simple variables (like setq) and complex places.

  6. (setf x 10)                     ; variable
    (setf (car mylist) 3)           ; list cell
    (setf (slot-value obj 'age) 25) ; CLOS slot
    (setf (gethash 'a table) 9)     ; hash table key
    (setf (aref arr 3) 22)          ; array
    (setf my-struct-field 100)      ; accessor
    


  7. SET evaluates its first argument and its result must be a symbol. It only modifies the symbol's global/special value, not lexicals.

    Because it is a Function. Functions in Lisp evaluate all their arguments before the function is called.

  8. (set 'a 100)
    a
    ;; 100
    
    
    (let ((a 1))
      (set 'a 200))     ; Sets GLOBAL A, not this lexical A
    a                   ; global A => 200
    
    
    (let ((x 10))
      (set x 20))       ; ERROR: X holds 10, not a symbol
    
    
    
    
    ;; Global A
    (set 'a 100)        ; sets global A = 100
    
    (setq a 'b)         ; a now holds the symbol B
    (set a 100)         ; sets global B = 100
    
    (setq a 42)         ; replace `setq` here with `setf` is also ok.
    (set a 100)         ; ERROR: 42 is not a symbol
    
    (let ((a 1))
      (set 'a 999)      ; sets global A, lexical a still 1
      a)                ; 1
    




Arrays (like in C / JS / TS)

  1. In Common Lisp, an array is a fixed-size, indexable collection of elements.
    It is similar to: In Lisp, vectors are just one-dimensional arrays. Here we focus on the general array features.


  2. Creating 1D Arrays with MAKE-ARRAY:
  3. ;; A 1D array of length 5, elements are unspecified, in SBCL it is treated as 0.
    (defparameter *a* (make-array 5))
    
    ;; A 1D array of length 5, all elements start as 0
    ;; (defparameter *b* (make-array '(5) :initial-element 0))
    (defparameter *b* (make-array 5 :initial-element 0))
    
    *a*  ; => #(<UNSPECIFIED> <UNSPECIFIED> <UNSPECIFIED> <UNSPECIFIED> <UNSPECIFIED>)
    *b*  ; => #(0 0 0 0 0)
    


  4. Array literal syntax for 1D arrays (vectors):
  5. #(1 2 3)      ; vector of 3 elements
    #("foo" "bar") ; vector of strings
    


  6. Accessing and modifying elements with AREF:
  7. (defparameter *nums* (make-array 4 :initial-element 0))
    ; *NUMS* => #(0 0 0 0)
    
    (aref *nums* 0)     ; => 0
    (setf (aref *nums* 0) 42)
    (aref *nums* 0)     ; => 42
    
    (aref *nums* 3)     ; last valid index (0-based)
    ; (aref *nums* 4)   ; ERROR: index out of bounds
    


  8. Comparing to C / JS / TS (informally):

  9. Language Example Notes
    C int a[4]; a[0] = 42; Fixed-size, contiguous memory.
    JS / TS const arr = [0, 0, 0, 0]; arr[0] = 42; Resizable, dynamic, can push/pop.
    Common Lisp (defparameter *a* (make-array 4 :initial-element 0))
    (setf (aref *a* 0) 42)
    By default fixed-size. Can also make adjustable arrays.



Multi-Dimensional Arrays

  1. Common Lisp arrays can have multiple dimensions, like int a[3][4]; in C.


  2. Use a list of dimensions with MAKE-ARRAY:
  3. ;; 2 rows, 3 columns, all zeros
    (defparameter *matrix* (make-array '(2 3) :initial-element 0))
    
    *matrix*
    ;; => #2A((0 0 0)
    ;;        (0 0 0))
    


  4. Access elements with AREF using one index per dimension.
  5. (setf (aref *matrix* 0 0) 10)
    (setf (aref *matrix* 0 1) 20)
    (setf (aref *matrix* 1 2) 30)
    
    *matrix*
    ;; => #2A((10 20 0)
    ;;        (0  0 30))
    
    (aref *matrix* 1 2)  ; => 30
    


  6. Literal syntax for multi-dimensional arrays uses #nA:
  7. #2A((1 2 3)
        (4 5 6))
    ;; 2x3 array
    
    #3A(((1 2) (3 4))
        ((5 6) (7 8)))
    ;; 3D array example
    


  8. Inspecting dimensions:
  9. (array-dimensions *matrix*) ; => (2 3)
    (array-dimension *matrix* 0) ; => 2   ; rows
    (array-dimension *matrix* 1) ; => 3   ; columns
    


  10. Iterating over a 2D array (like a matrix):
  11. (defun print-matrix (m)
      (destructuring-bind (rows cols) (array-dimensions m)
        (dotimes (i rows)
          (dotimes (j cols)
            (format t "~3A " (aref m i j)))
          (format t "~%"))))
    
    (print-matrix *matrix*)
    ;; 10 20  0
    ;;  0  0 30
    



Element Types and Specialized Arrays

  1. By default, arrays can hold any type (element type is T).
    You can restrict the element type for efficiency (implementation-dependent optimizations).


  2. Character array (like a mutable string buffer):
  3. (defparameter *chars*
      (make-array 5 :element-type 'character
                    :initial-element #\?))
    
    *chars* ; => #(#\? #\? #\? #\? #\?)
    
    (setf (aref *chars* 0) #\H)
    (setf (aref *chars* 1) #\i)
    
    *chars* ; => #(#\H #\i #\? #\? #\?)
    


  4. Numeric array, e.g. fixnum:
  5. (defparameter *ints*
      (make-array 4 :element-type 'fixnum
                    :initial-element 0))
    
    (setf (aref *ints* 0) 10)
    (setf (aref *ints* 1) 20)
    *ints* ; => #(10 20 0 0)
    


  6. Element type does not change the API (you still use aref and setf),
    but can allow the implementation to store data more compactly (for example, like a C int[] or char[]).



Adjustable Arrays and "Dynamic" Behavior

  1. JavaScript / TypeScript arrays are dynamic: you can always push / pop and change their length.
    Common Lisp arrays are normally fixed-size, more like C arrays.
    However, you can ask Lisp to make an array: This combination behaves very similarly to a dynamic array with capacity + current length.



  2. What is a fill pointer?


  3. ;; Physical size = 5, but logical length (fill-pointer) = 0
    (defparameter *buf* (make-array 5 :fill-pointer 0))
    
    *buf*         ; => #()
    (length *buf*); => 0
    
    ;; Underlying storage exists:
    (setf (aref *buf* 0) 42)
    (setf (aref *buf* 1) 99)
    
    ;; Still hidden because fill-pointer is 0
    *buf*         ; => #()
    (length *buf*); => 0
    
    ;; Move fill pointer to 2
    (setf (fill-pointer *buf*) 2)
    *buf*         ; => #(42 99)
    (length *buf*); => 2
    


  4. Creating adjustable, fill-pointer arrays (dynamic-style):
  5. ;; Start with capacity 0, fill-pointer 0, adjustable
    (defparameter *dyn*
      (make-array 0
                  :element-type 't
                  :adjustable t
                  :fill-pointer 0))
    
    *dyn*            ; => #()
    (length *dyn*)   ; => 0
    


  6. vector-push and vector-push-extend:


  7. (vector-push-extend 10 *dyn*)
    (vector-push-extend 20 *dyn*)
    (vector-push-extend 30 *dyn*)
    
    *dyn*          ; => #(10 20 30)
    (length *dyn*) ; => 3
    
    ;; You can also pop like from a stack:
    (vector-pop *dyn*) ; => 30
    *dyn*              ; => #(10 20)
    (length *dyn*)     ; => 2
    


  8. ADJUST-ARRAY: manually change dimensions


  9. ;; Grow to physical size 5.
    ;; Existing contents kept, new slots initialized with 0.
    (setf *dyn* (adjust-array *dyn* 5 :initial-element 0))
    
    *dyn*          ; => #(10 20 0 0 0)
    (length *dyn*) ; => 2      ; fill-pointer still 2!
    
    ;; If you want logical length = 5:
    (setf (fill-pointer *dyn*) 5)
    *dyn*          ; => #(10 20 0 0 0)
    (length *dyn*) ; => 5
    


  10. Summary: :fill-pointer and :adjustable

  11. Option Meaning Typical use
    :fill-pointer n Array has a logical length n. length and printing use this. Buffers, stacks, dynamic sequences built on top of an array.
    :fill-pointer t Fill pointer is initially set to the full size (all elements "in use"). Start full, then shrink/grow by changing fill pointer.
    :adjustable t Array can be resized with ADJUST-ARRAY (and by vector-push-extend). Dynamic arrays whose capacity grows over time.


  12. Other useful MAKE-ARRAY keyword arguments (overview)

  13. Keyword Example Effect
    :element-type (make-array 10 :element-type 'fixnum) Restrict element type (numbers, characters, etc.) for possible speed/memory benefits.
    :initial-element (make-array 5 :initial-element 0) Fill all slots with this value.
    :initial-contents (make-array 3 :initial-contents '(10 20 30)) Provide a list (or nested lists for multi-d arrays) to initialize elements.
    :fill-pointer (make-array 10 :fill-pointer 0) Enable fill pointer (logical length), required for vector-push, vector-pop.
    :adjustable (make-array 0 :adjustable t) Allow resizing via ADJUST-ARRAY, used by vector-push-extend.
    :displaced-to (make-array 5 :displaced-to other-array) Make an array that shares storage with another (view / slice).
    :displaced-index-offset (make-array 3 :displaced-to big :displaced-index-offset 2) Start the view at a non-zero offset into the underlying array.


  14. Big picture:



Array Element Types

  1. Every Common Lisp array has an element type: this tells Lisp what kinds of values may be stored in it.


  2. If you don't specify one, the default is T (anything).
    That means the array can hold numbers, strings, symbols, lists, other arrays: anything at all.


  3. However, when you restrict the element type, Lisp can often use a more compact and efficient internal representation: similar to how C arrays of int or float are faster and smaller than generic pointer arrays.


  4. Common element types include:

  5. Element Type Description Example
    T Can hold any Lisp object (default). Slowest and most general. (make-array 3 :element-type 't :initial-contents '(a b c))
    BIT Only 0 or 1 allowed. Stored as packed bits, like a C bool[]. (make-array 8 :element-type 'bit :initial-contents '(1 0 1 0 1 0 0 1))
    CHARACTER Holds characters (like a mutable string). (make-array 5 :element-type 'character :initial-element #\?)
    BASE-CHAR Subset of CHARACTER (typically ASCII). Useful for portable strings. (make-array 5 :element-type 'base-char)
    STRING-CHAR Usually equivalent to CHARACTER, but emphasizes use as text data. (make-array 5 :element-type 'string-char)
    FIXNUM Machine-native integers (fast). Range depends on platform, typically 29–61 bits. (make-array 4 :element-type 'fixnum :initial-element 0)
    INTEGER Can hold any integer (including big integers). May be slower than fixnum. (make-array 3 :element-type 'integer :initial-element 42)
    (UNSIGNED-BYTE 8) 8-bit unsigned integer (0–255). Ideal for bytes or binary file data. (make-array 4 :element-type '(unsigned-byte 8) :initial-element 255)
    (SIGNED-BYTE 8) 8-bit signed integer (−128–127). (make-array 4 :element-type '(signed-byte 8) :initial-element -5)
    (UNSIGNED-BYTE 16) 16-bit unsigned integer (0–65535). (make-array 2 :element-type '(unsigned-byte 16) :initial-element 1024)
    FLOAT Generic floating-point (may default to single-float). (make-array 3 :element-type 'float :initial-element 1.0)
    SINGLE-FLOAT 32-bit float (IEEE single precision). (make-array 3 :element-type 'single-float :initial-element 0.0)
    DOUBLE-FLOAT 64-bit float (IEEE double precision). (make-array 2 :element-type 'double-float :initial-element 0.0d0)
    COMPLEX Holds complex numbers (e.g. #C(1.0 2.0)). (make-array 2 :element-type 'complex :initial-contents '(#C(1 2) #C(3 4)))
    STRING Shortcut type for one-dimensional array of character. (make-array 5 :element-type 'string-char)


  6. Testing element type of an array:
  7. (array-element-type #(1 2 3))
    ;; => T
    
    (array-element-type (make-array 10 :element-type 'bit))
    ;; => BIT
    


  8. Typed arrays are specialized:

  9. (defparameter *bytes*
      (make-array 4 :element-type '(unsigned-byte 8)
                    :initial-contents '(72 101 108 108))) ; "Hell"
    
    (write-sequence *bytes* #p"out.bin")
    


  10. Multi-dimensional typed arrays:
  11. (make-array '(3 3)
                 :element-type 'single-float
                 :initial-element 0.0)
    ;; => #2A((0.0 0.0 0.0)
    ;;        (0.0 0.0 0.0)
    ;;        (0.0 0.0 0.0))
    


  12. Notes and portability tips:

  13. Example summary:
  14. (defparameter *arr-any*  (make-array 3 :element-type 't))
    (defparameter *arr-int*  (make-array 3 :element-type 'fixnum :initial-element 42))
    (defparameter *arr-float* (make-array 3 :element-type 'single-float :initial-element 0.5))
    (defparameter *arr-bit*  (make-array 8 :element-type 'bit :initial-contents '(1 0 1 0 1 1 0 0)))
    (defparameter *arr-char* (make-array 4 :element-type 'character :initial-contents "LISP"))
    
    (list
      (array-element-type *arr-any*)
      (array-element-type *arr-int*)
      (array-element-type *arr-float*)
      (array-element-type *arr-bit*)
      (array-element-type *arr-char*))
    ;; => (T FIXNUM SINGLE-FLOAT BIT CHARACTER)
    



CAR and CDR

  1. Historical meaning:
    The names CAR and CDR come from the 1950s IBM 704 machine architecture. Today, they simply mean:


  2. Basic usage:
  3. (defparameter *nums* '(10 20 30 40))
    
    (car *nums*) ; => 10
    (cdr *nums*) ; => (20 30 40)
    


  4. CAR and CDR act on cons cells (pairs):

  5. (cons 10 (cons 20 (cons 30 nil)))
    ;; = (10 20 30)
    
    (car '(10 20 30)) ; => 10
    (cdr '(10 20 30)) ; => (20 30)
    


  6. Understanding the structure:

  7. Expression Diagram Result
    '(10 20 30) [10 | o]→[20 | o]→[30 | NIL] List of three numbers
    (car '(10 20 30)) Returns first cell's left part 10
    (cdr '(10 20 30)) Returns pointer to second cell (20 30)


  8. Nested CAR/CDR combinations

  9. (defparameter *lst* '((a b) (c d) (e f)))
    
    (car *lst*)        ; => (A B)
    (cdr *lst*)        ; => ((C D) (E F))
    (car (car *lst*))  ; => A
    (car (cdr *lst*))  ; => (C D)
    (car (cdr (car *lst*))) ; => B
    


  10. Shorthand forms: Lisp has built-in combinations up to four levels deep:

  11. Form Equivalent to Description
    (caar x) (car (car x)) First of the first
    (cadr x) (car (cdr x)) Second element
    (caddr x) (car (cdr (cdr x))) Third element
    (cddr x) (cdr (cdr x)) All but the first two elements
    (defparameter *nums* '(1 2 3 4))
    (cadr *nums*)  ; => 2
    (caddr *nums*) ; => 3
    (cddr *nums*)  ; => (3 4)
    


  12. Modern synonyms (more readable):

  13. Old Modern equivalent Meaning
    car first Head of list
    cdr rest Tail of list
    (cadr x) (second x) Second element
    (caddr x) (third x) Third element
    (cdddr x) (nthcdr 3 x) Drop first 3 elements
    (first '(a b c d)) ; => A
    (rest  '(a b c d)) ; => (B C D)
    (third '(a b c d)) ; => C
    (nth 2 '(a b c d)) ; => C
    


  14. Summary:



CONS

  1. A CONS is the most fundamental data structure in Lisp. It constructs a pair of two values, traditionally called: Together, these form a cons cell: the atomic "node" of all lists in Lisp.


  2. Creating a pair:
  3. (cons 'apple 'banana)
    ;; => (APPLE . BANANA)
    



  4. CONS is how all lists are built: a list is just a chain of cons cells where each CDR points to the next cons (and the last points to NIL):
  5. (cons 'a (cons 'b (cons 'c nil)))
    ;; => (A B C)
    
    ;; Equivalent literal
    '(A B C)
    


  6. Understanding the structure visually:

  7. Code Cons Cell Chain Printed Form
    (cons 'a 'b) [a | b] (A . B)
    (cons 'a (cons 'b nil)) [a | o]→[b | NIL] (A B)
    (cons 'a (cons 'b (cons 'c nil))) [a | o]→[b | o]→[c | NIL] (A B C)



  8. Dotted pairs vs proper lists

  9. (cons 'a 'b)          ; => (A . B)
    (cons 'a '(b c d))    ; => (A B C D)
    (cons '(a b) '(c d))  ; => ((A B) C D)
    

    (cons 'a (cons 'b 'c))
    ;; => (A B . C)
    



  10. Accessing parts of a CONS cell:
  11. (defparameter *pair* (cons 'x 'y))
    
    (car *pair*) ; => X
    (cdr *pair*) ; => Y
    




  12. CONSing lists together
  13. (cons 0 '(1 2 3))
    ;; => (0 1 2 3)
    
    (cons '(1 2) '(3 4))
    ;; => ((1 2) 3 4)
    

    (append '(1 2) '(3 4))
    ;; => (1 2 3 4)
    



  14. Common idioms:
  15. (push <item> <list>)
    ;; same as (setf <list> (cons <item> <list>))
    
    (pop <list>)
    ;; removes and returns the first element (like stack pop)
    

    (defparameter *stack* nil)
    (push 'first *stack*) ; => (FIRST)
    (push 'second *stack*) ; => (SECOND FIRST)
    (pop *stack*)         ; => SECOND
    *stack*               ; => (FIRST)
    



  16. Pairs as associations:
  17. (defparameter *pair* (cons 'key 'value))
    *pair* ; => (KEY . VALUE)
    
    (car *pair*) ; => KEY
    (cdr *pair*) ; => VALUE
    

    (defparameter *alist*
      '((apple . red)
        (banana . yellow)
        (grape . purple)))
    
    (assoc 'banana *alist*)
    ;; => (BANANA . YELLOW)
    
    (cdr (assoc 'banana *alist*))
    ;; => YELLOW
    



  18. CONS memory analogy:

  19. In Lisp In C analogy
    (cons a b) struct Pair { void *car; void *cdr; }
    (car x) x->car
    (cdr x) x->cdr
    (cons 1 (cons 2 (cons 3 nil))) Linked list: head→next→next→NULL


  20. Summary:



Using Symbols in Common Lisp

  1. What is a symbol really?



  2. Using symbols as variable names

  3. (defvar *counter* 0)     ; *COUNTER* is a symbol used as a global variable
    (setq *counter* 10)      ; store 10 in its value cell
    
    (let ((x 42))            ; X is a symbol used as a local variable
      x)                     ; => 42
    

    (setq a 100)
    a                       ; => 100   ; evaluates to the value cell of A
    
    (symbol-value 'a)       ; => 100   ; same, but using the symbol object explicitly
    


  4. Using symbols as function names

  5. (defun square (x)
      (* x x))
    
    (square 5)                ; => 25
    (function square)         ; => #<FUNCTION SQUARE>
    (symbol-function 'square) ; same as FUNCTION but as a function
    



  6. Symbols as data (quoted)

  7. 'foo       ; symbol FOO
    (quote foo); same
    
    '(a b c)   ; list of three symbols: A, B, C
    

    (defparameter *expr* '(+ 1 2))
    *expr*           ; => (+ 1 2)  ; data (list of symbols and numbers)
    (eval *expr*)    ; => 3        ; treat it as code and evaluate
    


  8. Symbols as keys in plists and alists

  9. Property lists (plists) using keywords:

    (defparameter *person*
      '(:name "Abby"
        :age  20
        :city "Berlin"))
    
    (getf *person* :name) ; => "Abby"
    (getf *person* :age)  ; => 20
    

    Association lists (alists) using ordinary symbols:

    (defparameter *colors*
      '((apple  . red)
        (banana . yellow)
        (grape  . purple)))
    
    (assoc 'banana *colors*)        ; => (BANANA . YELLOW)
    (cdr (assoc 'banana *colors*))  ; => YELLOW
    



  10. Symbols and keyword parameters

  11. (defun make-user (&key name age admin)
      (list :name name :age age :admin admin))
    
    (make-user :name "Alice" :age 30 :admin t)
    ;; => (:NAME "Alice" :AGE 30 :ADMIN T)
    



  12. Symbol properties: symbol-plist

  13. (setf (symbol-plist 'user-id)
          '(:type integer :db-column "user_id"))
    
    (symbol-plist 'user-id)
    ;; => (:TYPE INTEGER :DB-COLUMN "user_id")
    
    (getf (symbol-plist 'user-id) :db-column)
    ;; => "user_id"
    



  14. Symbols and packages (namespaces)

  15. (symbol-name 'car)       ; => "CAR"
    (symbol-package 'car)    ; => #<PACKAGE "COMMON-LISP">
    
    ;; Intern a new symbol in a custom package:
    (make-package "MY-APP")
    (intern "FOO" "MY-APP")  ; => MY-APP::FOO
    



  16. Changing how symbols behave: value vs function

  17. (defun foo (x) (+ x 1)) ; define function FOO
    (setq foo 10)           ; define variable FOO
    
    foo          ; => 10          ; value cell
    (foo 5)      ; => 6           ; function cell
    
    (symbol-value 'foo)     ; => 10
    (symbol-function 'foo)  ; => #<FUNCTION FOO>
    



  18. Summary


Association Lists (Alists)

  1. What is an association list?

  2. (defparameter *colors*
      '((apple  . red)
        (banana . yellow)
        (grape  . purple)))
    
    ;; Each element is a cons cell:
    ;; (car pair) = key, (cdr pair) = value
    


  3. Accessing data with ASSOC

  4. (assoc 'banana *colors*)
    ;; => (BANANA . YELLOW)
    
    (cdr (assoc 'banana *colors*))
    ;; => YELLOW
    

    (assoc 'pear *colors*) ; => NIL
    


  5. Custom comparison functions

  6. (defparameter *people*
      '(("Alice" . 23)
        ("Bob"   . 30)
        ("Eve"   . 28)))
    
    (assoc "Bob" *people* :test #'string=)
    ;; => ("Bob" . 30)
    


  7. Adding or updating entries

  8. (defparameter *grades* nil)
    
    (setf *grades* (acons 'alice 95 *grades*))
    (setf *grades* (acons 'bob   88 *grades*))
    
    *grades* ; => ((BOB . 88) (ALICE . 95))
    

    (let ((cell (assoc 'bob *grades*)))
      (when cell
        (rplacd cell 90)))
    
    *grades* ; => ((BOB . 90) (ALICE . 95))
    

    (defun set-alist (key value alist)
      "Return a new alist with KEY updated to VALUE."
      (let ((pair (assoc key alist)))
        (if pair
            (progn (setf (cdr pair) value) alist)
            (acons key value alist))))
    
    (setf *grades* (set-alist 'alice 100 *grades*))
    *grades* ; => ((BOB . 90) (ALICE . 100))
    


  9. Removing an entry

  10. (setf *grades*
          (remove 'bob *grades* :key #'car))
    
    *grades* ; => ((ALICE . 100))
    


  11. Traversing an alist
  12. (dolist (pair *colors*)
      (format t "~A → ~A~%" (car pair) (cdr pair)))
    ;; APPLE → RED
    ;; BANANA → YELLOW
    ;; GRAPE → PURPLE
    


  13. Nested alists

  14. (defparameter *library*
      '((fiction . ((1984        . "Orwell")
                    (brave-new-world . "Huxley")))
        (science . ((cosmos . "Sagan")
                    (origin . "Darwin")))))
    
    (assoc 'fiction *library*)
    ;; => (FICTION ( (1984 . "Orwell") (BRAVE-NEW-WORLD . "Huxley") ))
    
    (assoc '1984 (cdr (assoc 'fiction *library*)))
    ;; => (1984 . "Orwell")
    


  15. Comparison: alist vs plist vs hash-table

  16. Structure Form Lookup Mutability Best for
    Alist ((key . val) ...) Linear (O(n)) via assoc Easy with rplacd or acons Small, dynamic mappings
    Plist (key1 val1 key2 val2 ...) Linear (O(n)) via getf Easy but less structured Keyword options, symbol metadata
    Hash table #<HASH-TABLE> Constant (O(1)) average Mutable with gethash, setf Large datasets, fast lookup


  17. Advanced: destructive updates with RPLACA and RPLACD

  18. (defparameter *pair* (assoc 'apple *colors*))
    (rplacd *pair* 'green)   ; change value to GREEN
    *colors* ; => ((APPLE . GREEN) (BANANA . YELLOW) (GRAPE . PURPLE))
    



  19. Quick utility examples
  20. (defun alist-keys (alist)
      (mapcar #'car alist))
    
    (defun alist-values (alist)
      (mapcar #'cdr alist))
    
    (alist-keys *colors*)   ; => (APPLE BANANA GRAPE)
    (alist-values *colors*) ; => (GREEN YELLOW PURPLE)
    


  21. Summary



Symbol Properties and SYMBOL-PLIST

  1. Every symbol has its own property list

  2. (symbol-plist 'apple)
    ;; => NIL  (no properties yet)
    


  3. Setting properties with setf

  4. (setf (symbol-plist 'apple)
          '(:color "red" :taste "sweet" :origin "Poland"))
    
    (symbol-plist 'apple)
    ;; => (:COLOR "red" :TASTE "sweet" :ORIGIN "Poland")
    


  5. Reading properties with get or getf

  6. (get 'apple :color)
    ;; => "red"
    
    (get 'apple :origin)
    ;; => "Poland"
    
    (get 'apple :price)
    ;; => NIL   ; key not present
    

    (getf (symbol-plist 'apple) :taste)
    ;; => "sweet"
    


  7. Changing and adding properties

  8. (setf (get 'apple :taste) "sour")
    (get 'apple :taste)
    ;; => "sour"
    
    (setf (getf (symbol-plist 'apple) :season) 'autumn)
    (symbol-plist 'apple)
    ;; => (:COLOR "red" :TASTE "sour" :ORIGIN "Poland" :SEASON AUTUMN)
    


  9. Removing a property

  10. (remprop 'apple :origin)
    (symbol-plist 'apple)
    ;; => (:COLOR "red" :TASTE "sour" :SEASON AUTUMN)
    
    (remf (symbol-plist 'apple) :taste)
    (symbol-plist 'apple)
    ;; => (:COLOR "red" :SEASON AUTUMN)
    


  11. Common pattern: attaching metadata to functions or symbols

  12. (defun compute-tax (price)
      (* price 0.19))
    
    (setf (get 'compute-tax :author) "Hwangfucius")
    (setf (get 'compute-tax :category) "Logic Study")
    
    (format t "Author: ~A~%" (get 'compute-tax :author))
    (format t "Category: ~A~%" (get 'compute-tax :category))
    ;; Author: Hwangfucius
    ;; Category: Logic Study
    



  13. PLIST structure recap

  14. Concept Example Notes
    Raw plist '(:color "red" :taste "sweet") Linear key-value sequence
    Attached to symbol (symbol-plist 'apple) Property list stored within that symbol object
    Read (get 'apple :color) Retrieve value
    Write (setf (get 'apple :taste) "sour") Modify or add
    Delete (remprop 'apple :taste) Remove entry


  15. Iterating over a symbol's plist

  16. (let ((plist (symbol-plist 'apple)))
      (loop for (key val) on plist by #'cddr
            do (format t "~A → ~A~%" key val)))
    
    ;; :COLOR → red
    ;; :SEASON → AUTUMN
    


  17. Comparing symbol plist with external alists

  18. Feature Symbol plist Alist
    Storage form (key1 val1 key2 val2 ...) ((key1 . val1) (key2 . val2))
    Attached to A single symbol object Any variable holding list
    Access functions get, remprop assoc, acons
    Use case Metadata or attributes for a symbol External key-value mapping



Packages, INTERN, and Namespaces

  1. What is a package?


  2. (symbol-name 'car)        ; "CAR"
    (symbol-package 'car)     ; #<PACKAGE "COMMON-LISP">
    (symbol-package :hello)   ; #<PACKAGE "KEYWORD">
    


  3. Creating a custom package with MAKE-PACKAGE

  4. (make-package "MY-APP" :use '("COMMON-LISP"))
    ;; => #<PACKAGE "MY-APP">
    



  5. INTERN: creating or finding a symbol inside a package

  6. (intern "FOO" "MY-APP")
    ;; first time => MY-APP::FOO, NIL
    ;; later      => MY-APP::FOO, :INTERNAL
    ;; return values typically: symbol, status
    

    (multiple-value-bind (sym status) (intern "FOO" "MY-APP")
      (list sym status))
    ;; => (MY-APP::FOO :INTERNAL)  ; for a fresh symbol
    


  7. Reading and printing package-qualified symbols


  8. Syntax Meaning When used
    pkg:foo Refer to exported (public) symbol FOO in package PKG. Normal "public API" usage.
    pkg::foo Refer to internal symbol FOO in package PKG. Peeking into implementation details.


  9. IN-PACKAGE: changing the current package

  10. ;; in a .lisp file:
    
    (in-package :my-app)
    
    (defparameter *x* 10)  ; *X* is really MY-APP::*X*
    



  11. DEFPACKAGE: the usual way to define packages

  12. (defpackage :my-app
      (:use :cl)
      (:export :start-app :*version*))
    
    (in-package :my-app)
    
    (defparameter *version* "1.0.0")
    
    (defun start-app ()
      (format t "Starting app v~A~%" *version*))
    



  13. FIND-SYMBOL: look up symbols by name and package

  14. (find-symbol "FOO" "MY-APP")
    ;; => MY-APP::FOO, :INTERNAL   or NIL, NIL if not present
    

    Function Creates new symbol? Returns
    intern Yes, if not already present Symbol, status (:internal / :external / :inherited)
    find-symbol No Symbol or NIL, plus same status


  15. SYMBOL-NAME and SYMBOL-PACKAGE

  16. (multiple-value-bind (sym status) (intern "FOO" "MY-APP")
      (list (symbol-name sym)
            (symbol-package sym)
            status))
    ;; => ("FOO" #<PACKAGE "MY-APP"> :INTERNAL)
    



  17. Exporting and importing symbols

  18. (in-package :my-app)
    
    (defvar *secret* 42)
    (export '*secret*)
    
    (symbol-package '*secret*) ; => #<PACKAGE "MY-APP">
    
    ;; From another package / REPL:
    MY-APP:*SECRET*  ; use single colon for exported symbol
    

    (use-package :my-app)
    *secret* ; now accessible directly (if no name conflict)
    


  19. Summary



my-app:start-app VS my-app::start-app

  1. Recap: exported vs internal symbols

  2. (defpackage :my-app
      (:use :cl)
      (:export :start-app :*version*))
    
    (in-package :my-app)
    
    (defparameter *version* "1.0.0")
    
    (defun start-app ()
      (format t "Starting app v~A~%" *version*))
    



  3. Single colon: pkg:symbol -> exported only





  4. Double colon: pkg::symbol → internal or external

  5. Continuing the same example (no :export):

    CL-USER> (my-app::start-app)
    Starting app!
    NIL
    



  6. What if the symbol doesn't exist?

  7. CL-USER> 'my-app::start-ap
    ;; => MY-APP::START-AP   ; a new symbol was created
    
    CL-USER> (my-app::start-ap)
    ;; => Undefined-function error at runtime
    



  8. Export vs internal access: behavior table

  9. Symbol status in MY-APP Form Result
    Exported my-app:start-app ✅ Works
    Exported my-app::start-app ✅ Also works (can still use internal-access syntax)
    Internal (not exported) my-app:start-app ❌ Reader error: not exported
    Internal (not exported) my-app::start-app ✅ Works (internal symbol access)


  10. Best practice / style



  11. Summary



Package Designators: :my-app VS "MY-APP"

  1. The confusion

  2. (defpackage :my-app
      (:use :cl))
    
    (in-package :my-app)
    
    (find-symbol "FOO" "MY-APP")
    (intern "BAR" "MY-APP")
    



  3. Package designator: multiple types allowed

  4. (find-symbol "FOO" "MY-APP")
    (find-symbol "FOO" :my-app)
    (find-symbol "FOO" (find-package :my-app))
    


  5. Why :my-app in DEFPACKAGE and IN-PACKAGE?

  6. (defpackage :my-app
      (:use :cl)
      (:export :start-app))
    
    (in-package :my-app)
    

    (defpackage "MY-APP"
      (:use "CL"))
    (in-package "MY-APP")
    



  7. Why "MY-APP" in FIND-SYMBOL / INTERN examples?

  8. (find-symbol "FOO" "MY-APP")
    (find-symbol "FOO" :my-app)
    (find-symbol "FOO" (find-package "MY-APP"))
    

    (intern "FOO" :my-app)
    (find-symbol "BAR" :my-app)
    


  9. Symbol name vs package name

  10. (symbol-name :my-app)
    ;; => "MY-APP"
    
    (find-package :my-app)
    ;; => #<PACKAGE "MY-APP">
    
    (find-package "MY-APP")
    ;; => #<PACKAGE "MY-APP">
    


  11. Side-by-side comparison

  12. Form Type What package functions see
    "MY-APP" String Package name string = "MY-APP"
    :my-app Keyword symbol Use (symbol-name :my-app)"MY-APP"
    #<PACKAGE "MY-APP"> Package object Used directly


  13. Practical guidelines

  14. (intern "FOO" :my-app)          ; idiomatic
    (intern "FOO" "MY-APP")         ; also valid
    (intern "FOO" (find-package :my-app)) ; most explicit
    


  15. Summary



Returning Multiple Values

  1. Introduction

  2. (values 10 20 30)
    ;; => 10
    ;; (prints only first value in REPL, but others still exist!)
    


  3. Creating multiple values with VALUES

  4. (defun divide (x y)
      (values (floor (/ x y))  ; quotient
              (mod x y)))      ; remainder
    
    (divide 10 3)
    ;; => 3
    ;; (prints 3, but second value 1 exists)
    
    (multiple-value-bind (q r) (divide 10 3)
      (list q r))
    ;; => (3 1)
    


  5. MULTIPLE-VALUE-BIND: unpacking values

  6. (multiple-value-bind (a b c) (values 1 2)
      (list a b c))
    ;; => (1 2 NIL)
    



  7. MULTIPLE-VALUE-LIST

  8. (multiple-value-list (values 1 2 3))
    ;; => (1 2 3)
    



  9. MULTIPLE-VALUE-CALL

  10. (multiple-value-call #'list (values 'a 'b 'c))
    ;; => (A B C)
    



  11. Ignoring extra values

  12. (defun test ()
      (values 1 2 3))
    
    (+ (test) 5)
    ;; => 6   ; only first value 1 used
    



  13. VALUES-LIST

  14. (values-list '(10 20 30))
    ;; => 10, 20, 30
    



  15. Key Functions and Macros Summary

  16. Name Purpose Example
    values Return multiple values (values a b c)
    multiple-value-bind Bind multiple results to variables (multiple-value-bind (x y) (func) ...)
    multiple-value-list Collect values into a list (multiple-value-list (func))
    values-list Return list elements as multiple values (values-list '(1 2 3))
    multiple-value-call Call function with all returned values (multiple-value-call #'list (values 1 2 3))


  17. Comparison to lists and tuples

  18. Concept Multiple Values List
    Representation Native runtime feature (not a list) Explicit object
    Memory allocation No consing needed Creates a list object
    Efficiency Very fast Slower for temporary data
    Backward compatibility Only first value used if context ignores others Always one object



Currying vs Closures

  1. Closures: Functions that remember

  2. (defun make-adder (n)
      "Return a function that adds N to its argument."
      #'(lambda (x)
          (+ x n)))
    
    (setq add5 (make-adder 5))
    (funcall add5 10)   ; => 15
    (funcall add5 100)  ; => 105
    

    (setq add2 (make-adder 2))
    (setq add10 (make-adder 10))
    
    (funcall add2 3)   ; => 5
    (funcall add10 3)  ; => 13
    





  3. Currying: Functions that take one argument at a time

  4. (defun curry (fn)
      "Transform a two-argument function into a curried one."
      #'(lambda (a)
          #'(lambda (b)
              (funcall fn a b))))
    
    (setq curried-add (curry #'+))
    
    (setq add3 (funcall curried-add 3))
    (funcall add3 4) ; => 7
    

    ((curry #'+) 2 5)
    ;; => 7
    


  5. Comparison Table

  6. Feature Closure Currying
    Definition Function that captures variables from its environment. Transformation turning f(a,b) into f(a)(b).
    Purpose To preserve data across calls ("remembering" variables). To allow partial application and functional chaining.
    Changes arity? No. Yes: from many arguments to one-at-a-time functions.
    Built with Lexical scope capture. Closures plus function nesting.
    Example (Lisp) (make-adder 5) (curry #'+)
    Analogy "A backpack that carries its variables." "A conveyor belt feeding one argument at a time."


  7. Example side-by-side

  8. ;; Closure
    (defun make-multiplier (factor)
      #'(lambda (x) (* x factor)))
    
    (setq double (make-multiplier 2))
    (funcall double 10) ; => 20
    
    
    ;; Currying
    (defun curry (fn)
      #'(lambda (a)
          #'(lambda (b)
              (funcall fn a b))))
    
    (setq curried-mul (curry #'*))
    (funcall (funcall curried-mul 2) 10) ; => 20
    




Basics on Printing in Common Lisp

  1. PRINT: prints an object in a readable way with quotes and a trailing newline. Often used for debugging.
  2. (print "Hello")
    ;; prints:  "Hello"
    ;; returns: "Hello"


  3. PRINC: prints the object in a more human-readable form (without quotes or escapes). Useful for user-facing messages rather than debugging.
  4. (princ "Hello")
    ;; prints:   Hello
    ;; returns: "Hello"


  5. WRITE: the most general printing function, with many keyword options to control behavior.
    It can specify whether to print readably, add escape characters, or include structure indentation.
  6. (write "Hello" :escape nil :pretty t)
    ;; prints:   Hello
    ;; returns: "Hello"


  7. FORMAT: the most powerful printing utility, allowing formatted text output (similar to printf in C).
    It can print to the terminal or to a string, and supports rich directives starting with ~.
  8. (format t "Hello, ~a!~%" "World")
    ;; prints:  Hello, World!
    ;; returns: NIL


  9. By using NIL as the first argument, FORMAT returns the formatted string instead of printing it.
  10. (format nil "Sum of ~d and ~d is ~d." 3 4 (+ 3 4))
    ;; returns: "Sum of 3 and 4 is 7."


  11. FORMAT directives (common ones):

  12. (format t "Name: ~a~%Age: ~d~%Code: ~~ABC~~~%" "Hwangfucius" 23)
    ;; prints:
    ;;      Name: Hwangfucius
    ;;      Age: 23
    ;;      Code: ~ABC~
    ;; returns:
    ;;      NIL
    



Details on FORMAT

  1. Its basic signature is: (format <destination> <control-string> &rest <arguments>)
    It interprets the control string and replaces ~-directives with formatted versions of the given arguments.


  2. Destination argument:
    The first argument (destination) determines where the output goes:

  3. (format t "Hello, ~a!~%" "World")
    ;; prints:  Hello, World!
    ;; returns: NIL
    
    (format nil "Hello, ~a!~%" "World")
    ;; prints nothing
    ;; returns: "Hello, World!
    ;; " (with a newline at the end)
    
    (format nil "Hello, ~a!" "World")
    ;; prints nothing
    ;; returns: "Hello, World!"
    
    (with-open-file (out "greeting.txt"
                         :direction :output
                         :if-exists :supersede)
      (format out "Saved greeting: ~a~%" "Hello from Common Lisp"))
    ;; writes to the file greeting.txt
    


  4. Basic substitution directives:

  5. (format t "Aesthetic (~a) vs standard (~s)~%" "Hello" "Hello")
    ;; prints: Aesthetic (Hello) vs standard ("Hello")
    
    (format t "Decimal: ~d~%" 42)
    ;; prints: Decimal: 42
    
    (format t "Line 1~%Line 2~%")
    ;; prints:
    ;; Line 1
    ;; Line 2
    
    (format t "Tilde example: ~~ This is a tilde.~%")
    ;; prints: Tilde example: ~ This is a tilde.
    


  6. ~a is meant for human-readable output, ~s for Lisp-readable output.
  7. (format t "Using ~~a: ~a~%" "Hello")
    ;; prints: Using ~a: Hello
    
    (format t "Using ~~s: ~s~%" "Hello")
    ;; prints: Using ~s: "Hello"
    


  8. ~d is for integers (decimal), ~f is for floating-point numbers, with optional width and precision controls.
  9. (format t "Integer: ~d~%" 123)
    ;; prints: Integer: 123
    
    (format t "Float default: ~f~%" 3.14159)
    ;; prints something like: Float default: 3.14159
    
    ;; ~,2f → 2 digits after the decimal point
    (format t "Pi to 2 decimals: ~,2f~%" 3.14159)
    ;; prints: Pi to 2 decimals: 3.14
    
    ;; ~10,2f → width 10, 2 decimals (padded on the left)
    (format t "Right-aligned: |~10,2f|~%" 3.14159)
    ;; prints: Right-aligned: |      3.14|
    


  10. Newlines and "fresh-line":
  11. (format t "First line~%Second line~%")
    ;; prints:
    ;; First line
    ;; Second line
    
    (format t "Hello")
    (format t "~&World~%")
    ;; If "Hello" ended the line, ~& starts a new one.
    ;; prints:
    ;; Hello
    ;; World
    
    ;; So basically it does the same as below:
    (format t "Hello~%")
    (format t "~&World~%")
    ;; prints:
    ;; Hello
    ;; World
    


  12. Multiple arguments and ordering:
    Each directive typically consumes one argument (unless it is a control directive). The arguments are used in the order they appear.
  13. (format t "~a + ~a = ~a~%" 2 3 (+ 2 3))
    ;; prints: 2 + 3 = 5
    
    (format t "Name: ~a, Age: ~d~%" "Hwangfucius" 23)
    ;; prints: Name: Hwangfucius, Age: 23
    


  14. The ~[ ... ~] control directive chooses among several alternatives based on an integer argument.

  15. (format t "~[zero~;one~;two~;many~]~%" 0)
    ;; prints:  zero
    ;; returns: NIL
    
    (format t "~[zero~;one~;two~;many~]~%" 2)
    ;; prints:  two
    ;; returns: NIL
    
    (format t "~[zero~;one~;two~;many~]~%" 10)
    ;; prints nothing in SBCL
    ;; returns: NIL
    ;; (However, the last clause is used as "fallback" in some other lisp interpreters.)


  16. The ~{ ... ~} control directive repeats its body for each element in a list argument.
    Inside the body, directives consume elements from the current list.
  17. (format t "Numbers: ~{~a ~}~%" '(1 2 3 4))
    ;; prints:  Numbers: 1 2 3 4
    ;; returns: NIL
    
    (format t "~{Name: ~a, Age: ~d~%~}" '(("Alice" 30) ("Bob" 25)))
    ;; prints:  Name: (Alice 30), Age: (Bob 25)
    ;; returns: NIL
    
    (format t "~{Name: ~a, Age: ~d~%~}" '("Alice" 30 "Bob" 25))
    ;; prints:
    ;;      Name: Alice, Age: 30
    ;;      Name: Bob, Age: 25
    ;; returns:
    ;;      NIL
    


  18. The ~* control directive allows you to skip one or more arguments without printing them.
    This is useful when combining FORMAT with conditional constructs.
  19. (format t "~a ~*~a~%" "first" "skip-me" "third")
    ;; ~a consumes "first"
    ;; ~* skips "skip-me"
    ;; ~a consumes "third"
    ;;
    ;; prints:  first third
    ;; returns: NIL
    


  20. The ~< ... ~> control directive can be used to create formatted fields with alignment (left, right, centered).
    This is more advanced, but useful for tables and pretty printing.
  21. (format t "~<~100a~>~%" "Hi")
    ;; A simple example: pad "Hi" with 98 blank spaces on the right into a field.
    ;; Exact behavior depends on additional modifiers,
    ;; but ~< ... ~> is the basic block alignment mechanism.


  22. FORMAT to build strings (instead of printing):
    As mentioned, using nil as the destination makes FORMAT return a string.
    This is very convenient for constructing complex strings.
  23. (let ((msg (format nil "User ~a has ~d unread messages." "Alice" 5)))
      (print msg))
    ;; prints: "User Alice has 5 unread messages."
    ;; msg is the string: "User Alice has 5 unread messages."