The Common Lisp Cookbook – Type System

Table of Contents

The Common Lisp Cookbook – Type System

📢 New videos: web dev demo part 1, dynamic page with HTMX, Weblocks demo

📕 Get the EPUB and PDF

Common Lisp has a complete and flexible type system and corresponding tools to inspect, check and manipulate types. It allows creating custom types, adding type declarations to variables and functions and thus to get compile-time warnings and errors.

Values Have Types, Not Variables

Being different from some languages such as C/C++, variables in Lisp are just placeholders for objects1. When you setf a variable, an object is “placed” in it. You can place another value to the same variable later, as you wish.

This implies a fact that in Common Lisp objects have types, while variables do not. This might be surprising at first if you come from a C/C++ background.

For example:

(defvar *var* 1234)
*VAR*

(type-of *var*)
(INTEGER 0 4611686018427387903)

The function type-of returns the type of the given object. The returned result is a type-specifier. In this case the first element is the type and the remaining part is extra information (lower and upper bound) of that type. You can safely ignore it for now. Also remember that integers in Lisp have no limit!

Now let’s try to setf the variable:

* (setf *var* "hello")
"hello"

* (type-of *var*)
(SIMPLE-ARRAY CHARACTER (5))

You see, type-of returns a different result: simple-array of length 5 with contents of type character. This is because *var* is evaluated to string "hello" and the function type-of actually returns the type of object "hello" instead of variable *var*.

Type Hierarchy

The inheritance relationship of Lisp types consists a type graph and the root of all types is T. For example:

