29.4 Program Interface to the Condition System

This section describes functions, macros, variables, and condition types associated with the Common Lisp Condition System.

29.4.1 Signaling Conditions

The functions in this section provide various mechanisms for signaling warnings, breaks, continuable errors, and fatal errors.

[Function] error datum &rest arguments

Invokes the signal facility on a condition. If the condition is not handled, (invoke-debugger condition) is executed. As a consequence of calling invoke-debugger, error never directly returns to its caller; the only exit from this function can come by non-local transfer of control in a handler or by use of an interactive debugging command.

If datum is a condition, then that condition is used directly. In this case, it is an error for the list of arguments to be non-empty; that is, error must have been called with exactly one argument, the condition.

If datum is a condition type (a class or class name), then the condition used is effectively the result of (apply #’make-condition datum arguments).

If datum is a string, then the condition used is effectively the result of

(make-condition ’simple-error
                :format-string datum
                :format-arguments arguments)


[Function] cerror continue-format-string datum &rest arguments

The function cerror invokes the error facility on a condition. If the condition is not handled, (invoke-debugger condition) is executed. While signaling is going on, and while control is in the debugger (if it is reached), it is possible to continue program execution (thereby returning from the call to cerror) using the continue restart.

If datum is a condition, then that condition is used directly. In this case, the list of arguments need not be empty, but will be used only with the continue-format-string and will not be used to initialize datum.

If datum is a condition type (a class or class name), then the condition used is effectively the result of (apply #’make-condition datum arguments).

If datum is a string, then the condition used is effectively the result of

(make-condition ’simple-error
                :format-string datum
                :format-arguments arguments)

The continue-format-string must be a string. Note that if datum is not a string, then the format arguments used by the continue-format-string will still be the list of arguments (which is in keyword format if datum is a condition type). In this case, some care may be necessary to set up the continue-format-string correctly. The format directive ~*, which ignores and skips over format arguments, may be particularly useful in this situation.

The value returned by cerror is nil.


[Function] signal datum &rest arguments

Invokes the signal facility on a condition. If the condition is not handled, signal returns nil.

If datum is a condition, then that condition is used directly. In this case, it is an error for the list of arguments to be non-empty; that is, signal must have been called with exactly one argument, the condition.

If datum is a condition type (a class or class name), then the condition used is effectively the result of (apply #’make-condition datum arguments).

If datum is a string, then the condition used is effectively the result of

(make-condition ’simple-error
                :format-string datum
                :format-arguments arguments)

Note that if (typep condition *break-on-signals*) is true, then the debugger will be entered prior to beginning the process of signaling. The continue restart function may be used to continue with the signaling process; the restart is associated with the signaled condition as if by use of with-condition-restarts. This is true also for all other functions and macros that signal conditions, such as warn, error, cerror, assert, and check-type.

During the dynamic extent of a call to signal with a particular condition, the effect of calling signal again on that condition object for a distinct abstract event is not defined. For example, although a handler may resignal a condition in order to allow outer handlers first shot at handling the condition, two distinct asynchronous keyboard events must not signal an the same (eq) condition object at the same time.

For further details about signaling and handling, see the discussion of condition handlers in section 29.3.17.


[Variable] *break-on-signals*

This variable is intended primarily for use when the user is debugging programs that do signaling. The value of *break-on-signals* should be suitable as a second argument to typep, that is, a type or type specifier.

When (typep condition *break-on-signals*) is true, then calls to signal (and to other advertised functions such as error that implicitly call signal) will enter the debugger prior to signaling that condition. The continue restart may be used to continue with the normal signaling process; the restart is associated with the signaled condition as if by use of with-condition-restarts.

Note that nil is a valid type specifier. If the value of *break-on-signals* is nil, then signal will never enter the debugger in this implicit manner.

When setting this variable, the user is encouraged to choose the most restrictive specification that suffices. Setting this flag effectively violates the modular handling of condition signaling that this chapter seeks to establish. Its complete effect may be unpredictable in some cases, since the user may not be aware of the variety or number of calls to signal that are used in programs called only incidentally.

By default—and certainly in any “production” use—the value of this variable should be nil, both for reasons of performance and for reasons of modularity and abstraction.


29.4.2 Assertions

These facilities are designed to make it convenient for the user to insert error checks into code.

[Macro] check-type place typespec [string]

A check-type form signals an error of type type-error if the contents of place are not of the desired type.

If a condition is signaled, handlers of this condition can use the functions type-error-datum and type-error-expected-type to access the contents of place and the typespec, respectively.

This function can return only if the store-value restart is invoked, either explicitly from a handler or implicitly as one of the options offered by the debugger. The restart is associated with the signaled condition as if by use of with-condition-restarts.

If store-value is called, check-type will store the new value that is the argument to store-value (or that is prompted for interactively by the debugger) in place and start over, checking the type of the new value and signaling another error if it is still not the desired type. Subforms of place may be evaluated multiple times because of the implicit loop generated. check-type returns nil.

The place must be a generalized variable reference acceptable to setf. The typespec must be a type specifier; it is not evaluated. The string should be an English description of the type, starting with an indefinite article (“a” or “an”); it is evaluated. If the string is not supplied, it is computed automatically from the typespec. (The optional string argument is allowed because some applications of check-type may require a more specific description of what is wanted than can be generated automatically from the type specifier.)

The error message will mention the place, its contents, and the desired type. _____________________________________________________________________

Implementation note: An implementation may choose to generate a somewhat differently worded error message if it recognizes that place is of a particular form, such as one of the arguments to the function that called check-type.

___________________________________________________________________________________________________________

Lisp> (setq aardvarks ’(sam harry fred))
  (SAM HARRY FRED)
Lisp> (check-type aardvarks (array * (3)))
Error: The value of AARDVARKS, (SAM HARRY FRED),
       is not a 3-long array.
To continue, type :CONTINUE followed by an option number:
 1: Specify a value to use instead.
 2: Return to Lisp Toplevel.
Debug> :continue 1
Use Value: #(sam fred harry)
  NIL
Lisp> aardvarks
  #<ARRAY-3 13571>
Lisp> (map ’list #’identity aardvarks)
  (SAM FRED HARRY)
Lisp> (setq aacount ’foo)
  FOO
Lisp> (check-type aacount (integer 0 *) "a non-negative integer")
Error: The value of AACOUNT, FOO, is not a non-negative integer.
To continue, type :CONTINUE followed by an option number:
 1: Specify a value to use instead.
 2: Return to Lisp Toplevel.
Debug> :continue 2
Lisp>


[Macro] assert test-form [({place}*) [datum {argument}*]]

An assert form signals an error if the value of the test-form is nil. Continuing from this error using the continue restart will allow the user to alter the values of some variables, and assert will then start over, evaluating the test-form again. (The restart is associated with the signaled condition as if by use of with-condition-restarts.) assert returns nil.

The test-form may be any form. Each place (there may be any number of them, or none) must be a generalized variable reference acceptable to setf. These should be variables on which test-form depends, whose values may sensibly be changed by the user in attempting to correct the error. Subforms of each place are evaluated only if an error is signaled, and may be re-evaluated if the error is re-signaled (after continuing without actually fixing the problem).

The datum and arguments are evaluated only if an error is to be signaled, and re-evaluated if the error is to be signaled again.

If datum is a condition, then that condition is used directly. In this case, it is an error to specify any arguments.

If datum is a condition type (a class or class name), then the condition used is effectively the result of (apply #’make-condition datum (list {argument}* )).

If datum is a string, then the condition used is effectively the result of

(make-condition ’simple-error
                :format-string datum
                :format-arguments (list {argument}* ))

If datum is omitted, then a condition of type simple-error is constructed using the test-form as data. For example, the following might be used:

(make-condition ’simple-error
  :format-string "The assertion ~S failed."
  :format-arguments ’(test-form))

Note that the test-form itself, and not its value, is used as the format argument. ________________________________________________________________

Implementation note: The debugger need not include the test-form in the error message, and any places should not be included in the message, but they should be made available for the user’s perusal. If the user gives the “continue” command, an opportunity should be presented to alter the values of any or all of the references. The details of this depend on the implementation’s style of user interface, of course.

___________________________________________________________________________________________________________

Here is an example of the use of assert:

(setq x (make-array ’(3 5) :initial-element 3))
(setq y (make-array ’(3 5) :initial-element 7))

(defun matrix-multiply (a b)
  (let ((*print-array* nil))
    (assert (and (= (array-rank a) (array-rank b) 2)
                 (= (array-dimension a 1)
                    (array-dimension b 0)))
            (a b)
            "Cannot multiply ~S by ~S." a b)
    (really-matrix-multiply a b)))

(matrix-multiply x y)
Error: Cannot multiply #<ARRAY-3-5 12345> by #<ARRAY-3-5 12364>.
To continue, type :CONTINUE followed by an option number:
 1: Specify new values.
 2: Return to Lisp Toplevel.
Debug> :continue 1
Value for A: x
Value for B: (make-array ’(5 3) :initial-element 6)
 #2A((54 54 54 54 54)
(54 54 54 54 54)
(54 54 54 54 54)
(54 54 54 54 54)
(54 54 54 54 54))


29.4.3 Exhaustive Case Analysis

The syntax for etypecase and ctypecase is the same as for typecase, except that no otherwise clause is permitted. Similarly, the syntax for ecase and ccase is the same as for case except for the otherwise clause.

etypecase and ecase are similar to typecase and case, respectively, but signal a non-continuable error rather than returning nil if no clause is selected.

ctypecase and ccase are also similar to typecase and case, respectively, but signal a continuable error if no clause is selected.

[Macro] etypecase keyform {(type {form}*)}*

This control construct is similar to typecase, but no explicit otherwise or t clause is permitted. If no clause is satisfied, etypecase signals an error (of type type-error) with a message constructed from the clauses. It is not permissible to continue from this error. To supply an error message, the user should use typecase with an otherwise clause containing a call to error. The name of this function stands for “exhaustive type case” or “error-checking type case.”

Example:

Lisp> (setq x 1/3)
  1/3
Lisp> (etypecase x
        (integer (* x 4))
        (symbol (symbol-value x)))
Error: The value of X, 1/3, is neither an integer nor a symbol.
To continue, type :CONTINUE followed by an option number:
 1: Return to Lisp Toplevel.
Debug>


[Macro] ctypecase keyplace {(type {form}*)}*

This control construct is similar to typecase, but no explicit otherwise or t clause is permitted.

The keyplace must be a generalized variable reference acceptable to setf. If no clause is satisfied, ctypecase signals an error (of type type-error) with a message constructed from the clauses. This error may be continued using the store-value restart. The argument to store-value is stored in keyplace and then ctypecase starts over, making the type tests again. Subforms of keyplace may be evaluated multiple times. If the store-value restart is invoked interactively, the user will be prompted for the value to be used.

The name of this function is mnemonic for “continuable (exhaustive) type case.”

Example:

Lisp> (setq x 1/3)
  1/3
Lisp> (ctypecase x
        (integer (* x 4))
        (symbol (symbol-value x)))
Error: The value of X, 1/3, is neither an integer nor a symbol.
To continue, type :CONTINUE followed by an option number:
 1: Specify a value to use instead.
 2: Return to Lisp Toplevel.
Debug> :continue 1
Use value: 3.7
Error: The value of X, 3.7, is neither an integer nor a symbol.
To continue, type :CONTINUE followed by an option number:
 1: Specify a value to use instead.
 2: Return to Lisp Toplevel.
Debug> :continue 1
Use value: 12
  48


[Macro] ecase keyform {({({key}*) | key} {form}*)}*

This control construct is similar to case, but no explicit otherwise or t clause is permitted. If no clause is satisfied, ecase signals an error (of type type-error) with a message constructed from the clauses. It is not permissible to continue from this error. To supply an error message, the user should use case with an otherwise clause containing a call to error. The name of this function stands for “exhaustive case” or “error-checking case.”

Example:

Lisp> (setq x 1/3)
  1/3
Lisp> (ecase x
        (alpha (foo))
        (omega (bar))
        ((zeta phi) (baz)))
Error: The value of X, 1/3, is not ALPHA, OMEGA, ZETA, or PHI.
To continue, type :CONTINUE followed by an option number:
 1: Return to Lisp Toplevel.
Debug>


[Macro] ccase keyplace {({({key}*) | key} {form}*)}*

This control construct is similar to case, but no explicit otherwise or t clause is permitted.

The keyplace must be a generalized variable reference acceptable to setf. If no clause is satisfied, ccase signals an error (of type type-error) with a message constructed from the clauses. This error may be continued using the store-value restart. The argument to store-value is stored in keyplace and then ccase starts over, making the type tests again. Subforms of keyplace may be evaluated multiple times. If the store-value restart is invoked interactively, the user will be prompted for the value to be used.

The name of this function is mnemonic for “continuable (exhaustive) case.” _____________________________________________________________________

Implementation note: The type-error signaled by ccase and ecase is free to choose any representation of the acceptable argument type that it wishes for placement in the expected-type slot. It will always work to use type (member . keys), but in some cases it may be more efficient, for example, to use a type that represents an integer subrange or a type composed using the or type specifier.

___________________________________________________________________________________________________________

29.4.4 Handling Conditions

These macros allow a program to gain control when a condition is signaled.

[Macro] handler-case expression {(typespec ([var]) {form}*)}*

Executes the given expression in a context where various specified handlers are active.

Each typespec may be any type specifier. If during the execution of the expression a condition is signaled for which there is an appropriate clause—that is, one for which (typep conditiontypespec) is true—and if there is no intervening handler for conditions of that type, then control is transferred to the body of the relevant clause (unwinding the dynamic state appropriately in the process) and the given variable var is bound to the condition that was signaled. If no such condition is signaled and the computation runs to completion, then the values resulting from the expression are returned by the handler-case form.

If more than one case is provided, those cases are made accessible in parallel. That is, in

(handler-case expression
  (type1 (var1) form1)
  (type2 (var2) form2))

if the first clause (containing form1) has been selected, the handler for the second is no longer visible (and vice versa).

The cases are searched sequentially from top to bottom. If a signaled condition matches more than one case (possible if there is type overlap) the earlier of the two cases will be selected.

If the variable var is not needed, it may be omitted. That is, a clause such as

(type (var) (declare (ignore var)) form)

may be written using the following shorthand notation:

(type () form)

If there are no forms in a selected case, the case returns nil. Note that

(handler-case expression
  (type1 (var1) . body1)
  (type2 (var2) . body2)
  ...)

is approximately equivalent to

(block #1=#:block-1
  (let (#2=#:var-2)
    (tagbody
      (handler-bind ((type1 #’(lambda (temp)
    (setq #2# temp)
    (go #3=#:tag-3)))
                     (type2 #’(lambda (temp)
    (setq #2# temp)
    (go #4=#:tag-4)))
                     ...)
        (return-from #1# expression))
      #3# (return-from #1# (let ((var1 #2#)) . body1))
      #4# (return-from #1# (let ((var2 #2#)) . body2))
      ...)))

[Note the use of “gensyms” such as #:block-1 as block names, variables, and tagbody tags in this example, and the use of #n= and #n# read-macro syntax to indicate that the very same gensym appears in multiple places.—GLS]

As a special case, the typespec can also be the symbol :no-error in the last clause. If it is, it designates a clause that will take control if the expression returns normally. In that case, a completely general lambda-list may follow the symbol :no-error, and the arguments to which the lambda-list parameters are bound are like those for multiple-value-call on the return value of the expression. For example,

(handler-case expression
  (type1 (var1) . body1)
  (type2 (var2) . body2)
  ...
  (typen (varn) . bodyn)
  (:no-error (nvar1 nvar2 ... nvarm) . nbody))

is approximately equivalent to

(block #1=#:error-return
  (multiple-value-call #’(lambda (nvar1 nvar2 ... nvarm) . nbody)
    (block #2=#:normal-return
      (return-from #1#
        (handler-case (return-from #2# expression)
          (type1 (var1) . body1)
          (type2 (var2) . body2)
          ...
          (typen (varn) . bodyn))))))

Examples of the use of handler-case:

(handler-case (/ x y)
  (division-by-zero () nil))

(handler-case (open *the-file* :direction :input)
  (file-error (condition) (format t "~&Fooey: ~A~%" condition)))

(handler-case (some-user-function)
  (file-error (condition) condition)
  (division-by-zero () 0)
  ((or unbound-variable undefined-function) () ’unbound))

(handler-case (intern x y)
  (error (condition) condition)
  (:no-error (symbol status)
    (declare (ignore symbol))
    status))


[Macro] ignore-errors {form}*

Executes its body in a context that handles conditions of type error by returning control to this form. If no such condition is signaled, any values returned by the last form are returned by ignore-errors. Otherwise, two values are returned: nil and the error condition that was signaled.

ignore-errors could be defined by

(defmacro ignore-errors (&body forms)
  ‘(handler-case (progn ,@forms)
     (error (c) (values nil c))))


[Macro] handler-bind ({(typespec handler)}*) {form}*

Executes body in a dynamic context where the given handler bindings are in effect. Each typespec may be any type specifier. Each handler form should evaluate to a function to be used to handle conditions of the given type(s) during execution of the forms. This function should take a single argument, the condition being signaled.

If more than one binding is specified, the bindings are searched sequentially from top to bottom in search of a match (by visual analogy with typecase). If an appropriate typespec is found, the associated handler is run in a context where none of the handler bindings are visible (to avoid recursive errors). For example, in the case of

(handler-bind ((unbound-variable #’(lambda ...))
               (error #’(lambda ...)))
  ...)

if an unbound variable error is signaled in the body (and not handled by an intervening handler), the first function will be called. If any other kind of error is signaled, the second function will be called. In either case, neither handler will be active while executing the code in the associated function.


29.4.5 Defining Conditions

[The contents of this section are still a subject of some debate within X3J13. The reader may wish to take this section with a grain of salt, two aspirin tablets, and call a hacker in the morning.—GLS]

[Macro] define-condition name ({parent-type}*)[({slot-specifier}*) {option}*]

Defines a new condition type called name, which is a subtype of each given parent-type. Except as otherwise noted, the arguments are not evaluated.

Objects of this condition type will have all of the indicated slots, plus any additional slots inherited from the parent types (its superclasses). If the slots list is omitted, the empty list is assumed.

A slot must have the form

slot-specifier ::= slot-name | (slot-name [[↓slot-option ]])

For the syntax of a slot-option, see defclass. The slots of a condition object are normal CLOS slots. Note that with-slots may be used instead of accessor functions to access slots of a condition object.

make-condition will accept keywords (in the keyword package) with the print name of any of the designated slots, and will initialize the corresponding slots in conditions it creates.

Accessors are created according to the same rules as used by defclass.

The valid options are as follows:

[X3J13 voted in March 1989 to integrate the Condition System and the Object System. In the original Condition System proposal, define-condition allowed only one parent-type (the inheritance structure was a simple hierarchy). Slot descriptions were much simpler, even simpler than those for defstruct:

slot ::= slot-name | (slot-name) | (slot-name default-value)

Similarly, define-condition allowed a :conc-name option similar to that of defstruct:

One consequence of the vote was to make define-condition slot descriptions like those of defclass.—GLS]

Here are some examples of the use of define-condition.

The following form defines a condition of type peg/hole-mismatch that inherits from a condition type called blocks-world-error:

(define-condition peg/hole-mismatch (blocks-world-error)
                  (peg-shape hole-shape)
  (:report
    (lambda (condition stream)
      (with-slots (peg-shape hole-shape) condition
        (format stream "A ~A peg cannot go in a ~A hole."
                peg-shape hole-shape))))

The new type has slots peg-shape and hole-shape, so make-condition will accept :peg-shape and :hole-shape keywords. The with-slots macro may be used to access the peg-shape and hole-shape slots, as illustrated in the :report information.

Here is another example. This defines a condition called machine-error that inherits from error:

(define-condition machine-error (error)
                  ((machine-name
                    :reader machine-error-machine-name))
  (:report (lambda (condition stream)
             (format stream "There is a problem with ~A."
                     (machine-error-machine-name condition)))))

Building on this definition, we can define a new error condition that is a subtype of machine-error for use when machines are not available:

(define-condition machine-not-available-error (machine-error) ()
  (:report (lambda (condition stream)
             (format stream "The machine ~A is not available."
                     (machine-error-machine-name condition)))))

We may now define a still more specific condition, built upon machine-not-available-error, that provides a default for machine-name but does not provide any new slots or report information. It just gives the machine-name slot a default initialization:

(define-condition my-favorite-machine-not-available-error
                  (machine-not-available-error)
                  ((machine-name :initform "MC.LCS.MIT.EDU")))

Note that since no :report clause was given, the information inherited from machine-not-available-error will be used to report this type of condition.


29.4.6 Creating Conditions

The function make-condition is the basic means for creating condition objects.

[Function] make-condition type &rest slot-initializations

Constructs a condition object of the given type using slot-initializations as a specification of the initial value of the slots. The newly created condition is returned.

The slot-initializations are alternating keyword/value pairs. For example:

(make-condition ’peg/hole-mismatch
                :peg-shape ’square :hole-shape ’round)


29.4.7 Establishing Restarts

The lowest-level form that creates restart points is called restart-bind. The restart-case macro is an abstraction that addresses many common needs for restart-bind while offering a more palatable syntax. See also with-simple-restart. The function that transfers control to a restart point established by one of these macros is called invoke-restart.

All restarts have dynamic extent; a restart does not survive execution of the form that establishes it.

[Macro] with-simple-restart (name format-string {format-argument}*){form}*

This is shorthand for one of the most common uses of restart-case.

If the restart designated by name is not invoked while executing the forms, all values returned by the last form are returned. If that restart is invoked, control is transferred to the with-simple-restart form, which immediately returns the two values nil and t.

The name may be nil, in which case an anonymous restart is established.

with-simple-restart could be defined by

(defmacro with-simple-restart ((restart-name format-string
                                &rest format-arguments)
                               &body forms)
  ‘(restart-case (progn ,@forms)
     (,restart-name ()
       :report
         (lambda (stream)
           (format stream format-string ,@format-arguments))
       (values nil t))))

Here is an example of the use of with-simple-restart.

Lisp> (defun read-eval-print-loop (level)
        (with-simple-restart
            (abort "Exit command level ~D." level)
          (loop
            (with-simple-restart
                (abort "Return to command level ~D." level)
              (let ((form (prog2 (fresh-line)
                                 (read)
                                 (fresh-line))))
                (prin1 (eval form)))))))
  READ-EVAL-PRINT-LOOP
Lisp> (read-eval-print-loop 1)
(+ ’a 3)
Error: The argument, A, to the function + was of the wrong type.
       The function expected a number.
To continue, type :CONTINUE followed by an option number:
 1: Specify a value to use this time.
 2: Return to command level 1.
 3: Exit command level 1.
 4: Return to Lisp Toplevel.
Debug>

__________________________________________________________________________

Remark: Some readers may wonder what ought to be done by the “abort” key (or whatever the implementation’s interrupt key is—Control-C or Control-G, for example). Such interrupts, whether synchronous or asynchronous in nature, are beyond the scope of this chapter and indeed are not currently addressed by Common Lisp at all. This may be a topic worth standardizing under separate cover. Here is some speculation about some possible things that might happen.

An implementation might simply call abort or break directly without signaling any condition.

Another implementation might signal some condition related to the fact that a key had been pressed rather than to the action that should be taken. This is one way to allow user customization. Perhaps there would be an implementation-dependent keyboard-interrupt condition type with a slot containing the key that was pressed—or perhaps there would be such a condition type, but rather than its having slots, different subtypes of that type with names like keyboard-abort, keyboard-break, and so on might be signaled. That implementation would then document the action it would take if user programs failed to handle the condition, and perhaps ways for user programs to usefully dismiss the interrupt.__

Implementation note: Implementors are encouraged to make sure that there is always a restart named abort around any user code so that user code can call abort at any time and expect something reasonable to happen; exactly what the reasonable thing is may vary somewhat. Typically, in an interactive program, invoking abort should return the user to top level, though in some batch or multi-processing situations killing the running process might be more appropriate.

__________________________________________________________________________________

[Macro] restart-case expression {(case-name arglist{keyword value}*{form}*)}*

The expression is evaluated in a dynamic context where the clauses have special meanings as points to which control may be transferred. If the expression finishes executing and returns any values, all such values are simply returned by the restart-case form. While the expression is running, any code may transfer control to one of the clauses (see invoke-restart). If a transfer occurs, the forms in the body of that clause will be evaluated and any values returned by the last such form will be returned by the restart-case form.

As a special case, if the expression is a list whose car is signal, error, cerror, or warn, then with-condition-restarts is implicitly used to associate the restarts with the condition to be signaled. For example,

(restart-case (signal weird-error)
  (become-confused ...)
  (rewind-line-printer ...)
  (halt-and-catch-fire ...))

is equivalent to

(restart-case (with-condition-restarts
                weird-error
                (list (find-restart ’become-confused)
                      (find-restart ’rewind-line-printer)
                      (find-restart ’halt-and-catch-fire))
                (signal weird-error))
  (become-confused ...)
  (rewind-line-printer ...)
  (halt-and-catch-fire ...))

If there are no forms in a selected clause, restart-case returns nil.

The case-name may be nil or a symbol naming this restart.

It is possible to have more than one clause use the same case-name. In this case, the first clause with that name will be found by find-restart. The other clauses are accessible using compute-restarts. [In this respect, restart-case is rather different from case!—GLS]

Each arglist is a normal lambda-list containing parameters to be bound during the execution of its corresponding forms. These parameters are used to pass any necessary data from a call to invoke-restart to the restart-case clause.

By default, invoke-restart-interactively will pass no arguments and all parameters must be optional in order to accommodate interactive restarting. However, the parameters need not be optional if the :interactive keyword has been used to inform invoke-restart-interactively about how to compute a proper argument list.

The valid keyword value pairs are the following:

Note that

(restart-case expression
  (name1 arglist1 options1 . body1)
  (name2 arglist2 options2 . body2)
  ...)

is essentially equivalent to

(block #1=#:block-1
  (let ((#2=#:var-2 nil))
    (tagbody
      (restart-bind ((name1 #’(lambda (&rest temp)
    (setq #2# temp)
    (go #3=#:tag-3))
slightly transformed options1)
                     (name2 #’(lambda (&rest temp)
    (setq #2# temp)
    (go #4=#:tag-4))
slightly transformed options2)
                     ...)
        (return-from #1# expression))
      #3# (return-from #1#
                (apply #’(lambda arglist1 . body1) #2#))
      #4# (return-from #1#
                (apply #’(lambda arglist2 . body2) #2#))
      ...)))

[Note the use of “gensyms” such as #:block-1 as block names, variables, and tagbody tags in this example, and the use of #n= and #n# read-macro syntax to indicate that the very same gensym appears in multiple places.—GLS]

Here are some examples of the use of restart-case.

(loop
  (restart-case (return (apply function some-args))
    (new-function (new-function)
        :report "Use a different function."
        :interactive
          (lambda ()
            (list (prompt-for ’function "Function: ")))
      (setq function new-function))))

(loop
  (restart-case (return (apply function some-args))
    (nil (new-function)
        :report "Use a different function."
        :interactive
          (lambda ()
            (list (prompt-for ’function "Function: ")))
      (setq function new-function))))

(restart-case (a-command-loop)
  (return-from-command-level ()
      :report
        (lambda (s)     ;Argument s is a stream
          (format s "Return from command level ~D." level))
    nil))

(loop
  (restart-case (another-random-computation)
    (continue () nil)))

The first and second examples are equivalent from the point of view of someone using the interactive debugger, but they differ in one important aspect for non-interactive handling. If a handler “knows about” named restarts, as in, for example,

(when (find-restart ’new-function)
  (invoke-restart ’new-function the-replacement))

then only the first example, and not the second, will have control transferred to its correction clause, since only the first example uses a restart named new-function.

Here is a more complete example:

(let ((my-food ’milk)
      (my-color ’greenish-blue))
  (do ()
      ((not (bad-food-color-p my-food my-color)))
    (restart-case (error ’bad-food-color
                         :food my-food :color my-color)
      (use-food (new-food)
          :report "Use another food."
        (setq my-food new-food))
      (use-color (new-color)
          :report "Use another color."
        (setq my-color new-color))))
  ;; We won’t get to here until MY-FOOD
  ;; and MY-COLOR are compatible.
  (list my-food my-color))

Assuming that use-food and use-color have been defined as

(defun use-food (new-food)
  (invoke-restart ’use-food new-food))

(defun use-color (new-color)
  (invoke-restart ’use-color new-color))

a handler can then restart from the error in either of two ways. It may correct the color or correct the food. For example:

#’(lambda (c) ... (use-color ’white) ...)   ;Corrects color

#’(lambda (c) ... (use-food ’cheese) ...)   ;Corrects food

Here is an example using handler-bind and restart-case that refers to a condition type foo-error, presumably defined elsewhere:

(handler-bind ((foo-error #’(lambda (ignore) (use-value 7))))
  (restart-case (error ’foo-error)
    (use-value (x) (* x x))))
  49


[Macro] restart-bind ({(name function {keyword value}*)}*) {form}*

Executes a body of forms in a dynamic context where the given restart bindings are in effect.

Each name may be nil to indicate an anonymous restart, or some other symbol to indicate a named restart.

Each function is a form that should evaluate to a function to be used to perform the restart. If invoked, this function may either perform a non-local transfer of control or it may return normally. The function may take whatever arguments the programmer feels are appropriate; it will be invoked only if invoke-restart is used from a program, or if a user interactively asks the debugger to invoke it. In the case of interactive invocation, the :interactive-function option is used.

The valid keyword value pairs are as follows:


[Macro] with-condition-restarts condition-form restarts-form{declaration}* {form}*

The value of condition-form should be a condition C and the value of restarts-form should be a list of restarts (R1 R2 ...). The forms of the body are evaluated as an implicit progn. While in the dynamic context of the body, an attempt to find a restart associated with a particular condition C′ will consider the restarts R1, R2, if C′ is eq to C.

Usually this macro is not used explicitly in code, because restart-case handles most of the common uses in a way that is syntactically more concise.

[The X3J13 vote left it unclear whether with-condition-restarts permits declarations to appear at the heads of its body. I believe that was the intent, but this is only my interpretation.—GLS]


29.4.8 Finding and Manipulating Restarts

The following functions determine what restarts are active and invoke restarts.

[Function] compute-restarts &optional condition

Uses the dynamic state of the program to compute a list of the restarts that are currently active. See restart-bind.

If condition is nil or not supplied, all outstanding restarts are returned. If condition is not nil, only restarts associated with that condition are returned.

Each restart represents a function that can be called to perform some form of recovery action, usually a transfer of control to an outer point in the running program. Implementations are free to implement these objects in whatever manner is most convenient; the objects need have only dynamic extent (relative to the scope of the binding form that instantiates them).

The list that results from a call to compute-restarts is ordered so that the inner (that is, more recently established) restarts are nearer the head of the list.

Note, too, that compute-restarts returns all valid restarts, including anonymous ones, even if some of them have the same name as others and would therefore not be found by find-restart when given a symbol argument.

Implementations are permitted, but not required, to return different (that is, non-eq) lists from repeated calls to compute-restarts while in the same dynamic environment. It is an error to modify the list that is returned by compute-restarts.


[Function] restart-name restart

Returns the name of the given restart, or nil if it is not named.


[Function] find-restart restart-identifier &optional condition

Searches for a particular restart in the current dynamic environment.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

If the restart-identifier is a non-nil symbol, then the innermost (that is, most recently established) restart with that name is returned; nil is returned if no such restart is found.

If restart-identifier is a restart object, then it is simply returned, unless it is not currently active, in which case nil is returned.

Although anonymous restarts have a name of nil, it is an error for the symbol nil to be given as the restart-identifier. Applications that would seem to require this should be rewritten to make appropriate use of compute-restarts instead.


[Function] invoke-restart restart-identifier &rest arguments

Calls the function associated with the given restart-identifier, passing any given arguments. The restart-identifier must be a restart or the non-null name of a restart that is valid in the current dynamic context. If the argument is not valid, an error of type control-error will be signaled. ___________________________

Implementation note: Restart functions call this function, not vice versa.

___________________________________________________________________________________________________________

[Function] invoke-restart-interactively restart-identifier

Calls the function associated with the given restart-identifier, prompting for any necessary arguments. The restart-identifier must be a restart or the non-null name of a restart that is valid in the current dynamic context. If the argument is not valid, an error of type control-error will be signaled.

The function invoke-restart-interactively will prompt for arguments by executing the code provided in the :interactive keyword to restart-case or :interactive-function keyword to restart-bind.

If no :interactive or :interactive-function option has been supplied in the corresponding restart-case or restart-bind, then it is an error if the restart takes required arguments. If the arguments are optional, an empty argument list will be used in this case.

Once invoke-restart-interactively has calculated the arguments, it simply performs (apply #’invoke-restart restart-identier arguments).

invoke-restart-interactively is used internally by the debugger and may also be useful in implementing other portable, interactive debugging tools.


29.4.9 Warnings

Warnings are a subclass of errors that are conventionally regarded as “mild.”

[Function] warn datum &rest arguments

Warns about a situation, by signaling a condition of type warning.

If datum is a condition, then that condition is used directly. In this case, if the condition is not of type warning or arguments is non-nil, an error of type type-error is signaled.

If datum is a condition type (a class or class name), then the condition used is effectively the result of (apply #’make-condition datum arguments). This result must be of type warning or an error of type type-error is signaled.

If datum is a string, then the condition used is effectively the result of

(make-condition ’simple-error
                :format-string datum
                :format-arguments arguments)

The precise mechanism for warning is as follows.

  1. The warning condition is signaled.

    While the warning condition is being signaled, the muffle-warning restart is established for use by a handler to bypass further action by warn (that is, to cause warn to immediately return nil).

    As part of the signaling process, if (typep condition *break-on-signals*) is true, then a break will occur prior to beginning the signaling process.

  2. If no handlers for the warning condition are found, or if all such handlers decline, then the condition will be reported to *error-output* by the warn function (with possible implementation-specific extra output such as motion to a fresh line before or after the display of the warning, or supplying some introductory text mentioning the name of the function that called warn or the fact that this is a warning).
  3. The value returned by warn (if it returns) is nil.

29.4.10 Restart Functions

Common Lisp has the following restart functions built in.

[Function] abort &optional condition

This function transfers control to the restart named abort. If no such restart exists, abort signals an error of type control-error.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

The purpose of the abort restart is generally to allow control to return to the innermost “command level.”


[Function] continue &optional condition

This function transfers control to the restart named continue. If no such restart exists, continue returns nil.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

The continue restart is generally part of simple protocols where there is a single “obvious” way to continue, as with break and cerror. Some user-defined protocols may also wish to incorporate it for similar reasons. In general, however, it is more reliable to design a special-purpose restart with a name that better suits the particular application.


[Function] muffle-warning &optional condition

This function transfers control to the restart named muffle-warning. If no such restart exists, muffle-warning signals an error of type control-error.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

warn sets up this restart so that handlers of warning conditions have a way to tell warn that a warning has already been dealt with and that no further action is warranted.


[Function] store-value value &optional condition

This function transfers control (and one value) to the restart named store-value. If no such restart exists, store-value returns nil.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

The store-value restart is generally used by handlers trying to recover from errors of types such as cell-error or type-error, where the handler may wish to supply a replacement datum to be stored permanently.


[Function] use-value value &optional condition

This function transfers control (and one value) to the restart named use-value. If no such restart exists, use-value returns nil.

If condition is nil or not supplied, all outstanding restarts are considered. If condition is not nil, only restarts associated with that condition are considered.

The use-value restart is generally used by handlers trying to recover from errors of types such as cell-error, where the handler may wish to supply a replacement datum for one-time use.


29.4.11 Debugging Utilities

Common Lisp does not specify exactly what a debugger is or does, but it does provide certain means for indicating intent to transfer control to a supervisory or debugging facility.

[Function] break &optional format-string &rest format-arguments

The function break prints the message described by the format-string and format-arguments and then goes directly into the debugger without allowing any possibility of interception by programmed error-handling facilities.

If no format-string is supplied, a suitable default will be generated.

If continued, break returns nil.

Note that break is presumed to be used as a way of inserting temporary debugging “breakpoints” in a program, not as a way of signaling errors; it is expected that continuing from a break will not trigger any unusual recovery action. For this reason, break does not take the additional format control string that cerror takes as its first argument. This and the lack of any possibility of interception by programmed error handling are the only program-visible differences between break and cerror. The user interface aspects of these functions are permitted to vary more widely; for example, it is permissible for a read-eval-print loop to be entered by break rather than by the conventional debugger.

break could be defined by

(defun break (&optional (format-string "Break")
              &rest format-arguments)
  (with-simple-restart (continue "Return from BREAK.")
    (invoke-debugger
      (make-condition ’simple-condition
                      :format-string format-string
                      :format-arguments format-arguments)))
  nil)


[Function] invoke-debugger condition

Attempts interactive handling of its argument, which must be a condition.

If the variable *debugger-hook* is not nil, it will be called as a function on two arguments: the condition being handled and the value of *debugger-hook*. If a hook function returns normally, the standard debugger will be tried.

The standard debugger will never directly return. Return can occur only by a special transfer of control, such as the use of a restart. _____________________

Remark: The exact way in which the debugger interacts with users is expected to vary considerably from system to system. For example, some systems may use a keyboard interface, while others may use a mouse interface. Of those systems using keyboard commands, some may use single-character commands and others may use parsed line-at-a-time commands. The exact set of commands will vary as well. The important properties of a debugger are that it makes information about the error accessible and that it makes the set of apparent restarts easily accessible.

It is desirable to have a mode where the debugger allows other features, such as the ability to inspect data, stacks, etc. However, it may sometimes be appropriate to have this kind of information hidden from users. Experience on the Lisp Machines has shown that some users who are not programmers develop a terrible phobia of debuggers. The reason for this usually may be traced to the fact that the debugger is very foreign to them and provides an overwhelming amount of information of interest only to programmers. With the advent of restarts, there is a clear mechanism for the construction of “friendly” debuggers. Programmers can be taught how to get to the information they need for debugging, but it should be possible to construct user interfaces to the debugger that are natural, convenient, intelligible, and friendly even to non-programmers. ______


[Variable] *debugger-hook*

This variable should hold either nil or a function of two arguments, a condition and the value of *debugger-hook*. This function may either handle the condition (transfer control) or return normally (allowing the standard debugger to run).

Note that, to minimize recursive errors while debugging, *debugger-hook* is bound to nil when calling this function. When evaluating code typed in by the user interactively, the hook function may want to bind *debugger-hook* to the function that was its second argument so that recursive errors can be handled using the same interactive facility.