* (describe 'integer)
COMMON-LISP:INTEGER
  [symbol]

INTEGER names the built-in-class #<BUILT-IN-CLASS COMMON-LISP:INTEGER>:
  Class precedence-list: INTEGER, RATIONAL, REAL, NUMBER, T
  Direct superclasses: RATIONAL
  Direct subclasses: FIXNUM, BIGNUM
  No direct slots.

INTEGER names a primitive type-specifier:
  Lambda-list: (&OPTIONAL (SB-KERNEL::LOW '*) (SB-KERNEL::HIGH '*))

The function describe shows that the symbol integer is a primitive type-specifier that has optional information lower bound and upper bound. Meanwhile, it is a built-in class. But why?

Most common Lisp types are implemented as CLOS classes. Some types are simply “wrappers” of other types. Each CLOS class maps to a corresponding type. In Lisp types are referred to indirectly by the use of type specifiers.

There are some differences between the function type-of and class-of. The function type-of returns the type of a given object in type specifier format while class-of returns the implementation details.

* (type-of 1234)
(INTEGER 0 4611686018427387903)

* (class-of 1234)
#<BUILT-IN-CLASS COMMON-LISP:FIXNUM>

Checking Types

The function typep can be used to check if the first argument is of the given type specified by the second argument.

* (typep 1234 'integer)
T

The function subtypep can be used to inspect if a type inherits from the another one. It returns 2 values:

For example:

* (subtypep 'integer 'number)
T
T

* (subtypep 'string 'number)
NIL
T

Sometimes you may want to perform different actions according to the type of an argument. The macro typecase is your friend:

* (defun plus1 (arg)
    (typecase arg
      (integer (+ arg 1))
      (string (concatenate 'string arg "1"))
      (t 'error)))
PLUS1

* (plus1 100)
101 (7 bits, #x65, #o145, #b1100101)

* (plus1 "hello")
"hello1"

* (plus1 'hello)
ERROR

Type Specifier

A type specifier is a form specifying a type. As mentioned above, returning value of the function type-of and the second argument of typep are both type specifiers.

As shown above, (type-of 1234) returns (INTEGER 0 4611686018427387903). This kind of type specifiers are called compound type specifier. It is a list whose head is a symbol indicating the type. The rest part of it is complementary information.

* (typep '#(1 2 3) '(vector number 3))
T

Here the complementary information of the type vector is its elements type and size respectively.

The rest part of a compound type specifier can be a *, which means “anything”. For example, the type specifier (vector number *) denotes a vector consisting of any number of numbers.

* (typep '#(1 2 3) '(vector number *))
T

The trailing parts can be omitted, the omitted elements are treated as *s:

* (typep '#(1 2 3) '(vector number))
T

* (typep '#(1 2 3) '(vector))
T

As you may have guessed, the type specifier above can be shortened as following:

* (typep '#(1 2 3) 'vector)
T

You may refer to the CLHS page for more information.

Defining New Types

You can use the macro deftype to define a new type-specifier.

Its argument list can be understood as a direct mapping to elements of rest part of a compound type specifier. They are defined as optional to allow symbol type specifier.

Its body should be a macro checking whether given argument is of this type (see defmacro).

We can use member to define enum types, for example:

(deftype fruit () '(member :apple :orange :pear))

Now let us define a new data type. The data type should be a array with at most 10 elements. Also each element should be a number smaller than 10. See following code for an example:

* (defun small-number-array-p (thing)
    (and (arrayp thing)
      (<= (length thing) 10)
      (every #'numberp thing)
      (every (lambda (x) (< x 10)) thing)))

* (deftype small-number-array (&optional type)
    `(and (array ,type 1)
          (satisfies small-number-array-p)))

* (typep '#(1 2 3 4) '(small-number-array number))
T

* (typep '#(1 2 3 4) 'small-number-array)
T

* (typep '#(1 2 3 4 100) 'small-number-array)
NIL

* (small-number-array-p '#(1 2 3 4 5 6 7 8 9 0 1))
NIL

Run-time type Checking

Common Lisp supports run-time type checking via the macro check-type. It accepts a place and a type specifier as arguments and signals an type-error if the contents of place are not of the given type.

* (defun plus1 (arg)
    (check-type arg number)
    (1+ arg))
PLUS1

* (plus1 1)
2 (2 bits, #x2, #o2, #b10)

* (plus1 "hello")
; Debugger entered on #<SIMPLE-TYPE-ERROR expected-type: NUMBER datum: "Hello">

The value of ARG is "Hello", which is not of type NUMBER.
   [Condition of type SIMPLE-TYPE-ERROR]
...

Compile-time type checking

You may provide type information for variables, function arguments etc via proclaim, declaim (at the toplevel) and declare (inside functions and macros).

However, similar to the :type slot introduced in CLOS section, the effects of type declarations are undefined in Lisp standard and are implementation specific. So there is no guarantee that the Lisp compiler will perform compile-time type checking.

However, it is possible, and SBCL is an implementation that does thorough type checking.

Let’s recall first that Lisp already warns about simple type warnings. The following function wrongly wants to concatenate a string and a number. When we compile it, we get a type warning.

(defconstant +foo+ 3)
(defun bar ()
  (concatenate 'string "+" +foo+))
; caught WARNING:
;   Constant 3 conflicts with its asserted type SEQUENCE.
;   See also:
;     The SBCL Manual, Node "Handling of Types"

The example is simple, but it already shows a capacity some other languages don’t have, and it is actually useful during development ;) Now, we’ll do better.

Declaring the type of variables

Use the macro declaim with a type declaration identifier (other identifiers are “ftype, inline, notinline, optimize…).

Let’s declare that our global variable *name* is a string. You can type the following in any order in the REPL:

(declaim (type (string) *name*))
(defparameter *name* "book")

Now if we try to set it with a bad type, we get a simple-type-error:

(setf *name* :me)
Value of :ME in (THE STRING :ME) is :ME, not a STRING.
   [Condition of type SIMPLE-TYPE-ERROR]

We can do the same with our custom types. Let’s quickly declare the type list-of-strings:

(defun list-of-strings-p (list)
  "Return t if LIST is non nil and contains only strings."
  (and (consp list)
       (every #'stringp list)))

(deftype list-of-strings ()
  `(satisfies list-of-strings-p))

Now let’s declare that our *all-names* variables is a list of strings:

(declaim (type (list-of-strings) *all-names*))
;; and with a wrong value:
(defparameter *all-names* "")
;; we get an error, still at compile-time:
Cannot set SYMBOL-VALUE of *ALL-NAMES* to "", not of type
(SATISFIES LIST-OF-STRINGS-P).
   [Condition of type SIMPLE-TYPE-ERROR]

Composing types

We can compose types. Following the previous example:

(declaim (type (or null list-of-strings) *all-names*))

Declaring the input and output types of functions

We use again the declaim macro, with ftype (function …) instead of just type:

(declaim (ftype (function (fixnum) fixnum) add))
;;                         ^^input ^^output [optional]
(defun add (n)
  (+ n  1))

With this we get nice type warnings at compile time.

If we change the function to erroneously return a string instead of a fixnum, we get a warning:

(defun add (n)
  (format nil "~a" (+ n  1)))
; caught WARNING:
;   Derived type of ((GET-OUTPUT-STREAM-STRING STREAM)) is
;     (VALUES SIMPLE-STRING &OPTIONAL),
;   conflicting with the declared function return type
;     (VALUES FIXNUM &REST T).

If we use add inside another function, to a place that expects a string, we get a warning:

(defun bad-concat (n)
  (concatenate 'string (add n)))
; caught WARNING:
;   Derived type of (ADD N) is
;     (VALUES FIXNUM &REST T),
;   conflicting with its asserted type
;     SEQUENCE.

If we use add inside another function, and that function declares its argument types which appear to be incompatible with those of add, we get a warning:

(declaim (ftype (function (string)) bad-arg))
(defun bad-arg (n)
    (add n))
; caught WARNING:
;   Derived type of N is
;     (VALUES STRING &OPTIONAL),
;   conflicting with its asserted type
;     FIXNUM.

This all happens indeed at compile time, either in the REPL, either with a simple C-c C-c in Slime, or when we load a file.

Declaring &key parameters

Use &key (:argument type).

For example:

(declaim (ftype (function (string &key (:n integer))) foo))
(defun foo (bar &key n) …)

Declaring &rest parameters

This is less evident, you might need a well-placed declare.

In the following, we declare a fruit type and we write a function that uses a single fruit argument, so compiling placing-order gives us a type warning as expected:

(deftype fruit () '(member :apple :orange :pear))

(declaim (ftype (function (fruit)) one-order))
(defun one-order (fruit)
  (format t "Ordering ~S~%" fruit))

(defun placing-order ()
  (one-order :bacon))

But in this version, we use &rest parameters, and we don’t have a type warning anymore:

(declaim (ftype (function (&rest fruit)) place-order))
(defun place-order (&rest selections)
  (dolist (s selections)
    (format t "Ordering ~S~%" s)))

(defun placing-orders ()
  (place-order :orange :apple :bacon)) ;; => no type warning

The declaration is correct, but our compiler doesn’t check it. A well-placed declare gives us the compile-time warning back:

(defun place-order (&rest selections)
  (dolist (s selections)
    (declare (type fruit s))      ;; <= declare
    (format t "Ordering ~S~%" s)))

(defun placing-orders ()
  (place-order :orange :apple :bacon))

=>

The value
  :BACON
is not of type
  (MEMBER :PEAR :ORANGE :APPLE)

For portable code, we would add run-time checks with an assert.

Declaring class slots types

A class slot accepts a :type slot option. It is however generally not used to check the type of the initform. SBCL, starting with version 1.5.9 released on november 2019, now gives those warnings, meaning that this:

(defclass foo ()
  ((name :type number :initform "17")))

throws a warning at compile time.

Note: see also sanity-clause, a data serialization/contract library to check slots’ types during make-instance (which is not compile time).

Alternative type checking syntax: defstar, serapeum

The Serapeum library provides a shortcut that looks like this:

 (-> mod-fixnum+ (fixnum fixnum) fixnum)
 (defun mod-fixnum+ (x y) ...)

The Defstar library provides a defun* macro that allows to add the type declarations into the lambda list. It looks like this:

(defun* sum ((a real) (b real))
   (+ a b))

It also allows:

Limitations

Complex types involving satisfies are not checked inside a function body by default, only at its boundaries. Even if it does a lot, SBCL doesn’t do as much as a statically typed language.

Consider this example, where we badly increment an integer with a string:

(declaim (ftype (function () string) bad-adder))
(defun bad-adder ()
  (let ((res 10))
    (loop for name in '("alice")
       do (incf res name))  ;; <= bad
    (format nil "finally doing sth with ~a" res)))

Compiling this function doesn’t throw a type warning.

However, if we had the problematic line at the function’s boundary we’d get the warning:

(defun bad-adder ()
  (let ((res 10))
    (loop for name in  '("alice")
       return (incf res name))))
; in: DEFUN BAD-ADDER
;     (SB-INT:NAMED-LAMBDA BAD-ADDER
;         NIL
;       (BLOCK BAD-ADDER
;         (LET ((RES 10))
;           (LOOP FOR NAME IN *ALL-NAMES* RETURN (INCF RES NAME)))))
;
; caught WARNING:
;   Derived type of ("a hairy form" NIL (SETQ RES (+ NAME RES))) is
;     (VALUES (OR NULL NUMBER) &OPTIONAL),
;   conflicting with the declared function return type
;     (VALUES STRING &REST T).

We could also use a the declaration in the loop body to get a compile-time warning:

       do (incf res (the string name)))

What can we conclude? This is yet another reason to decompose your code into small functions.

See also


  1. The term object here has nothing to do with Object-Oriented or so. It means “any Lisp datum”. 

Page source: type.md

T
O
C