
Copyright © 1992-2008 Bruno Haible
Copyright © 1998-2008 Sam Steingold
Legal Status of the CLISP Implementation Notes
These notes are dually licensed under GNU GFDL and GNU GPL. This means that you can redistribute this document under either of these two licenses, at your choice.
These notes are covered by the GNU GFDL. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License (GFDL), either version 1.2 of the License, or (at your option) any later version published by the Free Software Foundation (FSF); with no Invariant Sections, with no Front-Cover Text, and with no Back-Cover Texts. A copy of the license is included in Appendix B, GNU Free Documentation License.
These notes are covered by the GNU GPL. This document documents free software; you can redistribute it and/or modify it under the terms of the GNU General Public License (GPL), either version 2 of the License, or (at your option) any later version published by the Free Software Foundation (FSF). A copy of the license is included in Appendix C, GNU General Public License.
Abstract
This document describes the GNU CLISP - an implementation of the [ANSI CL standard].
See the section called “Bugs” for instructions on how to report bugs (both in these notes and in CLISP itself).
See Q: A.1.1.5 for information on CLISP support.
Table of Contents
List of Figures
List of Tables
EVAL/APPLYTYPECODESHEAPCODESList of Examples
EXT:FILL-STREAM usageREGEXP:MATCHREGEXP:REGEXP-QUOTEThese notes discuss the CLISP implementation of Common Lisp by and . The current maintainers are and .
This implementation is mostly conforming to the [ANSI CL standard] available on-line as the [Common Lisp HyperSpec] (but the printed ANSI document remains the authoritative source of information). [ANSI CL standard] supersedes the earlier specifications [CLtL1] and [CLtL2].
The first part of these notes, Part I, “Chapters or the Common Lisp HyperSpec”, is indexed in parallel to the [Common Lisp HyperSpec] and documents how CLISP implements the standard [ANSI CL standard].
The second part, Part II, “Common Portable Extensions”, documents the
 common extensions to the [ANSI CL standard], specifically Meta-Object Protocol and “GRAY”
 STREAMs.
The third part, Part III, “Extensions Specific to CLISP”, documents the CLISP-specific extensions, e.g., Section 32.4, “Socket Streams”.
The fourth part, Part IV, “Internals of the CLISP Implementation”, is intended mostly
 for developers as it documents the CLISP internals, e.g., garbage-collection,
 adding new built-ins, and the bytecodes generated by the compiler
 (i.e., what is printed by DISASSEMBLE).
The following is the mark-up notations used in this document:
Table 1. Mark-up conventions
| Object Kind | Example | 
|---|---|
| Function | CAR | 
| Variable | CUSTOM:*LOAD-PATHS* | 
| Formal Argument | x | 
| Keyword | :EOF | 
| Number | 0 | 
| Character | #\Newline | 
| Class, type | REGEXP:MATCH | 
| Format instruction | ~A | 
| Standard lambda list keyword | &KEY | 
| Declaration | FTYPE | 
| Package | “COMMON-LISP-USER” | 
| Real file | config.lisp | 
| Abstract file | #P".c" | 
| Code (you are likely to type it) | ( | 
| Data (CLISP is likely to print it) | #(1 2 3) | 
| Program listing | 
(defun cycle-length (n  | 
| Bytecode instruction | (STOREV  | 
| First mention of an entity | firstterm | 
| External module | libsvm,bindings/glibc | 
Table of Contents
STREAM-ELEMENT-TYPEEXT:MAKE-STREAMREAD-BYTE,
  EXT:READ-INTEGER & EXT:READ-FLOATWRITE-BYTE,
  EXT:WRITE-INTEGER & EXT:WRITE-FLOATFILE-POSITIONEXT:ELASTIC-NEWLINEOPENCLOSEOPEN-STREAM-PBROADCAST-STREAMDISASSEMBLEEXT:UNCOMPILEDOCUMENTATIONDESCRIBETRACEINSPECTROOMTIMEEDAPROPOS & APROPOS-LISTDRIBBLELISP-IMPLEMENTATION-VERSIONEXT:ARGVTable of Contents
The final delimiter of an interactive stream:
 This final delimiter is never actually seen by programs; no need to
 test for #\^D or #\^Z - use
 READ-CHAR-NO-HANG to check for end-of-stream.
 Calling CLEAR-INPUT on the stream removes the end-of-stream state,
 thus making it available for further input.
A newline character can be entered by the user by pressing the Newline key or, on the numeric keypad, the Enter key.
Safety settings are ignored by the interpreted code;
 therefore where the standard uses the phrase “should signal an
 error”, an ERROR is SIGNALed.
 See Section 3.3.2, “Declaration SAFETY” for the safety of compiled code.
All 978 symbols in the “COMMON-LISP” package specified by the [ANSI CL standard] are implemented.
Table of Contents
The standard characters are #\Newline and the
 graphic characters
 with a CODE-CHAR between 32 and 126 (inclusive).
The requirement of step 4 that a
 “reader
  macro function may return zero values or one value”
  is enforced.  You can use the function VALUES to control the
  number of values returned.
A reserved token
  ,
 i.e., a token that has
 potential number
 syntax but cannot be interpreted as a NUMBER, is interpreted as
 SYMBOL when being read.
When a token with package markers is read, then no checking is
 done whether the SYMBOL-PACKAGE part and the SYMBOL-NAME part do
 not have number syntax. (What would the purpose of this check be?)
 So we consider tokens like USER:: or :1 or
 LISP::4711 or 21:3 as symbols.
The backquote read macro also works when nested. Example:
(EVAL``(,#'(LAMBDA() ',a) ,#'(LAMBDA() ',b))) ≡ (EVAL`(list #'(LAMBDA() ',a) #'(LAMBDA() ',b))) ≡ (EVAL(list 'list (list 'function (list 'lambda nil (list 'quote a))) (list 'function (list 'lambda nil (list 'quote b)))))
Reader macros are also defined for the following:
Additional reader macros
FUNCTION objects and input STREAM's EXT:ENCODINGs
 PATHNAME: #"test.lisp"
   is the value of (PATHNAME "test.lisp")#\Code allows input of characters of arbitrary code:
 e.g., #\Code231 reads as the character
 (.CODE-CHAR 231)
This is the list of objects whose external representation cannot be meaningfully read in:
Unreadable objects
#<type ...>STRUCTURE-OBJECTs lacking a keyword
   constructor#<ARRAY type
   dimensions>ARRAYs except STRINGs, if
   *PRINT-ARRAY* is NIL#<SYSTEM-FUNCTION
   name>#<ADD-ON-SYSTEM-FUNCTION
   name>#<SPECIAL-OPERATOR
   name>#<COMPILED-CLOSURE
   name>CUSTOM:*PRINT-CLOSURE* is NIL
#<CLOSURE name ...>#<FRAME-POINTER #x...>#<DISABLED POINTER>BLOCK or TAGBODY#<...STREAM...>STREAM#<PACKAGE name>PACKAGE#<HASH-TABLE #x...>HASH-TABLE, if *PRINT-ARRAY* is NIL
#<READTABLE #x...>READTABLE#<SYMBOL-MACRO
   form>SYMBOL-MACRO handler#<MACRO function>DEFMACRO and friends)
#<FFI:FOREIGN-POINTER
   #x...>#<FFI:FOREIGN-ADDRESS
   #x...>#<FFI:FOREIGN-VARIABLE name
   #x...>#<FFI:FOREIGN-FUNCTION name
   #x...>#<UNBOUND>#<SPECIAL REFERENCE>SPECIAL
#<DOT>READ result for “.”
#<END OF FILE>READ result, when the end-of-stream is reached
#<READ-LABEL ...>READ result for #n#
#<ADDRESS #x...>#<SYSTEM-POINTER #x...>Table of Contents
All the functions built by FUNCTION, COMPILE and the like are
 atoms.  There are built-in functions written in C, compiled
 functions (both of type COMPILED-FUNCTION) and interpreted
 functions (of type FUNCTION).
Macro EXT:THE-ENVIRONMENT. As in Scheme, the macro (
 returns the current lexical environment.  This works only in interpreted code and
 is not compilable!EXT:THE-ENVIRONMENT)
Function (EXT:EVAL-ENV
 . evaluates a form in a given lexical environment, just as if the
 form had been a part of the program that the form &OPTIONAL environment)environment came from.
“Undefined variables”, i.e. variables which are
 referenced outside any lexical binding for a variable of the same name
 and which are not declared SPECIAL, are treated like dynamic variables
 in the global environment.  The compiler SIGNALs a WARNING when it
 encounters an undefined variable.
Lists of the form (( are also
 treated as function forms. This makes the syntax
 SETF symbol) ...)( consistent with the syntax
 function-name arguments ...)(.
 It implements the item 7 of the [ANSI CL standard] issue FUNCTION-NAME:LARGE and the definition of
 function forms,
 and is consistent with the use of function names elsewhere in Common Lisp.
FUNCALL #'function-name arguments ...)
Compiler macros are expanded in the compiled code only, and ignored by the interpreter.
When a DEFUN form is EVALuated, the macros used there are
 expanded, so they must be already defined, and their (re)definition
 does not affect functions which are already defined.
This means that even the interpreted code is minimally compiled in CLISP.
Non-conforming code that does not follow the rule
“Special proclamations for dynamic variables must be made in the compilation environment.”
can produce quite unexpected results, e.g., observable differences between compiled and interpreted programs:
(defun adder-c (value) (declare ((COMPILE))) (lambda (x) (+ x value))) ⇒ADDER-C; compiled function;valueis lexical (defun adder-i (value) (lambda (x) (+ x value))) ⇒ADDER-I; interpreted function;valueis lexical (setq add-c-10 (adder-c 10)) ⇒ADD-C-10; compiled function (setq add-i-10 (adder-i 10)) ⇒ADD-I-10; interpreted function (funcall add-c-10 32) ⇒42; as expected (funcall add-i-10 32) ⇒42; as expected (defvar value 12) ⇒VALUE; affectsADDER-IandADD-I-10but notADDER-CandADD-C-10(funcall add-c-10 32) ⇒42; as before (funcall add-i-10 32) ⇒44;valueis now dynamic!
Non-conformance. The code shown above has a SPECIAL proclamation (by DEFVAR)
 for the variable value in the execution environment
 (before the last two FUNCALLs)
 but not in the compilation environment: at the moment
 the ADDER-I function is defined,
 value is not known to be a SPECIAL variable.
 Therefore the code is not conforming.
The function ADD-C-10 was compiled before
 value was declared SPECIAL, so the symbol value was
 eliminated from its code and the SPECIAL declaration did
 not affect the return value (i.e., (funcall
  add-c-10 32) always returned 42).
On the opposite, function ADDER-I was not
 compiled, so ADD-I-10
 was interpreted.
 Whenever ADD-I-10 is executed, its definition is
 interpreted all over again.  Before DEFVAR, value is evaluated as
 a lexical (because is is not declared SPECIAL yet), but after
 DEFVAR, we see a globally SPECIAL symbol value which
 can have only a global SYMBOL-VALUE (not a local binding), and thus
 we are compelled to evaluate it to 12.
This behavior was implemented intentionally to ease interactive
 development, because usually
 the ADDER-I above would be followed by a
 (forgotten) DEFVAR.
When a user compiles a program, the compiler is allowed to
 remember the information whether a variable was SPECIAL or not,
 because that allows the compiler to generate more efficient code,
 but in interpreted code, when the user changes the state of a variable,
 he does not want to re-evaluate all DEFUNs that use the variable.
[ANSI CL standard] gives the implementation freedom regarding interpreted evaluation, how much it wants to remember / cache, and how much it wants to evaluate according the current environment, if the environment has changed. CLISP implements ad-hoc look-up for variables (but not for macros, see Section 3.2.2.2, “Minimal Compilation [CLHS-3.2.2.2]”).
Hash tables are externalizable objects.
The declarations (,
 TYPE type variable ...)(,
   are ignored by both the interpreter and the compiler.FTYPE type function ...)
SPECIALDeclaration EXT:NOTSPECIAL. Declarations (
 and PROCLAIM '(SPECIAL variable))DEFCONSTANT are undone by the ( declaration.  This declaration can be used only in
 global PROCLAIM '(EXT:NOTSPECIAL
  variable))PROCLAIM and DECLAIM forms, not in local DECLARE forms.
 Of course, you cannot expect miracles: functions compiled before the
 EXT:NOTSPECIAL proclamation was issued will still be treating variable as
 special even after the EXT:NOTSPECIAL proclamation.
Function EXT:SPECIAL-VARIABLE-P. You can use the function ( to check whether the symbol is a
 special variable.  EXT:SPECIAL-VARIABLE-P symbol
  &OPTIONAL environment)environment of NIL or omitted means use the global environment.
 You can also obtain the current lexical environment using the macro
 EXT:THE-ENVIRONMENT (interpreted code only).
 This function will always return T for global special
 variables and constant variables.
SAFETYDeclaration (
 results in “safe” compiled code: function calls are never
 eliminated. This guarantees the semantics described in [ANSI CL standard]
 Section 3.5.
OPTIMIZE (SAFETY 3))
(COMPILE)The declaration (COMPILE) has the effect that the current
 form is compiled prior to execution.  Examples:
(LOCALLY(DECLARE(compile))form)
executes a compiled version of form.
(LET((x 0)) (FLET((inc () (DECLARE(compile)) (INCFx)) (dec () (DECFx))) (VALUES#'inc #'dec)))
 returns two functions.  The first is compiled and increments x, the
 second is interpreted (slower) and decrements the same x.
SPACEThe declaration determines what metadata is recorded in the function object:
The initial value of an &AUX variable in a boa lambda list is
 the value of the corresponding slot's initial form.
CONSTANTPFunction CONSTANTP fully complies with [ANSI CL standard].
Additionally, some non-trivial forms are identified as constants, e.g.,
( returns CONSTANTP '(+ 1 2 3))T.
Since DEFCONSTANT initial value forms are not
evaluated at compile time, CONSTANTP will not report T of their
name within the same compilation unit for the null lexical environment.  This is
consistent and matches questionable code using the pattern
(if (.  Use
CONSTANTP form) (EVAL form))EVAL-WHEN if you need recognition and the value during
compile-time.
EVAL-WHENEVAL-WHEN also accepts the situations (NOT EVAL)
 and (NOT COMPILE).
The situations EVAL,
 LOAD and COMPILE are
 deprecated by the [ANSI CL standard], and they are not equivalent to the new
 standard situations :EXECUTE,
 :LOAD-TOPLEVEL
 and :COMPILE-TOPLEVEL in that they ignore the
 top-level form versus non-top-level form distinction.
THEThe special form ( is
 similar to THE value-type form)CHECK-TYPE but does a type check only in interpreted
 code (no type check is done in compiled code - but see the EXT:ETHE
 macro) and does not allow interactive error correction by the user.
Table of Contents
The general form of the COMPLEX type specifier is (.  The type
 specifier COMPLEX type-of-real-part
 type-of-imaginary-part)( is
 equivalent to COMPLEX type)(.COMPLEX type
 type)
DEFTYPE lambda lists are subject to destructuring (nested lambda lists
 are allowed, as in DEFMACRO) and may contain a &WHOLE marker,
 but not an &ENVIRONMENT marker.
Function (. If EXT:TYPE-EXPAND
   typespec &OPTIONAL
   once-p)typespec is a user-defined type,
 this will expand it recursively until it is no longer a user-defined
 type (unless once-p is supplied and
 non-NIL).  Two values are returned - the expansion and an indicator
 (T or NIL) of whether the original
 typespec was a user-defined type.
The possible results of TYPE-OF
CONSSYMBOL, NULL, BOOLEAN,
  KEYWORDBIT, (INTEGER 0
    #.MOST-POSITIVE-FIXNUM),
   (INTEGER
    #.MOST-NEGATIVE-FIXNUM (0)),
   (INTEGER
    (#.MOST-POSITIVE-FIXNUM)),
   (INTEGER *
    (#.MOST-NEGATIVE-FIXNUM))RATIONAL, SHORT-FLOAT, SINGLE-FLOAT,
   DOUBLE-FLOAT, LONG-FLOAT, COMPLEXCHARACTER, BASE-CHAR,
   STANDARD-CHAR(ARRAY element-type
    dimensions), (SIMPLE-ARRAY
    element-type dimensions)(VECTOR T
    size), (SIMPLE-VECTOR
    size)(STRING
    size), (SIMPLE-STRING
    size)(BASE-STRING
    size), (SIMPLE-BASE-STRING
    size)(BIT-VECTOR
    size), (SIMPLE-BIT-VECTOR
    size)FUNCTION, COMPILED-FUNCTION,
   STANDARD-GENERIC-FUNCTIONSTREAM, FILE-STREAM, SYNONYM-STREAM,
   BROADCAST-STREAM, CONCATENATED-STREAM, TWO-WAY-STREAM,
   ECHO-STREAM, STRING-STREAMPACKAGE, HASH-TABLE, READTABLE, PATHNAME,
   LOGICAL-PATHNAME, RANDOM-STATE, BYTESPECIAL-OPERATOR,
   LOAD-TIME-EVAL, SYMBOL-MACRO,
   GLOBAL-SYMBOL-MACRO, EXT:ENCODING,
   FFI:FOREIGN-POINTER, FFI:FOREIGN-ADDRESS, FFI:FOREIGN-VARIABLE,
   FFI:FOREIGN-FUNCTIONEXT:WEAK-POINTER, EXT:WEAK-LIST, EXT:WEAK-AND-RELATION,
   EXT:WEAK-OR-RELATION, EXT:WEAK-MAPPING, EXT:WEAK-AND-MAPPING,
   EXT:WEAK-OR-MAPPING, EXT:WEAK-ALIST,
   READ-LABEL,
   FRAME-POINTER,
   SYSTEM-INTERNALADDRESS (should not
  occur)SYMBOL (structure types or CLOS
  classes)The CLOS symbols are EXPORTed from the package “CLOS”.
 “COMMON-LISP” uses (as in USE-PACKAGE) “CLOS” and EXT:RE-EXPORTs the
 [ANSI CL standard] standard exported symbols (the CLISP extensions, e.g.,
 those described in Chapter 29, Meta-Object Protocol, are not EXT:RE-EXPORTed).
 Since the default :USE argument
 to MAKE-PACKAGE is “COMMON-LISP”, the standard CLOS symbols are normally
 visible in all user-defined packages.
 If you do not want them (for example, if you want to use the
 PCL
 implementation of CLOS instead of the native one), do the following:
(DEFPACKAGE"CL-NO-CLOS" (:use "CL")) (DO-EXTERNAL-SYMBOLS(symbol“COMMON-LISP”) (SHADOWsymbol"CL-NO-CLOS")) (DO-SYMBOLS(symbol"CL-NO-CLOS") (EXPORTsymbol"CL-NO-CLOS")) (IN-PACKAGE"CL-NO-CLOS") (LOAD"pcl") ; or whatever (DEFPACKAGE"MY-USER" (:use "CL-NO-CLOS")) (IN-PACKAGE"MY-USER") ;; your code which uses PCL goes here
DEFCLASS supports the option :METACLASS STRUCTURE-CLASS.
 This option is necessary in order to define a subclass of a
 DEFSTRUCT-defined structure type using DEFCLASS instead of
 DEFSTRUCT.
When CALL-NEXT-METHOD is called with arguments, the rule that
 the ordered set of applicable methods must be the same as for the
 original arguments is enforced by the implementation only in
 interpreted code.
CLOS:GENERIC-FLET and
 CLOS:GENERIC-LABELS
 are implemented as macros, not as special operators (as permitted by
 Section 3.1.2.1.2.2).
 They are not imported into the packages “COMMON-LISP-USER” and “COMMON-LISP” because
 of the [ANSI CL standard] issue GENERIC-FLET-POORLY-DESIGNED:DELETE.
PRINT-OBJECT is only called on objects of type
 STANDARD-OBJECT and STRUCTURE-OBJECT.
 It is not called on other objects, like CONSes
 and NUMBERs, due to the performance concerns.
Among those classes listed in Figure
 4-8, only the following are instances of BUILT-IN-CLASS:
TCHARACTERNUMBER, COMPLEX, REAL, FLOAT,
   RATIONAL, RATIO, INTEGERSEQUENCEARRAY, VECTOR, BIT-VECTOR,
   STRINGLIST, CONSSYMBOL, NULLFUNCTION, GENERIC-FUNCTION,
   STANDARD-GENERIC-FUNCTIONHASH-TABLEPACKAGEPATHNAME, LOGICAL-PATHNAME
 RANDOM-STATEREADTABLESTREAM, BROADCAST-STREAM,
   CONCATENATED-STREAM, ECHO-STREAM, STRING-STREAM,
   FILE-STREAM, SYNONYM-STREAM, TWO-WAY-STREAM
 DEFCLASS supports the :METACLASS option.  Possible values are
 STANDARD-CLASS (the default), STRUCTURE-CLASS (which creates
 structure classes, like DEFSTRUCT does), and user-defined
 meta-classes (see Section 29.3.6.7, “Generic Function CLOS:VALIDATE-SUPERCLASS”).
It is not required that the superclasses of a class are
 defined before the DEFCLASS form for the class is evaluated.
 Use Meta-Object Protocol generic functions CLOS:CLASS-FINALIZED-P to check whether the
 class has been finalized and thus its instances can be created,
 and CLOS:FINALIZE-INHERITANCE to force class finalization.
See also Section 29.3.1, “Macro DEFCLASS”.
Trivial changes, e.g., those that can occur when doubly loading
 the same code, do not require updating the instances.
 These are the changes that do not modify the set of local slots
 accessible in instances, e.g., changes to slot options :INITFORM,
 :DOCUMENTATION, and changes to class options
 :DEFAULT-INITARGS, :DOCUMENTATION.
The instances are updated when they are first accessed, not at
 the time when the class is redefined or MAKE-INSTANCES-OBSOLETE is
 called.  When the class has been redefined several times since the
 instance was last accessed, UPDATE-INSTANCE-FOR-REDEFINED-CLASS is
 still called just once.
COERCEFIXNUM is not a character
  designator in [ANSI CL standard], although CODE-CHAR provides an
  obvious venue to COERCE a FIXNUM to a CHARACTER.
  When CUSTOM:*COERCE-FIXNUM-CHAR-ANSI* is NIL, CLISP COERCEs FIXNUMs to
  CHARACTERs via CODE-CHAR.
  When CUSTOM:*COERCE-FIXNUM-CHAR-ANSI* is non-NIL, FIXNUMs cannot be
  COERCEd to CHARACTERs.
Table of Contents
Function FUNCTION-LAMBDA-EXPRESSION. The name of a FFI:FOREIGN-FUNCTION is a string
(the name of the underlying C function), not a lisp function name.
Macro DESTRUCTURING-BIND. This macro does not perform full error checking.
Macros PROG1, PROG2, AND,
 OR, PSETQ, WHEN, UNLESS, COND, CASE, MULTIPLE-VALUE-LIST,
  MULTIPLE-VALUE-BIND, MULTIPLE-VALUE-SETQ. These macros are implemented as special operators (as permitted by
 Section 3.1.2.1.2.2)
 and, as such, are rather efficient.
DEFCONSTANTThe initial value is not evaluated at compile time,
 just like with DEFVAR and DEFPARAMETER.
 Use EVAL-WHEN if you need the value at compile time.
If the variable is already bound to a value which is not EQL to
 the new value, a WARNING is issued.
constant variables may not be bound dynamically or lexically.
EXT:FCASEThis macro allows specifying the test for CASE, e.g.,
(fcase string= (subseq foo 0 (position #\Space foo))
  ("first" 1)
  (("second" "two") 2)
  (("true" "yes") t)
  (otherwise nil))
is the same as
(let ((var (subseq foo 0 (position #\Space foo))))
  (cond ((string= var "first") 1)
        ((or (string= var "second") (string= var "two")) 2)
        ((or (string= var "true") (string= var "yes")) t)
        (t nil)))
If you use a built-in HASH-TABLE test (see Section 18.1.3, “Function HASH-TABLE-TEST”)
as the test (e.g., EQUAL instead of STRING= above, but not a test
defined using EXT:DEFINE-HASH-TABLE-TEST), the compiler will be able to optimize the
EXT:FCASE form better than the corresponding COND form.
This function checks that exactly one of its arguments is non-NIL
 and, if this is the case, returns its value and index in the argument
 list as multiple values, otherwise returns NIL.
EQEQ compares CHARACTERs and FIXNUMs as EQL does.
 No unnecessary copies are made of CHARACTERs and NUMBERs.
 Nevertheless, one should use EQL as it is more portable across Common Lisp
 implementations.
( always
 returns LET ((x y)) (EQ x x))T, regardless of y.
See also Equality of foreign values..
SYMBOL-FUNCTION(
 requires SETF (SYMBOL-FUNCTION symbol) object)object to be either a function, a SYMBOL-FUNCTION return
 value, or a lambda expression.  The lambda expression is thereby immediately
 converted to a FUNCTION.
SETFAdditional places:
FUNCALL(SETF (FUNCALL #'symbol ...)
     object) and
    (SETF (FUNCALL 'symbol ...) object)
    are equivalent to (SETF (symbol ...) object).
 PROGN(SETF (PROGN form ... place)
     object)LOCALLY(SETF (LOCALLY declaration ...
     form ... place) object)
  IF(SETF (IF condition
     place1
     place2)
     object)GET-DISPATCH-MACRO-CHARACTER(SETF (GET-DISPATCH-MACRO-CHARACTER ...)
     ...) calls SET-DISPATCH-MACRO-CHARACTER.
 EXT:LONG-FLOAT-DIGITS:(SETF (EXT:LONG-FLOAT-DIGITS) digits) sets the
    default mantissa length of LONG-FLOATs to digits bits.
 VALUES-LIST(
    is equivalent to SETF (VALUES-LIST list) form)(.VALUES-LIST (SETF list
     (MULTIPLE-VALUE-LIST form)))
&KEY markers in DEFSETF lambda lists are supported, but the
 corresponding keywords must appear literally in the program text.
(,
 GET-SETF-EXPANSION form &OPTIONAL environment)(EXT:GET-SETF-METHOD , and
 form &OPTIONAL environment)(EXT:GET-SETF-METHOD-MULTIPLE-VALUE  receive as optional argument form &OPTIONAL
  environment)environment the environment
  necessary for macro expansions. In DEFINE-SETF-EXPANDER
  and EXT:DEFINE-SETF-METHOD lambda lists, one can
  specify &ENVIRONMENT and a variable, which will be bound to the
  environment.  This environment should be passed to all calls of
  GET-SETF-EXPANSION, EXT:GET-SETF-METHOD and
 EXT:GET-SETF-METHOD-MULTIPLE-VALUE.  If this is
 done, even local macros will be interpreted as places correctly.
An attempt to modify read-only data SIGNALs an ERROR.
 Program text and quoted constants loaded from files are considered
 read-only data.  This check is only performed for strings, not for
 conses, other kinds of arrays, and user-defined data types.
FUNCTION( returns the local function
 definition established by FUNCTION symbol)FLET or LABELS, if it exists, otherwise
 the global function definition.
( returns SPECIAL-OPERATOR-P symbol)NIL or
 T.  If it returns T, then ( returns the (useless) special operator handler.SYMBOL-FUNCTION
  symbol)
DEFINE-SYMBOL-MACROThe macro DEFINE-SYMBOL-MACRO establishes SYMBOL-MACROs with
 global scope (as opposed to SYMBOL-MACROs defined with
 SYMBOL-MACROLET, which have local scope).
The function
 EXT:SYMBOL-MACRO-EXPAND
 tests for a SYMBOL-MACRO: If symbol is defined as a SYMBOL-MACRO
 in the global environment, ( returns two
 values, EXT:SYMBOL-MACRO-EXPAND symbol)T and the expansion; otherwise it returns NIL.
EXT:SYMBOL-MACRO-EXPAND is a special case of MACROEXPAND-1. MACROEXPAND-1
 can also test whether a symbol is defined as a SYMBOL-MACRO in lexical environments
 other than the global environment.
LAMBDAConstant LAMBDA-LIST-KEYWORDS. (&OPTIONAL &REST &KEY &ALLOW-OTHER-KEYS
  &AUX &BODY &WHOLE &ENVIRONMENT)
Table 5.1. Function call limits
| CALL-ARGUMENTS-LIMIT | 212=4096 | 
| MULTIPLE-VALUES-LIMIT | 27=128 | 
| LAMBDA-PARAMETERS-LIMIT | 212=4096 | 
DEFUN and DEFMACRO are allowed in non-toplevel positions. As
 an example, consider the old ([CLtL1]) definition of GENSYM:
(let ((gensym-prefix "G")
      (gensym-count 1))
  (defun gensym (&optional (x nil s))
    (when s
      (cond ((stringp x) (setq gensym-prefix x))
            ((integerp x)
             (if (minusp x)
               (error "~S: index ~S is negative" 'gensym x)
               (setq gensym-count x)))
            (t (error "~S: argument ~S of wrong type" 'gensym x))))
    (prog1
      (make-symbol
        (concatenate 'string
          gensym-prefix
          (write-to-string gensym-count :base 10 :radix nil)))
      (incf gensym-count))))
See also Section 3.2.2.2, “Minimal Compilation [CLHS-3.2.2.2]”.
Function EXT:ARGLIST. Function ( returns the lambda list of
 the function or macro that EXT:ARGLIST name)name names and SIGNALs an ERROR if name is
 not FBOUNDP.  It also SIGNALs an ERROR when the macro lambda list is not
 available due to the compiler optimization settings
 (see Section 3.3.4, “Declaration SPACE”).
Variable CUSTOM:*SUPPRESS-CHECK-REDEFINITION*. When CUSTOM:*SUPPRESS-CHECK-REDEFINITION* is NIL,
 CLISP issues a WARNING when a function (macro, variable, class,
 etc) is redefined in a different file than its original definition.
 It is not a good idea to set this variable to T.
Variable CUSTOM:*DEFUN-ACCEPT-SPECIALIZED-LAMBDA-LIST*. When CUSTOM:*DEFUN-ACCEPT-SPECIALIZED-LAMBDA-LIST* is
non-NIL, DEFUN accepts specialized lambda lists, converting type-parameter
associations to type declarations:
(defun f ((x list) (y integer)) ...)
is equivalent to
(defun f (x y) (declare (type list x) (type integer y)) ...)
This extension is disabled by -ansi and by setting CUSTOM:*ANSI* to T,
but can be re-enabled by setting CUSTOM:*DEFUN-ACCEPT-SPECIALIZED-LAMBDA-LIST* explicitly.
Table of Contents
The standard is unambiguous in that the iteration variables do
 still exist in the FINALLY clause, but not as to what values
 these variables might have.
 Therefore the code which relies on the values of such variables, e.g.,
 
(loop for x on y finally (return x))
is inherently non-portable across Common Lisp implementations, and should be avoided.
There have been some tightening in the LOOP syntax between
 [CLtL2] and [ANSI CL standard], e.g., the following form is legal in the
 former but not the latter:
(loop initially for i from 1 to 5 do (print i) finally return i)
When CUSTOM:*LOOP-ANSI* is NIL, such forms are still
accepted in CLISP but elicit a warning at macro-expansion time.
When CUSTOM:*LOOP-ANSI* is non-NIL, an ERROR is SIGNALed.
The macros DOLIST and DOTIMES establish a single binding for
the iteration variable and assign it on each iteration.
Table of Contents
Generic function
 CLOS:NO-PRIMARY-METHOD
 (similar to NO-APPLICABLE-METHOD) is called when there is an
 applicable method but no applicable primary
 method.
The default methods for CLOS:NO-PRIMARY-METHOD, NO-APPLICABLE-METHOD and
 NO-NEXT-METHOD SIGNAL an ERROR of type
 CLOS:METHOD-CALL-ERROR
  .
 You can find out more information about the error using functions
 CLOS:METHOD-CALL-ERROR-GENERIC-FUNCTION,
 CLOS:METHOD-CALL-ERROR-ARGUMENT-LIST, and
 (only for NO-NEXT-METHOD)
 CLOS:METHOD-CALL-ERROR-METHOD.
 Moreover, when the generic function has only one dispatching
 argument, (i.e., such an argument that not all the
 corresponding parameter specializers are T), an ERROR of type
 CLOS:METHOD-CALL-TYPE-ERROR
  
  is SIGNALed, additionally making TYPE-ERROR-DATUM and
  TYPE-ERROR-EXPECTED-TYPE available.
Table of Contents
DEFSTRUCT.The :PRINT-FUNCTION option should contain a lambda expression
 (
 This lambda expression names a LAMBDA (object stream depth) (declare (ignore depth)) ...)FUNCTION whose task is to output the
 external representation of the STRUCTURE-OBJECT object onto the
 STREAM stream. This may be done by outputting text onto the
 stream using WRITE-CHAR, WRITE-STRING, WRITE, PRIN1, PRINC,
 PRINT, PPRINT, FORMAT and the like.
 The following rules must be obeyed:
*PRINT-ESCAPE* must be
  respected.*PRINT-PRETTY* is up to you.
 *PRINT-CIRCLE* need not be
  respected.  This is managed by the system.  (But the print-circle
  mechanism handles only those objects that are direct or indirect
  components of the structure.)*PRINT-LEVEL* is respected by
  WRITE, PRIN1, PRINC, PRINT, PPRINT, FORMAT instructions
  ~A, ~S, ~W, and FORMAT instructions
  ~R, ~D, ~B, ~O, ~X, ~F,
  ~E, ~G, ~$ with not-numerical arguments.
  Therefore the print-level mechanism works automatically if only these
  functions are used for outputting objects and if they are not called
  on objects with nesting level > 1. (The print-level mechanism does
  not recognize how many parentheses you have output. It only counts how
  many times it was called recursively.)*PRINT-LENGTH* must be respected,
  especially if you are outputting an arbitrary number of components.
 *PRINT-READABLY* must be
  respected. Remember that the values of *PRINT-ESCAPE*,
  *PRINT-LEVEL*, *PRINT-LENGTH* are ignored if
  *PRINT-READABLY* is true.  The value of *PRINT-READABLY* is
  respected by PRINT-UNREADABLE-OBJECT, WRITE, PRIN1, PRINC,
  PRINT, PPRINT, FORMAT instructions ~A, ~S,
  ~W, and FORMAT instructions ~R, ~D,
  ~B, ~O, ~X, ~F, ~E,
  ~G, ~$ with not-numerical arguments.  Therefore
  *PRINT-READABLY* will be respected automatically if only these
  functions are used for printing objects.*PRINT-BASE*, *PRINT-RADIX*, *PRINT-CASE*,
  *PRINT-GENSYM*, *PRINT-ARRAY*, CUSTOM:*PRINT-CLOSURE*,
  CUSTOM:*PRINT-RPARS*, CUSTOM:*PRINT-INDENT-LISTS*.The :INHERIT option is exactly like :INCLUDE except that it
 does not create new accessors for the inherited slots (this is a
 CLISP extension).
The following functions accept a structure name as the only argument.
 If DEFSTRUCT was given the :TYPE option (i.e., DEFSTRUCT did
 not define a new type), then (
 fails (and the regular CLOS Meta-Object Protocol is not applicable), but these
 functions still work.FIND-CLASS name)
EXT:STRUCTURE-SLOTSLIST of effective slot definition metaobjects.
EXT:STRUCTURE-DIRECT-SLOTSLIST of direct slot definition metaobjects.
EXT:STRUCTURE-KEYWORD-CONSTRUCTORSYMBOL) of the keyword
   constructor function for the structure, or NIL if the structure has
   no keyword constructor.EXT:STRUCTURE-BOA-CONSTRUCTORSLIST of names (SYMBOLs)
  of BOA constructors for the structure.EXT:STRUCTURE-COPIERSYMBOL) of the copier for the
   structure.EXT:STRUCTURE-PREDICATESYMBOL) of the predicate for
   the structure.Table of Contents
When an error occurred, you are in a break loop. You can evaluate forms as usual. The help command (or help key if there is one) lists the available debugging commands.
Macro EXT:MUFFLE-CERRORS. The macro (
 executes the EXT:MUFFLE-CERRORS {form}*)forms; when a continuable ERROR occurs whose CONTINUE RESTART
 can be invoked non-interactively (this includes all continuable ERRORs signaled
 by the function CERROR), no message is printed, instead, the CONTINUE
 RESTART is invoked.
Macro EXT:APPEASE-CERRORS. The macro (
 executes the EXT:APPEASE-CERRORS {form}*)forms; when a continuable ERROR occurs whose CONTINUE RESTART
 can be invoked non-interactively (this includes all continuable ERRORs SIGNALed
 by the function CERROR), it is reported as a WARNING, and the
 CONTINUE RESTART is invoked.
Macro EXT:ABORT-ON-ERROR. The macro (
 executes the EXT:ABORT-ON-ERROR {form}*)forms; when an ERROR occurs,
 or when a Control+C interrupt occurs,
 the error message is printed and the ABORT RESTART is invoked.
Macro EXT:EXIT-ON-ERROR. The macro (
 executes the EXT:EXIT-ON-ERROR {form}*)forms; when an ERROR occurs,
 or when a Control+C interrupt occurs,
 the error message is printed and CLISP terminates with an error status.
Variable CUSTOM:*REPORT-ERROR-PRINT-BACKTRACE*. When this variable is non-NIL the error message printed by
 EXT:ABORT-ON-ERROR and EXT:EXIT-ON-ERROR includes the backtrace (stack).
Function EXT:SET-GLOBAL-HANDLER. The function (
 establishes a global handler for the EXT:SET-GLOBAL-HANDLER condition handler)condition.
 The handler should be FUNCALLable (a
 SYMBOL or a FUNCTION).  If it returns, the next applicable
 handler is invoked, so if you do not want to land in the debugger, it
 should not return.
 E.g., the option -on-error abort and the macro
 EXT:ABORT-ON-ERROR are implemented by installing the following handler:
 
(defun sys::abortonerror (condition) (sys::report-error condition) (INVOKE-RESTART(FIND-RESTART'ABORTcondition)))
 When handler is NIL, the handler
 for condition is removed and returned.
 When condition is also NIL, all global handlers are removed and returned
 as a LIST, which can then be passed to EXT:SET-GLOBAL-HANDLER as the
 first argument and the handlers re-established.
Macro EXT:WITHOUT-GLOBAL-HANDLERS. The macro ( removes all global handlers, executes EXT:WITHOUT-GLOBAL-HANDLERS &BODY
  body)body, and
 then restores the handlers.
Macro EXT:WITH-RESTARTS. The macro EXT:WITH-RESTARTS is like RESTART-CASE, except that the
 forms are specified after the restart clauses instead of before them,
 and the restarts created are not implicitly associated with any CONDITION.
 ( is
 therefore equivalent to EXT:WITH-RESTARTS ({restart-clause}*) {form}*)(.RESTART-CASE (PROGN {form}*)
 {restart-clause}*)
The error message prefix for the first line is “*** - ”.
 All subsequent lines are indented by 6 characters.
 Long lines are broken on whitespace
 (see Section 30.2, “Class EXT:FILL-STREAM”).
Macro RESTART-CASE. In (,
  the argument list can also be specified after the keyword/value pairs
  instead of before them, i.e., each RESTART-CASE form {restart-clause}*)restart-clause can be either
  (
  or restart-name EXT:*ARGS*
   {keyword-value-pair}* {form}*)(.
restart-name
   {keyword-value-pair}* EXT:*ARGS* {form}*)
Function COMPUTE-RESTARTS. COMPUTE-RESTARTS and FIND-RESTART behave as specified in
 [ANSI CL standard]: If the optional condition argument is non-NIL,
 only RESTARTs associated with that CONDITION
 and RESTARTs associated with no CONDITION at all are considered.
 Therefore the effect of associating a restart to a condition is not to
 activate it, but to hide it from other conditions.
 This makes the syntax-dependent implicit association performed by
 RESTART-CASE nearly obsolete.
No notes.
Table of Contents
The [ANSI CL standard] packages present in CLISP
Function EXT:PACKAGE-LOCK. 
 Packages can be “locked”.
When a package is locked, attempts to change its symbol table or
redefine functions which its symbols name result in a continuable ERROR
(continuing overrides locking for this operation).
When CUSTOM:*SUPPRESS-CHECK-REDEFINITION* is T (not a good idea!), the ERROR
is not SIGNALed for redefine operations.
Function (
returns the generalized boolean indicating whether the EXT:PACKAGE-LOCK package)package is locked.
A package (or a list thereof) can be locked using (.
CLISP locks its system packages (specified in the variable
SETF
 (EXT:PACKAGE-LOCK package-or-list) T)CUSTOM:*SYSTEM-PACKAGE-LIST*).
Macro EXT:WITHOUT-PACKAGE-LOCK. If you want to evaluate some forms with certain packages unlocked,
 you can use
 EXT:WITHOUT-PACKAGE-LOCK
  :
(EXT:WITHOUT-PACKAGE-LOCK (“COMMON-LISP” “EXT” “CLOS”)
  (defun restart () ...))
or
(EXT:WITHOUT-PACKAGE-LOCK (“COMMON-LISP”) (trace read-line))
(
temporarily unlocks all packages in EXT:WITHOUT-PACKAGE-LOCK () ...)CUSTOM:*SYSTEM-PACKAGE-LIST*.
Variable CUSTOM:*SYSTEM-PACKAGE-LIST*. This variable specifies the default packages to be locked by EXT:SAVEINITMEM
 and unlocked by EXT:WITHOUT-PACKAGE-LOCK as a list of package names.
 You may add names to this list, e.g., a module will add its package,
 but you should not remove CLISP internal packages from this list.
Discussion - see also the USENET posting by . This should prevent you from accidentally hosing yourself with
(DEFSTRUCT instance ...)
and allow enforcing modularity.
Note that you will also get the continuable ERROR when you try to
assign (with SETQ, PSETQ, etc.) a value to an internal special
variable living in a locked package and not accessible in your current
*PACKAGE*, but only in the interpreted code and during compilation.
There is no check for package locks in compiled code because of the
performance considerations.
The “COMMON-LISP-USER” package uses the “COMMON-LISP” and “EXT” packages.
The following additional packages exist:
Implementation-Defined Packages
EXPORTs all CLOS-specific symbols, including some
    additional symbols.
 EXPORTed symbols.  It defines many system internals.
 EXT:RE-EXPORTs
    all the external symbols in all CLISP extensions, so a simple
    (USE-PACKAGE "EXT") is enough to
    make all the extensions available in the current package.
    This package uses packages (in addition to “COMMON-LISP”):
    “LDAP”, “POSIX”, “SOCKET”, “GSTREAM”, “GRAY”,
    “I18N”, “CUSTOM”.EXPORTs some character sets, for use with
    EXT:MAKE-ENCODING and as :EXTERNAL-FORMAT argument.
 All pre-existing packages except “COMMON-LISP-USER” belong to the implementation, in the sense that the programs that do not follow Section 11.1.2.1.2 ("Constraints on the “COMMON-LISP” Package for Conforming Programs") cause undefined behavior.
CLISP supports programs written with case sensitive symbols. For
example, with case sensitive symbols, the symbols cdr
(the function equivalent to REST) and the symbol CDR
(a user-defined type denoting a Call Data Record) are different and unrelated.
There are some incompatibilities between programs assuming case
sensitive symbols and programs assuming the [ANSI CL standard] case insensitive symbols.
For example, (eq 'KB 'Kb) evaluates to false in a case
sensitive world and to true in a case insensitive world. However, unlike some
commercial Common Lisp implementations, CLISP allows both kinds of programs to
coexist in the same process and interoperate with each other. Example:
OLD.lisp(IN-PACKAGE"OLD") (DEFUNFOO () ...)
modern.lisp
(in-package "NEW")
(defun bar () (old:foo))
(symbol-name 'bar) ; ⇒ "bar"
This is achieved through specification of the symbol case policy at the package level. A modern package is one that is declared to be both case-sensitive and case-inverted and which use the symbols from the “CS-COMMON-LISP” package.
A case-sensitive package
  
  is one whose DEFPACKAGE declaration (or MAKE-PACKAGE
 creation form) has the option (.
 In a case-sensitive package, the reader does not uppercase the
 symbol name before calling :CASE-SENSITIVE T)INTERN.  Similarly, the printer, when
 printing the SYMBOL-NAME part of a SYMBOL (i.e. the part after
 the package markers), behaves as if the readtable's case were set
 to :PRESERVE.
 See also Section 11.5.5, “Function EXT:PACKAGE-CASE-SENSITIVE-P”.
A case-inverted package
  
  is one whose DEFPACKAGE declaration (or MAKE-PACKAGE
 creation form) has the option (.
 In the context of a case-inverted package, symbol names are
 case-inverted: upper case characters are mapped to lower case, lower
 case characters are mapped to upper case, and other characters are left
 untouched.  Every symbol thus conceptually has two symbol names: an
 old-world symbol name and a modern-world symbol name, which is the
 case-inverted old-world name.  The first symbol name is returned by the
 function :CASE-INVERTED T)SYMBOL-NAME, the modern one by the
 function cs-cl:symbol-name.  The internal
 functions for creating or looking up symbols in a package, which
 traditionally took a string argument, now conceptually take two string
 arguments: old-style-string and inverted-string.  Actually, a function
 like INTERN takes the old-style-string as argument and computes the
 inverted-string from it; whereas the
 function cs-cl:intern takes the inverted-string as
 argument and computes the old-style-string from it.
 See also Section 11.5.4, “Function EXT:PACKAGE-CASE-INVERTED-P”.
For a few built-in functions, a variant for the case-inverted world is defined in the “CS-COMMON-LISP” package, which has the nickname “CS-CL”:
cs-cl:symbol-namecs-cl:interncs-cl:find-symbolcs-cl:symbol-name.cs-cl:shadowcs-cl:find-all-symbolscs-cl:string=cs-cl:string/=cs-cl:string<cs-cl:string>cs-cl:string<=cs-cl:string>=cs-cl:string-trimcs-cl:string-left-trimcs-cl:string-right-trimSYMBOL to a STRING and therefore
     exist in a variant that uses cs-cl:symbol-name
     instead of SYMBOL-NAME.cs-cl:make-packagePACKAGE.
A package “CS-COMMON-LISP-USER” is provided for the user to modify and work in. It plays the same role as “COMMON-LISP-USER”, but for the case-sensitive world.
The handling of package names is unchanged.  Package names are
 still usually uppercase.  The package names are also subject to
 (.READTABLE-CASE *READTABLE*)
Note that gensyms and keywords are still treated traditionally: even in a case-sensitive package,
(STRING='#:FooBar '#:foobar) ⇒(TEQ':KeyWord ':keyword) ⇒T
We believe this has a limited negative impact for the moment, but can be changed some time in the future.
The following practices will pose no problems when migrating to a modern case-sensitive world:
(STRING= (SYMBOL-NAME x) (SYMBOL-NAME y)).
The following practices will not work in a case-sensitive world or can give problems:
SYMBOL-NAME return values with EQ.
(SYMBOL-NAME x) with
  (cs-cl:symbol-name y).CLISP supports a command-line option -modern that
 sets the *PACKAGE* initially to the “CS-COMMON-LISP-USER” package, and
 *PRINT-BASE* to :DOWNCASE.
For packages to be located in the “modern”
 (case-sensitive) world, you need to augment their DEFPACKAGE
 declaration by adding the option (.:MODERN T)
MAKE-PACKAGEThe default value of the :USE argument is
 (“COMMON-LISP”).
MAKE-PACKAGE accepts additional keyword arguments
 :CASE-SENSITIVE and :CASE-INVERTED (but not :MODERN!)
DEFPACKAGEDEFPACKAGE accepts additional options :CASE-SENSITIVE,
 :CASE-INVERTED, and :MODERN.
When the package being defined already exists, it is modified as follows (and in this order):
:CASE-SENSITIVE(SETF EXT:PACKAGE-CASE-SENSITIVE-P)
     (with a warning):CASE-INVERTED(SETF EXT:PACKAGE-CASE-INVERTED-P)
     (with a warning):MODERNif “COMMON-LISP” is being used, it is un-used and
     “CS-COMMON-LISP” is used instead; also, “CS-COMMON-LISP” is used instead of “COMMON-LISP”
     throughout the DEFPACKAGE form, e.g.,
(DEFPACKAGE"FOO" (:MODERNT) (:USE"COMMON-LISP" "EXT"))
is equivalent to
(DEFPACKAGE"FOO" (:CASE-SENSITIVET) (:CASE-INVERTEDT) (:USE"CS-COMMON-LISP" "EXT"))
:NICKNAMESRENAME-PACKAGE
  :DOCUMENTATION(SETF
      DOCUMENTATION):SHADOWSHADOW
  :SHADOWING-IMPORT-FROMSHADOWING-IMPORT
  :USEUSE-PACKAGE and UNUSE-PACKAGE
  :IMPORT-FROMIMPORT
  :INTERNINTERN (but not UNINTERN)
  :EXPORTINTERN and EXPORT (but not
     UNEXPORT):SIZEEXT:RE-EXPORTThe function ( re-EXT:RE-EXPORT FROM-PACK
  TO-PACK)EXPORTs all external
 SYMBOLs from FROM-PACK also from
 TO-PACK, provided it already uses
 FROM-PACK; and SIGNALs an ERROR otherwise.
EXT:PACKAGE-CASE-INVERTED-PReturns T if the argument is a
  case-inverted package.
  This function is SETFable, although it is probably not a good idea
  to change the case-inverted status of an existing package.
EXT:PACKAGE-CASE-SENSITIVE-PReturns T if the argument is a
  case-sensitive package.
  This function is SETFable, although it is probably not a good idea
  to change the case-sensitive status of an existing package.
Table of Contents
The type NUMBER is the disjoint union of the types
 REAL and COMPLEX (“exhaustive
 partition”)
The type REAL is the disjoint union of the types
 RATIONAL and FLOAT.
The type RATIONAL is the disjoint union of the types
 INTEGER and RATIO.
The type INTEGER is the disjoint union of the types
 FIXNUM and BIGNUM.
The type FLOAT is the disjoint union of the types
 SHORT-FLOAT, SINGLE-FLOAT, DOUBLE-FLOAT and
 LONG-FLOAT.
Byte specifiers are objects of built-in type BYTE,
 not INTEGERs.
When a mathematical function may return an exact (RATIONAL) or
 inexact (FLOAT) result, it always returns the exact result.
There are four floating point types: SHORT-FLOAT,
 SINGLE-FLOAT, DOUBLE-FLOAT and LONG-FLOAT:
| type | sign | mantissa | exponent | comment | 
|---|---|---|---|---|
| SHORT-FLOAT | 1 bit | 16+1 bits | 8 bits | immediate | 
| SINGLE-FLOAT | 1 bit | 23+1 bits | 8 bits | IEEE 754 | 
| DOUBLE-FLOAT | 1 bit | 52+1 bits | 11 bits | IEEE 754 | 
| LONG-FLOAT | 1 bit | >=64 bits | 32 bits | variable length | 
The single and double float formats are those of the IEEE 754
 “Standard for Binary Floating-Point Arithmetic”,
 except that CLISP does not support features like
 ±0, ±inf,
 NaN, gradual underflow, etc.
 Common Lisp does not make use of these features, so, to reduce portability
 problems, CLISP by design returns the same floating point results on
 all platforms (CLISP has a floating-point emulation built in for
 platforms that do not support IEEE 754).  Note that
 
NaN
    in your program, your program is broken, so you will spend time
    determining where the NaN came from.
    It is better to SIGNAL an ERROR in this case.LONG-FLOATs of
    variable precision - it does not
    need unnormalized floats.
 This is why *FEATURES* does not contain the
 :IEEE-FLOATING-POINT keyword.
Arbitrary Precision Floats. LONG-FLOATs have variable mantissa length, which is a
 multiple of 16 (or 32, depending on the word size of the processor).
 The default length used when LONG-FLOATs are READ is given by the
 place (.  It can be set by EXT:LONG-FLOAT-DIGITS)(,
 where SETF (EXT:LONG-FLOAT-DIGITS) n)n is a positive INTEGER.  E.g., ( sets the default precision of SETF (EXT:LONG-FLOAT-DIGITS)
 3322)LONG-FLOATs to about
 1000 decimal digits.
The floating point contagion is controlled by the variable
 CUSTOM:*FLOATING-POINT-CONTAGION-ANSI*.  When it is non-NIL, contagion is done as per the
 [ANSI CL standard]: SHORT-FLOAT → SINGLE-FLOAT →
 DOUBLE-FLOAT → LONG-FLOAT.
1.5 is actually 1.5±0.05.
  Consider adding 1.5 and 1.75.
  [ANSI CL standard] requires that (+ 1.5 1.75)
  return 3.25, while traditional CLISP would return
  3.3.  The implied random variables are:
  3.25±0.005 and 3.3±0.05.
  Note that the traditional CLISP way does
  lie about the mean: the mean is 3.25 and
  nothing else, while the standard way
  could be lying about the deviation
  (accuracy): if the implied accuracy of 1.5 (0.05)
  is its actual accuracy, then the accuracy of the result cannot be
  smaller that that.  Therefore, since Common Lisp has no way of knowing the
  actual accuracy, [ANSI CL standard] (and all the other standard engineering
  programming languages, like C, Fortran
  etc) decides that keeping the accuracy correct is the business of the
  programmer, while the language should preserve what it can - the precision.
  E(x2) -
  E(x)2 can be negative!)
  The user should not mix floats of different precision (that's what
  CUSTOM:*WARN-ON-FLOATING-POINT-CONTAGION* is for), but one should not be penalized for this too
  harshly.When CUSTOM:*FLOATING-POINT-CONTAGION-ANSI* is NIL, the traditional CLISP method is used,
 namely the result of an arithmetic operation whose arguments are of
 different float types is rounded to the float format of the shortest
 (least precise) of the arguments: RATIONAL →
 LONG-FLOAT → DOUBLE-FLOAT → SINGLE-FLOAT
 → SHORT-FLOAT (in contrast to 12.1.4.4 Rule of Float Precision
 Contagion!)
{1.0 ± 1e-8} + {1.0 ± 1e-16} = {2.0 ±
  1e-8}.  So, if we add 1.0s0 and
  1.0d0, we should get 2.0s0.
  (- (+ 1.7 PI) PI)
  should not return 1.700000726342836417234L0, it
  should return 1.7f0 (or
  1.700001f0 if there were rounding errors).
  SHORT-FLOATs,
  a LONG-FLOAT (like PI) happens to be used, the long precision
  should not propagate throughout all the intermediate values.
  Otherwise, the long result would look precise, but its accuracy is
  only that of a SHORT-FLOAT; furthermore much computation time
  would be lost by calculating with LONG-FLOATs when only
  SHORT-FLOATs would be needed.
  If the variable CUSTOM:*WARN-ON-FLOATING-POINT-CONTAGION* is non-NIL, a WARNING is emitted for
 every coercion involving different floating-point types.
 As explained above, float precision contagion is not a good idea.
 You can avoid the contagion by doing all your computations with the
 same floating-point type (and using FLOAT to convert all constants,
 e.g., PI, to your preferred type).
This variable helps you eliminate all occurrences of float
 precision contagion: set it to T to have CLISP SIGNAL a
 WARNING on float precision contagion; set it to ERROR to have
 CLISP SIGNAL an ERROR on float precision contagion, so that you
 can look at the stack backtrace.
The contagion between floating point and rational numbers is controlled
 by the variable CUSTOM:*FLOATING-POINT-RATIONAL-CONTAGION-ANSI*.  When it is non-NIL, contagion is done as per
 the [ANSI CL standard]: RATIONAL → FLOAT.
When CUSTOM:*FLOATING-POINT-RATIONAL-CONTAGION-ANSI* is NIL, the traditional CLISP method is used,
 namely if the result is mathematically an exact rational number, this
 rational number is returned (in contrast to 12.1.4.1 Rule of Float and Rational
 Contagion!)
CUSTOM:*FLOATING-POINT-RATIONAL-CONTAGION-ANSI* has an effect only in those few cases when the mathematical
 result is exact although one of the arguments is a floating-point number,
 such as (, * 0 1.618)(,
 / 0 1.618)(, ATAN 0 1.0)(,
 EXPT 2.0 0)(.PHASE 2.718)
If the variable CUSTOM:*WARN-ON-FLOATING-POINT-RATIONAL-CONTAGION* is non-NIL, a WARNING is emitted for
 every avoidable coercion from a rational number to a floating-point number.
 You can avoid such coercions by calling FLOAT to convert the particular
 rational numbers to your preferred floating-point type.
This variable helps you eliminate all occurrences of avoidable
 coercions to a floating-point number when a rational number result
 would be possible: set it to T to have CLISP SIGNAL a WARNING
 in such situations; set it to ERROR to have CLISP SIGNAL an
 ERROR in such situations, so that you can look at the stack
 backtrace.
CUSTOM:*PHASE-ANSI*A similar variable, CUSTOM:*PHASE-ANSI*, controls the return
 value of PHASE when the argument is an exact nonnegative REAL.
 Namely, if CUSTOM:*PHASE-ANSI* is non-NIL, it returns a floating-point zero;
 if CUSTOM:*PHASE-ANSI* is NIL, it returns an exact zero.  Example:
 (PHASE 2/3)
Complex numbers can have a real part and an imaginary part of
 different types. For example, ( evaluates to
 the number SQRT -9.0)#C(0 3.0)0,
 not only 0.0
 (which would mean “approximately 0”).
The type specifier for this is (, and COMPLEX INTEGER
 SINGLE-FLOAT)( in general.COMPLEX type-of-real-part
 type-of-imaginary-part)
The type specifier ( is equivalent to COMPLEX
 type)(.COMPLEX type type)
Complex numbers can have a real part and an imaginary part of
 different types.  If the imaginary part is EQL to 0,
 the number is automatically converted to a real number.
This has the advantage that
 ( - instead of
 evaluating to LET ((x (SQRT -9.0))) (* x x))#C(-9.0 0.0)x = #C(0.0 3.0)#C(-9.0 0)-9.0,
 with x = #C(0 3.0)
To ease reproducibility, the variable *RANDOM-STATE* is
 initialized to the same value on each invocation, so that
 
$clisp -norc-x'(RANDOM1s0)'
will always print the same number.
If you want a new random state on each invocation, you can arrange for that by using init function:
$clisp -norc-x'(EXT:SAVEINITMEM"foo" :init-function (LAMBDA() (SETQ*RANDOM-STATE*(MAKE-RANDOM-STATET))))'$clisp -norc-Mfoo.mem-x'(RANDOM1s0)'
 or by placing ( into your RC file.SETQ *RANDOM-STATE*
  (MAKE-RANDOM-STATE T))
Function EXT:! ( returns the
 factorial of EXT:! n)n, n being a nonnegative INTEGER.
Function EXT:EXQUO. ( returns
 the integer quotient EXT:EXQUO x y)x/y of two integers
 x,y, and SIGNALs an ERROR when the quotient is not
 integer.  (This is more efficient than /.)
Function EXT:XGCD. (
 returns the values EXT:XGCD x1 ... xn)l, k1, ..., kn, where l is the
 greatest common divisor of the integers x1, ..., xn, and
 k1, ..., kn are the integer coefficients such that
l= (GCDx1...xn) = (+ (*k1x1) ... (*knxn))
Function EXT:MOD-EXPT. (
 is equivalent to EXT:MOD-EXPT k l m)(
 except it is more efficient for very large arguments.MOD (EXPT k l) m)
Function EXPT. (
 is not very precise if EXPT base exponent)exponent has a large
 absolute value.
Function LOG. ( LOG number base)SIGNALs an ERROR if
 base = 1
Constant PI. The value of PI is a LONG-FLOAT with the precision given
  by (.  When this precision is changed, the value of EXT:LONG-FLOAT-DIGITS)PI is
  automatically recomputed.  Therefore PI is not a constant variable.
Function UPGRADED-COMPLEX-PART-TYPE. When the argument is not a recognizable subtype or REAL,
 UPGRADED-COMPLEX-PART-TYPE SIGNALs an ERROR, otherwise it
 returns its argument (even though a COMPLEX number in CLISP can
 always have REALPART and IMAGPART of any type) because it allows
 the most precise type inference.
Variable CUSTOM:*DEFAULT-FLOAT-FORMAT*. When rational numbers are to be converted to floats (due to
 FLOAT, COERCE, SQRT or a transcendental function), the result
 type is given by the variable CUSTOM:*DEFAULT-FLOAT-FORMAT*.
Macro EXT:WITHOUT-FLOATING-POINT-UNDERFLOW. The macro ( executes the
 EXT:WITHOUT-FLOATING-POINT-UNDERFLOW {form}*)forms, with errors of type FLOATING-POINT-UNDERFLOW inhibited.
 Floating point operations will silently return zero instead of
 SIGNALing an ERROR of type FLOATING-POINT-UNDERFLOW.
Condition FLOATING-POINT-INVALID-OPERATION. This CONDITION is never SIGNALed by CLISP.
Condition FLOATING-POINT-INEXACT. This CONDITION is never SIGNALed by CLISP.
FLOAT-RADIX always returns 2.
( coerces
 FLOAT-DIGITS number digits)number (a REAL) to a floating point number with at least
 digits mantissa digits.  The following always evaluates to T:
 
(>=(FLOAT-DIGITS(FLOAT-DIGITSnumberdigits))digits)
Table 12.2. Fixnum limits
| CPU type | 32-bit CPU | 64-bit CPU | 
|---|---|---|
| MOST-POSITIVE-FIXNUM | 224-1 = 16777215 | 248-1 = 281474976710655 | 
| MOST-NEGATIVE-FIXNUM | -224 = -16777216 | -248 = -281474976710656 | 
BIGNUMs are limited in size.  Their maximum size is
 32*(216-2)=2097088 bits.
 The largest representable BIGNUM is therefore
 22097088-1.
Together with PI, the other LONG-FLOAT constants
  
  are recomputed whenever ( is EXT:LONG-FLOAT-DIGITS)SETFed.
  They are not constant variables.
Table of Contents
The characters are ordered according to a superset of the ASCII character set.
More precisely, CLISP uses the ISO Latin-1 (ISO 8859-1) character set:
| #x0 | #x1 | #x2 | #x3 | #x4 | #x5 | #x6 | #x7 | #x8 | #x9 | #xA | #xB | #xC | #xD | #xE | #xF | |
|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|
| #x00 | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | 
| #x10 | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | 
| #x20 | ! | " | # | $ | % | & | ' | ( | ) | * | + | , | - | . | / | |
| #x30 | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | : | ; | < | = | > | ? | 
| #x40 | @ | A | B | C | D | E | F | G | H | I | J | K | L | M | N | O | 
| #x50 | P | Q | R | S | T | U | V | W | X | Y | Z | [ | \ | ] | ^ | _ | 
| #x60 | ` | a | b | c | d | e | f | g | h | i | j | k | l | m | n | o | 
| #x70 | p | q | r | s | t | u | v | w | x | y | z | { | | | } | ~ | |
| #x80 | ||||||||||||||||
| #x90 | ||||||||||||||||
| #xA0 | ¡ | ¢ | £ | ¤ | ¥ | ¦ | § | ¨ | © | ª | « | ¬ |  | ® | ¯ | |
| #xB0 | ° | ± | ² | ³ | ´ | µ | ¶ | · | ¸ | ¹ | º | » | ¼ | ½ | ¾ | ¿ | 
| #xC0 | À | Á | Â | Ã | Ä | Å | Æ | Ç | È | É | Ê | Ë | Ì | Í | Î | Ï | 
| #xD0 | Ð | Ñ | Ò | Ó | Ô | Õ | Ö | × | Ø | Ù | Ú | Û | Ü | Ý | Þ | ß | 
| #xE0 | à | á | â | ã | ä | å | æ | ç | è | é | ê | ë | ì | í | î | ï | 
| #xF0 | ð | ñ | ò | ó | ô | õ | ö | ÷ | ø | ù | ú | û | ü | ý | þ | ÿ | 
Here ** are control characters, not graphic characters. (The characters left blank here cannot be represented in this character set).
More precisely, CLISP uses the NeXTstep character set:
| #x0 | #x1 | #x2 | #x3 | #x4 | #x5 | #x6 | #x7 | #x8 | #x9 | #xA | #xB | #xC | #xD | #xE | #xF | |
|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|
| #x00 | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | 
| #x10 | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | ** | 
| #x20 | ! | " | # | $ | % | & | ' | ( | ) | * | + | , | - | . | / | |
| #x30 | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | : | ; | < | = | > | ? | 
| #x40 | @ | A | B | C | D | E | F | G | H | I | J | K | L | M | N | O | 
| #x50 | P | Q | R | S | T | U | V | W | X | Y | Z | [ | \ | ] | ^ | _ | 
| #x60 | ` | a | b | c | d | e | f | g | h | i | j | k | l | m | n | o | 
| #x70 | p | q | r | s | t | u | v | w | x | y | z | { | | | } | ~ | |
| #x80 | À | Á | Â | Ã | Ä | Å | Ç | È | É | Ê | Ë | Ì | Í | Î | Ï | |
| #x90 | Ð | Ñ | Ò | Ó | Ô | Õ | Ö | Ù | Ú | Û | Ü | Ý | Þ | µ | × | ÷ | 
| #xA0 | © | ¡ | ¢ | £ | ⁄ | ¥ | ƒ | § | ¤ | ’ | “ | « | ‹ | › | fi | fl | 
| #xB0 | ® | – | † | ‡ | · | ¦ | ¶ | • | ‚ | „ | ” | » | … | ‰ | ¬ | ¿ | 
| #xC0 | ¹ | ˋ | ´ | ˆ | ˜ | ¯ | ˘ | ˙ | ¨ | ² | ˚ | ¸ | ³ | ˝ | ˛ | ˇ | 
| #xD0 | — | ± | ¼ | ½ | ¾ | à | á | â | ã | ä | å | ç | è | é | ê | ë | 
| #xE0 | ì | Æ | í | ª | î | ï | ð | ñ | Ł | Ø | Œ | º | ò | ó | ô | õ | 
| #xF0 | ö | æ | ù | ú | û | ı | ü | ý | ł | ø | œ | ß | þ | ÿ | 
Here ** are control characters, not graphic characters. (The characters left blank here cannot be represented in this character set).
Table 13.2. Semi-standard characters
| character | code | 
|---|---|
| #\Backspace | #x08 | 
| #\Tab | #x09 | 
| #\Linefeed | #x0A | 
| #\Page | #x0C | 
| #\Return | #x0D | 
#\Newline is the line terminator.
Table 13.4. Additional syntax for characters with code from #x00 to #x1F:
| character | code | 
|---|---|
| #\^@ | #x00 | 
| #\^A … #\^Z | #x01 … #x1A | 
| #\^[ | #x1B | 
| #\^\ | #x1C | 
| #\^] | #x1D | 
| #\^^ | #x1E | 
| #\^_ | #x1F | 
See also Section 2.6.1, “Sharpsign Backslash [CLHS-2.4.8.1]”.
The only defined character script is the type CHARACTER
 itself.
Characters have no implementation-defined or [CLtL1] font and bit attributes. All characters are simple characters.
For backward compatibility, there is a class SYS::INPUT-CHARACTER
 representing either a character with font and bits, or a keystroke.
 The following functions work with objects of types CHARACTER
 and SYS::INPUT-CHARACTER.
 Note that EQL or EQUAL are equivalent to EQ on objects of type
 SYS::INPUT-CHARACTER.
EXT:CHAR-FONT-LIMIT = 16EXT:CHAR-BITS-LIMIT = 16Character bits:
| key | value | 
|---|---|
| :CONTROL | EXT:CHAR-CONTROL-BIT | 
| :META | EXT:CHAR-META-BIT | 
| :SUPER | EXT:CHAR-SUPER-BIT | 
| :HYPER | EXT:CHAR-HYPER-BIT | 
(EXT:CHAR-FONT
  object)CHARACTER or SYS::INPUT-CHARACTER.
  (EXT:CHAR-BITS
  object)CHARACTER or SYS::INPUT-CHARACTER.
  (EXT:MAKE-CHAR
     char [bits
            [font]])SYS::INPUT-CHARACTER, or NIL if such a
 character cannot be created.(EXT:CHAR-BIT
  object name)T if the named bit is set in object,
  else NIL.(EXT:SET-CHAR-BIT
  object name new-value)SYS::INPUT-CHARACTER with the named bit set or
   unset, depending on the BOOLEAN new-value.
 SYS::INPUT-CHARACTER is not a subtype of
  CHARACTER.
SYS::INPUT-CHARACTER type only to
 mention special keys and Control/Alternate/Shift key status on return from
 (READ-CHAR EXT:*KEYBOARD-INPUT*).The graphic characters are those UNICODE characters which are defined by the UNICODE standard, excluding the ranges U0000 … U001F and U007F … U009F.
The alphabetic characters are those UNICODE characters which are defined as letters by the UNICODE standard, e.g., the ASCII characters
             ABCDEFGHIJKLMNOPQRSTUVWXYZ
             abcdefghijklmnopqrstuvwxyz
and the international alphabetic characters from the character set:
             ÇüéâäàåçêëèïîìÄÅÉæÆôöòûùÿÖÜßáíóúñѪºãõØøÀÃÕ etc.
EXT:CHAR-INVERTCASE( returns the corresponding
 character in the other case for EXT:CHAR-INVERTCASE char)CHAR, i.e., CHAR-UPCASE for a
 lowercase character and CHAR-DOWNCASE for an uppercase character; for
 a character that does not have a case attribute, the argument is returned.
 See also EXT:STRING-INVERTCASE and EXT:NSTRING-INVERTCASE.
The characters with case are those UNICODE characters c, for
 which the upper case mapping uc and the lower case mapping lc
 have the following properties:
uc and lc are differentc is one of uc and lcuc and of lc
   is ucuc and of lc
   is lcThe titlecase property of UNICODE characters has no equivalent in Common Lisp.
The numeric characters are those UNICODE characters which are defined as digits by the UNICODE standard.
The characters are ordered according to their UNICODE code.
The functions CHAR-EQUAL CHAR-NOT-EQUAL, CHAR-LESSP,
 CHAR-GREATERP, CHAR-NOT-GREATERP, CHAR-NOT-LESSP ignore bits and
 font attributes of their arguments.
Newlines are written according to the stream's EXT:ENCODING, see the
 function STREAM-EXTERNAL-FORMAT and the description of EXT:ENCODINGs,
 in particular, line terminators.
 The default behavior is as follows:
When reading from a file, CR/LF is converted to #\Newline
 (the usual convention on DOS), and CR not followed by LF is
 converted to #\Newline as well (the usual conversion on MacOS, also used
 by some programs on Win32).
 If you do not want this, i.e., if you really want to distinguish
 LF, CR and CR/LF, you have to resort to
 binary input (function READ-BYTE).
Justification. Unicode Newline Guidelines say: “Even if you know which characters represents NLF on your particular platform, on input and in interpretation, treat CR, LF, CRLF, and NEL the same. Only on output do you need to distinguish between them.”
Rationale. In CLISP, #\Newline is identical to #\Linefeed
 (which is specifically permitted by [ANSI CL standard] in section
 13.1.7 “Character
   Names”).
 Consider a file containing exactly this string:
 (
 Suppose we open it with CONCATENATE 'STRING "foo" (STRING #\Linefeed)
  "bar" (STRING #\Return) (STRING #\Linefeed))(.
 What should OPEN "foo" :EXTERNAL-FORMAT :DOS)READ-LINE return?
 Right now, it returns "foo"
 (the second READ-LINE returns "bar"
 and reaches end-of-stream).
 If our i/o were “faithful”, READ-LINE would have
 returned the string (, i.e., a string with an embedded #\Newline
 between "foo"
 and "bar" (because a single #\Linefeed is not a
 #\Newline in the specified CONCATENATE 'STRING "foo" (STRING
  #\Linefeed) "bar"):EXTERNAL-FORMAT, it will not make READ-LINE return,
 but it is a CLISP #\Newline!)  Even though the specification for
 READ-LINE does not explicitly forbids newlines inside the returned
 string, such behavior would be quite surprising, to say the least.
 Moreover, this line (with an embedded #\Newline) would be written as two
 lines (when writing to a STREAM with :EXTERNAL-FORMAT of :DOS), because
 the embedded #\Newline would be written as CR+LF.
The integer returned by CHAR-INT is the same as the character's
 code (CHAR-CODE).
CHAR-CODECHAR-CODE takes values from 0 (inclusive) to
 CHAR-CODE-LIMIT (exclusive), i.e., the implementation
 supports exactly CHAR-CODE-LIMIT characters.
Table 13.5. Number of characters
| binaries built | without UNICODE support | with UNICODE support | 
|---|---|---|
| CHAR-CODE-LIMIT | 28 = 256 | 17 * 216 = 1114112 | 
BASE-CHARThe types EXT:STRING-CHAR and
 BASE-CHAR are equivalent to CHARACTER.
 EXT:STRING-CHAR used to be available as
 STRING-CHAR prior to removal from [ANSI CL standard] by
 CHARACTER-PROPOSAL:2.
EXT:CHAR-WIDTH( returns the number of screen
 columns occupied by EXT:CHAR-WIDTH char)char.
 This is 0 for non-spacing characters
 (such as control characters and many combining characters),
 2 for double-width East Asian characters,
 and 1 for all other characters.
 See also function EXT:STRING-WIDTH.
The characters that are not graphic chars and the space character have names:
Table 13.6. Additional characters (Platform Dependent: Win32 platform only.)
| code | char | |
|---|---|---|
| ( | #\Null | |
| ( | #\Bell | |
| ( | #\Backspace | |
| ( | #\Tab | |
| ( | #\Newline | #\Linefeed | 
| ( | #\Code11 | |
| ( | #\Page | |
| ( | #\Return | |
| ( | #\Code26 | |
| ( | #\Escape | #\Esc | 
| ( | #\Space | |
| ( | #\Rubout | 
Table 13.7. Additional characters (Platform Dependent: UNIX platform only.)
| code | char | ||
|---|---|---|---|
| ( | #\Null | #\Nul | |
| ( | #\Soh | ||
| ( | #\Stx | ||
| ( | #\Etx | ||
| ( | #\Eot | ||
| ( | #\Enq | ||
| ( | #\Ack | ||
| ( | #\Bell | #\Bel | |
| ( | #\Backspace | #\Bs | |
| ( | #\Tab | #\Ht | |
| ( | #\Newline | #\Nl | #\Linefeed | 
| ( | #\Vt | ||
| ( | #\Page | #\Np | |
| ( | #\Return | #\Cr | |
| ( | #\So | ||
| ( | #\Si | ||
| ( | #\Dle | ||
| ( | #\Dc1 | ||
| ( | #\Dc2 | ||
| ( | #\Dc3 | ||
| ( | #\Dc4 | ||
| ( | #\Nak | ||
| ( | #\Syn | ||
| ( | #\Etb | ||
| ( | #\Can | ||
| ( | #\Em | ||
| ( | #\Sub | ||
| ( | #\Escape | #\Esc | |
| ( | #\Fs | ||
| ( | #\Gs | ||
| ( | #\Rs | ||
| ( | #\Us | ||
| ( | #\Space | #\Sp | |
| ( | #\Rubout | #\Delete | #\Del | 
Table of Contents
Function EXT:MAPCAP. The function EXT:MAPCAP is like MAPCAN, except that it
 concatenates the resulting lists with APPEND instead of NCONC:
(EXT:MAPCAPfunctionx1...xn) ≡ (APPLY#'APPEND(MAPCARfunctionx1...xn))
(Actually a bit more efficient that this would have been.)
Function EXT:MAPLAP. The function EXT:MAPLAP is like MAPCON, except that it
 concatenates the resulting lists with APPEND instead of NCONC:
 
(EXT:MAPLAPfunctionx1...xn) ≡ (APPLY#'APPEND(MAPLISTfunctionx1...xn))
(Actually a bit more efficient that this would have been.)
Function MAKE-ARRAY. MAKE-ARRAY can return specialized arrays for the ARRAY-ELEMENT-TYPEs
 (,
 UNSIGNED-BYTE 2)(,
 UNSIGNED-BYTE 4)(, UNSIGNED-BYTE 8)(, UNSIGNED-BYTE 16)(, and, of course, the required
 specializations UNSIGNED-BYTE 32)NIL, BIT and CHARACTER.
Table 15.1. Array limits
| CPU type | 32-bit CPU | 64-bit CPU | 
|---|---|---|
| ARRAY-RANK-LIMIT | 212 = 4096 | |
| ARRAY-DIMENSION-LIMIT | 224-1 = 16777215 | 232-1 = 4294967295 | 
| ARRAY-TOTAL-SIZE-LIMIT | 224-1 = 16777215 | 232-1 = 4294967295 | 
Function ADJUST-ARRAY for displaced arrays. An array to which another array is displaced should not be shrunk
 (using ADJUST-ARRAY) in such a way that the other array points into
 void space.  This cannot be checked at the time ADJUST-ARRAY is
 called!
Table of Contents
String comparison (STRING< and friends) is based on the
 function CHAR<= (see Section 13.7, “Ordering of Characters
   [CLHS-13.1.6]”).
 Therefore diphthongs do not obey the usual national rules.  Example:
 o < oe < z < ö.
EXT:STRING-WIDTH( returns the number of screen columns occupied by
 EXT:STRING-WIDTH string &KEY start
  end)string.  This is computed as the sum of all EXT:CHAR-WIDTHs of all
 of the string's characters:
(REDUCE#'+string:KEY#'EXT:CHAR-WIDTH)
EXT:STRING-INVERTCASE
  and EXT:NSTRING-INVERTCASE(
 and EXT:STRING-INVERTCASE string &KEY start end)(
 are similar to EXT:NSTRING-INVERTCASE string &KEY start end)STRING-UPCASE et al: they use EXT:CHAR-INVERTCASE to
 invert the case of each characters in the argument string region.
Table of Contents
Function NREVERSE. The result of NREVERSE is always EQ to the argument.
 NREVERSE on a VECTOR swaps pairs of elements.
 NREVERSE on a LIST swaps the first and the last
 element and reverses the list chaining between them.
Function NRECONC. The result of NRECONC is EQ to the first argument unless it is
 NIL, in which case the result is EQ to the second argument.
REMOVE, REMOVE-IF, REMOVE-IF-NOT, REMOVE-DUPLICATES return
 their argument unchanged, if no element has to be removed.
DELETE, DELETE-IF, DELETE-IF-NOT, DELETE-DUPLICATES
 destructively modify their argument: If the argument is a LIST,
 the CDR parts are modified.  If the argument is a VECTOR with
 fill pointer, the fill pointer is lowered and the remaining elements are
 compacted below the new fill pointer.
Variable CUSTOM:*SEQUENCE-COUNT-ANSI*. Contrary to the [ANSI CL standard] issue RANGE-OF-COUNT-KEYWORD:NIL-OR-INTEGER,
 negative :COUNT keyword arguments are not allowed unless you set
 CUSTOM:*SEQUENCE-COUNT-ANSI* to a non-NIL value, in which case “using a
 negative integer value is functionally equivalent to using a value of
 zero”, as per the [ANSI CL standard] issue.
SORT & STABLE-SORTSORT and STABLE-SORT accept two additional keyword arguments
 :START and :END:
(SORTsequencepredicate&KEY:KEY:START:END) (STABLE-SORTsequencepredicate&KEY:KEY:START:END)
SORT and STABLE-SORT are identical.
 They implement the mergesort algorithm.
 Worst case complexity: O(n*log(n)) comparisons,
 where n is the LENGTH of the subsequence bounded
 by the :START and :END arguments.
Table of Contents
MAKE-HASH-TABLEMAKE-HASH-TABLE accepts two additional keyword arguments
 :INITIAL-CONTENTS and :WEAK:
(MAKE-HASH-TABLE&KEY:TEST :INITIAL-CONTENTS :SIZE :REHASH-SIZE :REHASH-THRESHOLD :WARN-IF-NEEDS-REHASH-AFTER-GC :WEAK)
The :TEST argument can be, other than one of the symbols EQ,
 EQL, EQUAL, EQUALP, one of the symbols EXT:FASTHASH-EQ and
 EXT:STABLEHASH-EQ.  Both of these tests use EQ as the comparison
 function; they differ in their performance characteristics.
 
EXT:FASTHASH-EQEXT:STABLEHASH-EQSYMBOL,
     EXT:STANDARD-STABLEHASH (subclass of STANDARD-OBJECT) and
     EXT:STRUCTURE-STABLEHASH (subclass of STRUCTURE-OBJECT) are
     stable across GCs.
     This test can thus avoid the scalability problems if all keys,
     other than immediate objects, are SYMBOL, EXT:STANDARD-STABLEHASH or
     EXT:STRUCTURE-STABLEHASH instances.
 One can recommend to use EXT:FASTHASH-EQ for short-lived hash tables.
 For tables with a longer lifespan which can be big or accessed
 frequently, it is recommended to use EXT:STABLEHASH-EQ, and to modify the
 objects that are used as its keys to become instances of
 EXT:STANDARD-STABLEHASH or EXT:STRUCTURE-STABLEHASH.
When the symbol EQ or the function #'eq is
used as a :TEST argument, the value of the variable
CUSTOM:*EQ-HASHFUNCTION* is used instead.
This value must be one of EXT:FASTHASH-EQ, EXT:STABLEHASH-EQ.
Similarly, the :TEST argument can also be one
 of the symbols EXT:FASTHASH-EQL,
 EXT:STABLEHASH-EQL,
 EXT:FASTHASH-EQUAL,
 EXT:STABLEHASH-EQUAL.
 The same remarks apply as for EXT:FASTHASH-EQ and EXT:STABLEHASH-EQ.
 When the symbol EQL or the function #'eql is used
 as a :TEST argument, the value of the variable
 CUSTOM:*EQL-HASHFUNCTION* is used instead;
 this value must be one of EXT:FASTHASH-EQL,
 EXT:STABLEHASH-EQL.
 Similarly, when the symbol EQUAL or the function #'equal
 is used as a :TEST argument, the value of the variable
 CUSTOM:*EQUAL-HASHFUNCTION* is used instead;
 this value must be one of EXT:FASTHASH-EQUAL,
 EXT:STABLEHASH-EQUAL.
The :WARN-IF-NEEDS-REHASH-AFTER-GC argument,
if true, causes a WARNING to be SIGNALed when an object is stored
into the table which will force table reorganizations at the first
access of the table after each garbage-collection.
This keyword argument can be used to check whether EXT:STABLEHASH-EQ
should be preferred over EXT:FASTHASH-EQ for a particular table.
Use HASH-TABLE-WARN-IF-NEEDS-REHASH-AFTER-GC
to check and SETF this parameter after the table has been created.
The :INITIAL-CONTENTS argument is an
 association list that is used to initialize the new hash table.
The :REHASH-THRESHOLD argument is ignored.
The :WEAK argument can take the following values:
 
| NIL(default) | 
| :KEY | 
| :VALUE | 
| :KEY-AND-VALUE | 
| :KEY-OR-VALUE | 
and specifies whether the HASH-TABLE is weak:
if the key, value, either or both are not accessible for the garbage-collection
purposes, i.e., if they are only accessible via weak HASH-TABLEs
and EXT:WEAK-POINTERs, it is garbage-collected and removed from the weak
HASH-TABLE.
The SETFable predicate EXT:HASH-TABLE-WEAK-P
checks whether the HASH-TABLE is weak.
Note that the only test that makes sense for weak hash tables are
EQ and its variants EXT:FASTHASH-EQ and EXT:STABLEHASH-EQ.
Just like all other weak objects, weak
HASH-TABLEs cannot be printed readably.
See also Section 31.7.9, “Weak Hash Tables”.
HASH-TABLEs and garbage-collectionWhen a hash table contains keys to be compared by identity - such
 as NUMBERs in HASH-TABLEs with the HASH-TABLE-TEST EQ;
 or CONSes in tables which test with EQ or EQL;
 or VECTORs in tables which test with EQ, EQL or EQUAL;
 or STANDARD-OBJECT or STRUCTURE-OBJECT instances in tables which
 test with EQ, EQL, EQUAL or EQUALP;
 - the hash code will in general depend on the object's address in
 memory.  Therefore it will in general be invalidated after a garbage-collection,
 and the hash table's internal structure must be recomputed at the next
 table access.
While :WARN-IF-NEEDS-REHASH-AFTER-GC can help
 checking the efficiency of a particular HASH-TABLE, the variable
CUSTOM:*WARN-ON-HASHTABLE-NEEDING-REHASH-AFTER-GC*
 
 achieves the same effect for all HASH-TABLEs in the system at once:
 when CUSTOM:*WARN-ON-HASHTABLE-NEEDING-REHASH-AFTER-GC* is true and a
 HASH-TABLE needs to be rehashed after a garbage-collection, a warning is
 issued that shows the inefficient HASH-TABLE.
What can be done to avoid the inefficiencies detected by these warnings?
STABLEHASH variant of the hash
    test.STANDARD-OBJECT or
    STRUCTURE-OBJECT instances, you can solve the problem by making
    the key object classes inherit from EXT:STANDARD-STABLEHASH or
    EXT:STRUCTURE-STABLEHASH, respectively.EXT:DEFINE-HASH-TABLE-TESTYou can define a new hash table test using the macro
 EXT:DEFINE-HASH-TABLE-TEST: (, after
 which EXT:DEFINE-HASH-TABLE-TEST test-name test-function hash-function)test-name can be passed as the
 :TEST argument to MAKE-HASH-TABLE.
 E.g.: 
(EXT:DEFINE-HASH-TABLE-TESTstringSTRING=SXHASH) (MAKE-HASH-TABLE:test 'string)
(which is not too useful because it is equivalent to an EQUAL
HASH-TABLE but less efficient).
The fundamental requirement is that the test-function and hash-function are
 consistent: 
(FUNCALLtest-functionxy) ⇒ (=(FUNCALLhash-functionx) (FUNCALLhash-functiony))
This means that the following definition:
(EXT:DEFINE-HASH-TABLE-TESTnumber=SXHASH) ; broken!
 is not correct because ( is
 = 1 1d0)T but (
 is = (SXHASH 1) (SXHASH 1d0))NIL.  The correct way is, e.g.: 
(EXT:DEFINE-HASH-TABLE-TESTnumber=(LAMBDA(x) (SXHASH(COERCEx 'SHORT-FLOAT))))
 (note that ( does not
 cons up fresh objects while COERCE x SHORT-FLOAT)( does).COERCE x
 DOUBLE-FLOAT)
HASH-TABLE-TESTFunction HASH-TABLE-TEST returns either one of EXT:FASTHASH-EQ,
 EXT:STABLEHASH-EQ, EXT:FASTHASH-EQL,
 EXT:STABLEHASH-EQL,
 EXT:FASTHASH-EQUAL,
 EXT:STABLEHASH-EQUAL, EQUALP (but not EQ, EQL
 nor EQUAL anymore), or, for HASH-TABLEs
 created with a user-defined HASH-TABLE-TEST (see macro EXT:DEFINE-HASH-TABLE-TEST),
 a CONS cell (.
test-function . hash-function)
EXT:DOHASHFor iteration through a HASH-TABLE, a macro EXT:DOHASH,
 similar to DOLIST, can be used instead of MAPHASH:
(EXT:DOHASH(key-varvalue-varhash-table-form[resultform]) {declaration}* {tag|form}*)
EXT:DOHASH forms are iteration forms.
Table of Contents
For most operations, pathnames denoting files and pathnames denoting directories cannot be used interchangeably.
#P"foo/bar" denotes
 the file #P"bar" in the directory #P"foo",
 while #P"foo/bar/" denotes the subdirectory
 #P"bar" of the directory #P"foo".
#P"foo\\bar"
 denotes the file #P"bar" in the directory #P"foo",
 while #P"foo\\bar\\" denotes the subdirectory
 #P"bar" of the directory #P"foo".
CUSTOM:*DEVICE-PREFIX*
  controls translation between Cygwin pathnames
  (e.g., #P"/cygdrive/c/gnu/clisp/") and native
  Win32 pathnames (e.g., #P"C:\\gnu\\clisp\\")
  When it is set to NIL, no translations occur and the Cygwin port
  will not understand the native paths and the native Win32 port will
  not understand the Cygwin paths.
  When its value is a string, it is used by PARSE-NAMESTRING to
  translate into the appropriate platform-specific representation,
  so that on Cygwin,
  (PARSE-NAMESTRING "c:/gnu/clisp/")
  returns #P"/cygdrive/c/gnu/clisp/",
  while on Win32
  (PARSE-NAMESTRING "/cygdrive/c/gnu/clisp/")
  returns #P"C:/gnu/clisp/".
  The initial value is "cygdrive", you should edit
  config.lisp to change it.This is especially important for the directory-handling functions.
Table 19.1. The minimum filename syntax that may be used portably
| pathname | meaning | 
|---|---|
| "xxx" | for a file with name xxx | 
| "xxx.yy" | for a file with name xxxand typeyy | 
| ".yy" | for a pathname with type yyand no
    name or with name.yyand no type,
    depending on the value ofCUSTOM:*PARSE-NAMESTRING-DOT-FILE*. | 
Hereby xxx denotes 1 to 8 characters,
 and yy denotes 1 to 3 characters, each of
 which being either an alphanumeric character or the underscore
 #\_.  Other properties of pathname syntax vary between
 operating systems.
When a pathname is to be fully specified (no wildcards), that
 means that no :WILD, :WILD-INFERIORS is allowed, no wildcard
 characters are allowed in the strings, and name EQ NIL may not
 be allowed either.
As permitted by the MAKE-PATHNAME specification, the PATHNAME
 directory component is canonicalized when the pathname is constructed:
 
"" and
    "." are removed"..",
    "*", and "**" are converted
    to :UP, :WILD and :WILD-INFERIORS,
    respectivelyfoo/../ are
    collapsed
Pathname components
hostNILdeviceNILdirectory = (startpoint
  . subdirs)| element | values | meaning | 
|---|---|---|
| startpoint | :RELATIVE|:ABSOLUTE | |
| subdirs | ()|( | |
| subdir | :WILD-INFERIORS | **or..., all subdirectories | 
| subdir | SIMPLE-STRING,
     may contain wildcard characters"?"and"*"(may also be specified as:WILD) | 
nametypeNIL or SIMPLE-STRING, may contain wildcard characters "?" and
  "*" (may also be specified as :WILD)
 versionNIL or :WILD or :NEWEST
    (after merging the defaults)A UNIX filename is split into name and type.
Pathname components
hostNIL or SIMPLE-STRING, wildcard characters may
   occur but do not act as wildcardsdeviceNIL or :WILD or A|...|Z
 directory = (startpoint
  . subdirs)| element | values | meaning | 
|---|---|---|
| startpoint | :RELATIVE|:ABSOLUTE | |
| subdirs | ()|( | |
| subdir | :WILD-INFERIORS | **or..., all subdirectories | 
| subdir | SIMPLE-STRING,
     may contain wildcard characters"?"and"*"(may also be specified as:WILD) | 
nametypeNIL or SIMPLE-STRING, may contain wildcard characters "?" and
  "*" (may also be specified as :WILD)
 versionNIL or :WILD or :NEWEST
    (after merging the defaults)If host is non-NIL, device must be NIL.
A Win32 filename is split into name and type.
| External notation: | "A:\sub1.typ\sub2.typ\name.typ" | 
| using defaults: |   "\sub1.typ\sub2.typ\name.typ" | 
| or |                      "name.typ" | 
| or | "*:\sub1.typ\**\sub3.typ\x*.lisp" | 
| or similar. | 
Instead of "\" one may use "/", as usual for DOS
 calls.
If host is non-NIL and the directory's startpoint
 is not :ABSOLUTE, ( will not be the same as PARSE-NAMESTRING (NAMESTRING
 pathname))pathname.
A filename is split into name and type according to the following rule:
"." in the filename, then the
   name is everything, type is NIL;".", then name is the part
   before and type the part after the last dot.if the only "." is the first character, then
   the behavior depends on the value of the user variable
    CUSTOM:*PARSE-NAMESTRING-DOT-FILE*
   which can be either
   
Due to this name/type splitting rule, there are pathnames
   that cannot result from PARSE-NAMESTRING.
   To get a pathname whose type contains a dot or whose name contains a
   dot and whose type is NIL, MAKE-PATHNAME must be used.  Example:
   (.MAKE-PATHNAME :NAME "foo.bar")
The symbol :UNSPECIFIC is not permitted as a
 pathname component for any slot of any pathname.
 It is also illegal to pass it as an argument to MAKE-PATHNAME,
 although it is a legal argument (treated as NIL)
 to USER-HOMEDIR-PATHNAME.
The only use for :UNSPECIFIC is that it is
 returned by PATHNAME-DEVICE for LOGICAL-PATHNAMEs, as required by
 [CLHS-19.3.2.1] Unspecific
  Components of a Logical Pathname.
External notation of pathnames (cf. PARSE-NAMESTRING and
 NAMESTRING), of course without spaces, [,],{,}:
| [ "/"] | "/"denotes absolute pathnames | 
| { name"/"} | each nameis a subdirectory | 
| [ name["."type] ] | filename with type (extension) | 
Name and type may be STRINGs of any LENGTH
 (consisting of printing CHARACTERs, except "/").
| [ [ drivespec] : ] | a letter "*"|a|...|z|A|...|Z | 
| { name[.type] \ } | each nameis a subdirectory,"\"may be
     replaced by"/" | 
| [ name[.type] ] | filename with type (extension) | 
Name and type may be STRINGs of any LENGTH
 (consisting of printing CHARACTERs, except "/",
 "\", ":").
No notes.
Pathname Designators. When CUSTOM:*PARSE-NAMESTRING-ANSI* is NIL, SYMBOL is also treated as a
  pathname
   designator, namely its SYMBOL-NAME is converted to the
  operating system's preferred pathname case.
Function PATHNAME-MATCH-P. PATHNAME-MATCH-P does not interpret missing components as
  wild.
TRANSLATE-PATHNAMETRANSLATE-PATHNAME accepts three additional keyword arguments:
 (TRANSLATE-PATHNAME source
 from-wildname
 to-wildname &KEY :ALL
 :MERGE :ABSOLUTE)
If :ALL is specified and non-NIL, a list of all resulting
 pathnames, corresponding to all matches of (, is
 returned.PATHNAME-MATCH-P
  source from-wildname)
If :MERGE is specified and NIL, unspecified pieces of
 to-pathname are not replaced by
 corresponding pieces of source.
If :ABSOLUTE is specified and non-NIL, the returned
 pathnames are converted to absolute by merging in the current process'
 directory, therefore rendering pathnames suitable for the OS and
 external programs.  So, to pass a pathname to an external program, you
 do ( or NAMESTRING (TRANSLATE-PATHNAME pathname
 #P"" #P"" :ABSOLUTE T))(.NAMESTRING
 (EXT:ABSOLUTE-PATHNAME pathname))
TRANSLATE-LOGICAL-PATHNAMETRANSLATE-LOGICAL-PATHNAME accepts an additional keyword
 argument :ABSOLUTE, similar to Section 19.5.1, “Function TRANSLATE-PATHNAME”.
PARSE-NAMESTRING(
 returns a logical pathname only if PARSE-NAMESTRING string &OPTIONAL
   host defaults &KEY start end
   junk-allowed)host is a
 logical host
 or host is NIL and defaults is a LOGICAL-PATHNAME.
 To construct a logical pathname from a string, the function
 LOGICAL-PATHNAME can be used.
The [ANSI CL standard] behavior of recognizing logical pathnames when
 the string begins with some alphanumeric characters followed by a
 colon (#\:) can be very confusing
 (cf. "c:/autoexec.bat",
 "home:.clisprc" and
 "prep:/pub/gnu")
 and therefore is disabled by default.
 To enable the [ANSI CL standard] behavior, you should set CUSTOM:*PARSE-NAMESTRING-ANSI* to non-NIL.
 Note that this also disables treating SYMBOLs as pathname designators.
MERGE-PATHNAMES( returns a
   logical pathname only if
 MERGE-PATHNAMES pathname
   [default-pathname])default-pathname is a LOGICAL-PATHNAME.
 To construct a logical pathname from a STRING, the function
 LOGICAL-PATHNAME can be used.
When both pathname and default-pathname
 are relative pathnames, the behavior depends on CUSTOM:*MERGE-PATHNAMES-ANSI*: when it is
 NIL, then CLISP retains its traditional behavior:
 (
 evaluates to MERGE-PATHNAMES #P"x/" #P"y/")#P"x/"
Rationale. MERGE-PATHNAMES is used to specify default components for
 pathnames, so there is some analogy between
 ( and
 MERGE-PATHNAMES a b)(.  Obviously, putting in the
 same default a second time should do the same as putting it in once:
 OR a b)( is the same as OR a b b)(, so
 OR a b)(
 should be the same as MERGE-PATHNAMES (MERGE-PATHNAMES a b) b)(.
MERGE-PATHNAMES a b)
(This question actually does matter because in Common Lisp there is no distinction between “pathnames with defaults merged-in” and “pathnames with defaults not yet applied”.)
Now, ( and MERGE-PATHNAMES (MERGE-PATHNAMES #P"x/" #P"y/")
  #P"y/")( are
 MERGE-PATHNAMES #P"x/" #P"y/")EQUAL in CLISP (when CUSTOM:*MERGE-PATHNAMES-ANSI* is NIL), but not in
 implementations that strictly follow the [ANSI CL standard].
 In fact, the above twice-default = once-default
 rule holds for all pathnames in CLISP.
Conversely, when CUSTOM:*MERGE-PATHNAMES-ANSI* is non-NIL, the normal [ANSI CL standard]
 behavior is exhibited: (
 evaluates to MERGE-PATHNAMES #P"x/" #P"y/")#P"y/x/".
Rationale. “merge” is merge and not or.
LOAD-LOGICAL-PATHNAME-TRANSLATIONSWhen the host argument to LOAD-LOGICAL-PATHNAME-TRANSLATIONS
is not a defined logical host yet, we proceed as follows:
LOGICAL_HOST_host_FROM and
  LOGICAL_HOST_host_TO exist, then their values
  define the map of the host.LOGICAL_HOST_host exists, its value is read from,
  and the result is passed to (SETF
  LOGICAL-PATHNAME-TRANSLATIONS).CUSTOM:*LOAD-LOGICAL-PATHNAME-TRANSLATIONS-DATABASE* is consulted.
  Its value should be a list of files and/or directories,
  which are searched for in the CUSTOM:*LOAD-PATHS*, just like for LOAD.
  When the element is a file, it is READ from,
  Allegro CL-style,
  odd objects being host names and even object being their
  LOGICAL-PATHNAME-TRANSLATIONS.
  When the element is a directory, a file, named hosthost.hostREAD
from once, CMUCL-style,
  the object read being the LOGICAL-PATHNAME-TRANSLATIONS of the
  host.EXT:ABSOLUTE-PATHNAME( converts the EXT:ABSOLUTE-PATHNAME pathname)pathname
 to a physical pathname, then - if its directory component is not
 absolute - converts it to an absolute pathname, by merging in the
 current process' directory. This is like TRUENAME, except that it
 does not verify that a file named by the pathname exists, not even that
 its directory exists. It does no filesystem accesses, except to
 determine the current directory. This function is useful when you want
 to save a pathname over time, or pass a pathname to an external
 program.
Table of Contents
CLISP has traditionally taken the view that a directory is a
 separate object and not a special kind of file, so whenever the
 standard says that a function operates on files
 without specifically mentioning that it also works on
 directories, CLISP SIGNALs an ERROR when passed a
 directory.
CLISP provides separate directory functions, such as
 EXT:DELETE-DIRECTORY, EXT:RENAME-DIRECTORY et al.
PROBE-FILEPROBE-FILE cannot be used to check whether a directory exists.
 Use functions EXT:PROBE-DIRECTORY or DIRECTORY for this.
FILE-AUTHORFILE-AUTHOR always returns NIL, because the operating systems
 CLISP is ported to do not store a file's author in the file system.
 Some operating systems, such as UNIX, have the notion of a file's
 owner, and some other Common Lisp implementations return
 the user name of the file owner.  CLISP does not do this, because
 owner and author are not the
 same; in particular, authorship is preserved by copying, while
 ownership is not.
Use OS:FILE-OWNER
 to find the owner of the file.  See also
 OS:FILE-PROPERTIES
 (Platform Dependent: Win32 platform only.).
EXT:PROBE-DIRECTORY( tests whether EXT:PROBE-DIRECTORY pathname)pathname exists
 and is a directory.
 It will, unlike PROBE-FILE or TRUENAME, not SIGNAL an ERROR
 if the parent directory of pathname does not exist.
DELETE-FILE( deletes the pathname
 DELETE-FILE pathname)pathname, not its TRUENAME, and returns the absolute pathname it
 actually removed or NIL if pathname did not exist.
 When pathname points to a file which is currently open in CLISP,
 an ERROR is SIGNALed.
 To remove a directory, use EXT:DELETE-DIRECTORY instead.
RENAME-FILEThis function cannot operate on directories,
  use EXT:RENAME-DIRECTORY to rename a directory.
DIRECTORY( can run in two modes:
DIRECTORY &OPTIONAL pathname &KEY
  :FULL :CIRCLE :IF-DOES-NOT-EXIST)
pathname contains no name or type component, a
  list of all matching directories is produced.
  E.g., (DIRECTORY "/etc/*/") lists
  all subdirectories in the directory
  #P"/etc/".(DIRECTORY "/etc/*") lists all
  regular files in the directory #P"/etc/".
  If the :FULL argument is non-NIL,
  additional information is returned: for each matching file you get a
  LIST of at least four elements
   (file-pathname
    file-truename
    file-write-date-as-decoded-time
    file-length).
If you want all the files and
subdirectories in the current directory, you should use
(.
If you want all the files and subdirectories in all the subdirectories
under the current directory (similar to the ls
 NCONC (DIRECTORY "*/") (DIRECTORY "*"))-R UNIX command),
use (.
NCONC (DIRECTORY "**/") (DIRECTORY "**/*"))
The argument :IF-DOES-NOT-EXIST controls the treatment of links
pointing to non-existent files and can take the following values:
:DISCARD (default):ERRORERROR is SIGNALed on bad directory entries
   (this corresponds to the default behavior of DIRECTORY in CMU CL)
:KEEP(DIRECTORY
    ... :TRUNAMEP NIL) call in CMU CL)
:IGNORE:DISCARD, but also
   do not signal an error when a directory is unaccessible (contrary to
   the [ANSI CL standard] specification).( is like EXT:DIR &OPTIONAL
 pathname)DIRECTORY, but displays the pathnames
 instead of returning them. (EXT:DIR)
 shows the contents of the current directory.
EXT:DEFAULT-DIRECTORY( is equivalent to EXT:DEFAULT-DIRECTORY)(.
 EXT:CD)( is equivalent to
 SETF (EXT:DEFAULT-DIRECTORY) pathname)(, except for the return value.EXT:CD pathname)
EXT:DELETE-DIRECTORY(
 removes an (empty) subdirectory.EXT:DELETE-DIRECTORY directory-pathname)
EXT:RENAME-DIRECTORY( renames a
 subdirectory to a new name.EXT:RENAME-DIRECTORY old-directory-pathname
  new-directory-pathname)
Table of Contents
STREAM-ELEMENT-TYPEEXT:MAKE-STREAMREAD-BYTE,
  EXT:READ-INTEGER & EXT:READ-FLOATWRITE-BYTE,
  EXT:WRITE-INTEGER & EXT:WRITE-FLOATFILE-POSITIONEXT:ELASTIC-NEWLINEOPENCLOSEOPEN-STREAM-PBROADCAST-STREAMInteractive streams are those whose next input might depend on a prompt one might output.
See also Section 32.1, “Random Screen Access”.
Input through *TERMINAL-IO* uses the GNU readline library.
  Arrow keys can be used to move within the input history.
  The TAB key completes the SYMBOL name or
  PATHNAME that is being typed.
  See readline user manual for general details and
  TAB key for CLISP-specific
  extensions.
The GNU readline library is not used (even when
   CLISP is linked against it) if the stdin and stdout do not both
   refer to the same terminal.
   This is determined by the function stdio_same_tty_p
   in file src/stream.d.
   In some exotic cases, e.g., when running under gdb in
   an rxvt window under Cygwin, this may be
   determined incorrectly.
See also Section 33.4, “Advanced Readline and History Functionality”.
Linking against GNU readline. For CLISP to use GNU readline it has to be detected by
  the configure process.
--without-readline, it will not even try to
     find GNU readline.--with-readline=default) is to use GNU readline if
     it is found and link CLISP without it otherwise.
  You can find out whether GNU readline has been detected by running
$ grep HAVE_READLINE config.hin your build directory.
EXT:WITH-KEYBOARD*TERMINAL-IO* is not the only stream that
 communicates directly with the user: During execution of the body of a
 ( form,
 EXT:WITH-KEYBOARD . body)EXT:*KEYBOARD-INPUT* is the STREAM that reads the
 keystrokes from the keyboard.
 It returns every keystroke in detail as an SYS::INPUT-CHARACTER with the
 following slots (see Section 13.2.1, “Input Characters” for accessing them):
charthe CHARACTER for standard keys
    (accessed with CHARACTER)
For non-standard keys CHARACTER SIGNALs an ERROR, use EXT:CHAR-KEY:
(EXT:WITH-KEYBOARD(LOOP:forchar= (READ-CHAREXT:*KEYBOARD-INPUT*) :forkey= (OR(EXT:CHAR-KEYchar) (CHARACTERchar)) :do (LISTcharkey)) :when (EQLkey#\Space) :return (LISTcharkey)))
keythe key name, for non-standard keys
    (accessed with EXT:CHAR-KEY):
    
bits:HYPER:SUPER:CONTROL:METAfont0.
This keyboard input is not echoed on the screen.  During execution of a
( form, no input from
EXT:WITH-KEYBOARD . body)*TERMINAL-IO* or any synonymous stream should be requested.
Since SYS::INPUT-CHARACTER is not a subtype of
   CHARACTER, READ-LINE on EXT:*KEYBOARD-INPUT* is illegal.
STREAM-ELEMENT-TYPEEXT:MAKE-STREAMREAD-BYTE,
  EXT:READ-INTEGER & EXT:READ-FLOATWRITE-BYTE,
  EXT:WRITE-INTEGER & EXT:WRITE-FLOATFILE-POSITIONEXT:ELASTIC-NEWLINEOPENCLOSEOPEN-STREAM-PBROADCAST-STREAMSTREAM-ELEMENT-TYPESTREAM-ELEMENT-TYPE is SETFable. The STREAM-ELEMENT-TYPE of
  STREAMs created by the functions OPEN, EXT:MAKE-PIPE-INPUT-STREAM
  EXT:MAKE-PIPE-OUTPUT-STREAM, EXT:MAKE-PIPE-IO-STREAM, SOCKET:SOCKET-ACCEPT, SOCKET:SOCKET-CONNECT
  can be modified, if the old and the new STREAM-ELEMENT-TYPEs are either
 
CHARACTER or
    (UNSIGNED-BYTE 8) or (SIGNED-BYTE 8); or(UNSIGNED-BYTE n) or (SIGNED-BYTE n), with the
    same n.Functions STREAM-ELEMENT-TYPE and ( are SETF
 STREAM-ELEMENT-TYPE)GENERIC-FUNCTIONs, see
 Chapter 30, Gray streams.
*STANDARD-INPUT*Note that you cannot change STREAM-ELEMENT-TYPE for some
 built-in streams, such as terminal streams,
 which is normally the value of *TERMINAL-IO*.
 Since *STANDARD-INPUT* normally is a SYNONYM-STREAM pointing
 to *TERMINAL-IO*, you cannot use READ-BYTE on it.
Since CGI
 (Common Gateway Interface) provides the form data for
 METHOD="POST" on the stdin,
 and the server will not send you an end-of-stream on the end of the data,
 you will need to use
 (
 to determine how much data you should read from EXT:GETENV "CONTENT_LENGTH")stdin.
 CLISP will detect that stdin is not a terminal and create a regular
 FILE-STREAM which can be passed to (.
 To test this functionality interactively,
 you will need to open the standard input in the binary mode:
SETF
 STREAM-ELEMENT-TYPE)
(let ((buf (MAKE-ARRAY(PARSE-INTEGER(EXT:GETENV"CONTENT_LENGTH")) :element-type '())) (UNSIGNED-BYTE8)WITH-OPEN-STREAM(in (EXT:MAKE-STREAM:INPUT:ELEMENT-TYPE'()) (UNSIGNED-BYTE8)READ-SEQUENCEbuf in)) buf)
EXT:MAKE-STREAMFunction EXT:MAKE-STREAM creates a Lisp stream out of an OS file descriptor:
 (EXT:MAKE-STREAM object &KEY :DIRECTION
  :ELEMENT-TYPE :EXTERNAL-FORMAT :BUFFERED)
object designates an OS handle (a file descriptor),
 and should be one of the following: 
:INPUT*STANDARD-INPUT*
  :OUTPUT*STANDARD-OUTPUT*
  :ERROR*ERROR-OUTPUT*
  STREAMFILE-STREAM or a SOCKET:SOCKET-STREAMWhen there are several Lisp STREAMs backed by the same OS
  file descriptor, the behavior may be highly confusing when some of the
  Lisp streams are :BUFFERED.  Use FORCE-OUTPUT for output STREAMs,
  and bulk input for input STREAMs.
The handle is duplicated (with dup),
 so it is safe to CLOSE a STREAM returned by EXT:MAKE-STREAM.
READ-BYTE,
  EXT:READ-INTEGER & EXT:READ-FLOATThe function (
 reads a multi-byte EXT:READ-INTEGER stream
    element-type &OPTIONAL ENDIANNESS eof-error-p eof-value)INTEGER from stream, which should be a
 STREAM with STREAM-ELEMENT-TYPE (.
 UNSIGNED-BYTE 8)element-type should be type equivalent to (,
 where UNSIGNED-BYTE n)n is a multiple of 8.
( is like
 EXT:READ-INTEGER stream element-type)( if READ-BYTE stream)stream's
 STREAM-ELEMENT-TYPE were set to element-type,
 except that stream's FILE-POSITION will increase by
 n/8
 instead of 1.
Together with (, this
 function permits mixed character/binary input from a stream.SETF STREAM-ELEMENT-TYPE)
The function ( reads a
 floating-point number in IEEE 754 binary representation from
 EXT:READ-FLOAT stream element-type
  &OPTIONAL ENDIANNESS eof-error-p eof-value)stream, which should be a STREAM with
 STREAM-ELEMENT-TYPE (.  UNSIGNED-BYTE 8)element-type should be
 type equivalent to SINGLE-FLOAT or DOUBLE-FLOAT.
Endianness. ENDIANNESS
   
  can be :LITTLE or :BIG.
  The default is :LITTLE, which corresponds
  to the READ-BYTE behavior in CLISP.
WRITE-BYTE,
  EXT:WRITE-INTEGER & EXT:WRITE-FLOATThe function ( writes a multi-byte EXT:WRITE-INTEGER integer stream element-type
  &OPTIONAL ENDIANNESS)INTEGER to
 stream, which should be a STREAM with
 STREAM-ELEMENT-TYPE (.  UNSIGNED-BYTE 8)element-type should be
 type equivalent to (, where UNSIGNED-BYTE n)n is a multiple of 8.
( is
 like EXT:WRITE-INTEGER integer stream element-type)( if WRITE-BYTE integer stream)stream's
 STREAM-ELEMENT-TYPE were set to element-type, except that stream's
 FILE-POSITION will increase by
 n/8
 instead of 1.
Together with (, this
  function permits mixed character/binary output to a SETF STREAM-ELEMENT-TYPE)STREAM.
The function ( writes a
 floating-point number in IEEE 754 binary representation to
 EXT:WRITE-FLOAT float
  stream element-type &OPTIONAL ENDIANNESS)stream, which should be a STREAM with STREAM-ELEMENT-TYPE
 (.  UNSIGNED-BYTE 8)element-type should be
 type equivalent to SINGLE-FLOAT or DOUBLE-FLOAT.
Function READ-SEQUENCE. In addition to READ-SEQUENCE, the following two
 functions are provided:
EXT:READ-BYTE-SEQUENCE
   performs multiple READ-BYTE operations:(
   fills the subsequence of EXT:READ-BYTE-SEQUENCE sequence
   stream &KEY :START :END :NO-HANG :INTERACTIVE)sequence specified by :START and :END
   with INTEGERs consecutively read from stream.  It returns the
   index of the first element of sequence that was not updated (=
   end or < end if the stream reached its end).
   When no-hang is non-NIL, it does not block: it treats input
   unavailability as end-of-stream. When no-hang is NIL and interactive is
   non-NIL, it can block for reading the first byte but does not block
   for any further bytes.
This function is especially efficient if sequence is a
   ( and VECTOR (UNSIGNED-BYTE 8))stream is a file/pipe/socket STREAM
   with STREAM-ELEMENT-TYPE (.
 UNSIGNED-BYTE 8)
EXT:READ-CHAR-SEQUENCE
   performs multiple READ-CHAR operations:( fills the subsequence of EXT:READ-CHAR-SEQUENCE sequence stream &KEY
    :START :END)sequence
   specified by :START and :END with characters consecutively read
   from stream.  It returns the index of the first element of
   sequence that was not updated (= end or < end if the
   stream reached its end).
This function is especially efficient if sequence is a
   STRING and stream is a file/pipe/socket STREAM with
   STREAM-ELEMENT-TYPE CHARACTER or an input STRING-STREAM.
 
Function WRITE-SEQUENCE. In addition to WRITE-SEQUENCE, the following two
functions are provided:
EXT:WRITE-BYTE-SEQUENCE
   performs multiple WRITE-BYTE operations:( outputs
  the EXT:WRITE-BYTE-SEQUENCE sequence stream
  &KEY :START :END :NO-HANG :INTERACTIVE)INTEGERs of the subsequence of sequence specified by
  :START and :END to stream.
  When no-hang is non-NIL, does not block.
  When no-hang is NIL and interactive is non-NIL, it can
  block for writing the first byte but does not block for any further
  bytes.  Returns two values: sequence and the index of the first
  byte that was not output.
This function is especially efficient if sequence is a
  ( and VECTOR (UNSIGNED-BYTE 8))stream is a file/pipe/socket STREAM with
  STREAM-ELEMENT-TYPE (.UNSIGNED-BYTE 8)
EXT:WRITE-CHAR-SEQUENCE
  performs multiple WRITE-CHAR operations:( outputs the characters of the subsequence of
  EXT:WRITE-CHAR-SEQUENCE sequence stream &KEY
  :START :END)sequence specified by :START and :END to stream.
  Returns the sequence argument.
This function is especially efficient if sequence is a
  STRING and stream is a file/pipe/socket STREAM with
  STREAM-ELEMENT-TYPE CHARACTER.
Rationale. The rationale for EXT:READ-CHAR-SEQUENCE, EXT:READ-BYTE-SEQUENCE, EXT:WRITE-CHAR-SEQUENCE and
 EXT:WRITE-BYTE-SEQUENCE is that some STREAMs support both character and binary
 i/o, and when you read into a SEQUENCE that can hold both (e.g.,
 LIST or SIMPLE-VECTOR) you cannot determine which kind of
 input to use.  In such situation READ-SEQUENCE and WRITE-SEQUENCE
 SIGNAL an ERROR, while EXT:READ-CHAR-SEQUENCE, EXT:READ-BYTE-SEQUENCE, EXT:WRITE-CHAR-SEQUENCE and
 EXT:WRITE-BYTE-SEQUENCE work just fine.
In addition to the standard functions LISTEN and
 READ-CHAR-NO-HANG, CLISP provides the following functionality
 facilitating non-blocking input and output, both binary and
 character.
(EXT:READ-CHAR-WILL-HANG-P stream)EXT:READ-CHAR-WILL-HANG-P queries the stream's input status.
  It returns NIL if READ-CHAR and PEEK-CHAR with a
  peek-type of NIL will return immediately.
  Otherwise it returns T.  (In the latter case the standard
  LISTEN function would return NIL.)
Note the difference with (: When the NOT (LISTEN
  stream))end-of-stream is reached, LISTEN returns
  NIL, whereas EXT:READ-CHAR-WILL-HANG-P returns NIL.
Note also that EXT:READ-CHAR-WILL-HANG-P is not a good way to test for end-of-stream:
  If EXT:READ-CHAR-WILL-HANG-P returns T, this does not mean that the stream will
  deliver more characters.  It only means that it is not known at this
  moment whether the stream is already at end-of-stream, or will deliver
  more characters.
(EXT:READ-BYTE-LOOKAHEAD stream)stream's
   STREAM-ELEMENT-TYPE is (UNSIGNED-BYTE 8) or (SIGNED-BYTE 8).
   Returns T if READ-BYTE would return immediately with an
   INTEGER result.
   Returns :EOF if the end-of-stream is already known to be reached.
   If READ-BYTE's value is not available immediately, returns NIL
   instead of waiting.(EXT:READ-BYTE-WILL-HANG-P stream)stream's
   STREAM-ELEMENT-TYPE is (UNSIGNED-BYTE 8) or (SIGNED-BYTE 8).
   Returns NIL if READ-BYTE will return immediately.
   Otherwise it returns true.(EXT:READ-BYTE-NO-HANG stream &OPTIONAL
    eof-error-p eof-value)stream's
   STREAM-ELEMENT-TYPE is (UNSIGNED-BYTE 8) or (SIGNED-BYTE 8).
   Returns an INTEGER or does end-of-stream handling, like READ-BYTE,
   if that would return immediately.
   If READ-BYTE's value is not available immediately, returns NIL
   instead of waiting.LISTEN on binary streamsThe [ANSI CL standard] specification for LISTEN mentions “character
   availability” as the criterion that determines the return value.
  Since a CHARACTER is never available on a
  binary STREAM (i.e., a stream with STREAM-ELEMENT-TYPE being a
  subtype of INTEGER), LISTEN returns NIL for such streams.
  (You can use SOCKET:SOCKET-STATUS to check binary streams).
  Any other behavior would be hard to make consistent: consider a bivalent
  stream, i.e., a STREAM that can be operated upon by both
  READ-CHAR and READ-BYTE.
  What should LISTEN return on such a stream if what is actually available
  on the stream at the moment is only a part of a multi-byte character?
  Right now one can use first SOCKET:SOCKET-STATUS to check if anything at all is
  available and then use LISTEN to make sure that a full CHARACTER
  is actually there.
FILE-POSITIONFILE-POSITION works on any FILE-STREAM.
EXT:ELASTIC-NEWLINEThe function ( is like
 EXT:ELASTIC-NEWLINE [stream])FRESH-LINE but the other way around: It outputs a conditional newline
 on stream, which is canceled if the next
 output on stream happens to be a newline.  More precisely, it
 causes a newline to be output right before the next character is
 written on stream, if this character is not a newline.
 The newline is also output if the next operation on the stream is
 FRESH-LINE, FINISH-OUTPUT, FORCE-OUTPUT or CLOSE.
The functionality of EXT:ELASTIC-NEWLINE is also available through
 the FORMAT directive ~..
A technique for avoiding unnecessary blank lines in output is to
 begin each chunk of output with a call to FRESH-LINE and to terminate it
 with a call to EXT:ELASTIC-NEWLINE.
See also
 doc/Newline-Convention.txt.
OPENOPEN accepts an additional keyword :BUFFERED.
The acceptable values for the arguments to the
   file/pipe/socket STREAM functions
:ELEMENT-TYPEtypes equivalent to CHARACTER or
    (, UNSIGNED-BYTE n)(; if the stream is to be
    unSIGNED-BYTE n):BUFFERED, n must be a multiple of 8.
If n is not a multiple of 8, CLISP will use the
    specified number of bits for i/o, and write the file length
    (as a number of n-bit bytes) in the preamble.
This is done to ensure the input/output consistency:
    suppose you open a file with :ELEMENT-TYPE of ( and write 7 bytes
    (i.e., 21 bit) there.
    The underlying OS can do input/output only in whole 8-bit bytes.
    Thus the OS will report the size of the file as 3 (8-bit) bytes.
    Without the preamble CLISP will have no way to know how many
    3-bit bytes to read from this file - 6, 7 or 8.
   UNSIGNED-BYTE 3)
:EXTERNAL-FORMATEXT:ENCODINGs, (constant) SYMBOLs in the
    “CHARSET” package, STRINGs (denoting iconv-based encodings),
    the symbol :DEFAULT, and the line terminator keywords
    :UNIX, :MAC, :DOS.  The default encoding is CUSTOM:*DEFAULT-FILE-ENCODING*.
    This argument determines how the lisp CHARACTER data is
    converted to/from the 8-bit bytes that the underlying OS uses.
  :BUFFEREDNIL, T, or :DEFAULT.
    Have CLISP manage an internal buffer for input or output (in
    addition to the buffering that might be used by the underlying OS).
    Buffering is a known general technique to significantly speed up i/o.
  
SOCKET:SOCKET-STREAMs and
    pipes, :DEFAULT is equivalent to
    T on the input side and to NIL on the output side; it you are
    transmitting a lot of data then using buffering
    will significantly speed up your i/o;:DEFAULT means that buffered file streams will be returned
    for regular files and (on UNIX) block-devices, and unbuffered file
    streams for special files.
  Note that some files, notably those on the /proc
  filesystem (on UNIX systems), are actually, despite their innocuous
  appearance, special files, so you might need to supply an explicit
  :BUFFERED NIL argument for them.  Actually, CLISP detects that
  the file is a /proc file, so that one is covered,
  but there are probably more strange beasts out there!
When an already opened file is opened again, a continuable ERROR is
 SIGNALed, unless both the existing and the new STREAMs are read-only
 (i.e., :DIRECTION is :INPUT or :INPUT-IMMUTABLE).
CLOSEFunction CLOSE is a GENERIC-FUNCTION, see
 Chapter 30, Gray streams.
When the :ABORT argument is non-NIL, CLOSE will not
 SIGNALs an ERROR even when the underlying OS call fails.
GET-OUTPUT-STREAM-STRING returns the same value after
 CLOSE as it would before it.
CLOSE on an already closed STREAM does nothing and returns
 T.
If you do not CLOSE your STREAM explicitly, it will be
 closed at garbage-collection time automatically.
 This is not recommended though because garbage-collection is not deterministic.
 Please use WITH-OPEN-STREAM etc.
OPEN-STREAM-PFunction OPEN-STREAM-P is a GENERIC-FUNCTION, see
 Chapter 30, Gray streams.
BROADCAST-STREAMINPUT-STREAM-P and INTERACTIVE-STREAM-P return false for
 BROADCAST-STREAMs.
(EXT:MAKE-BUFFERED-OUTPUT-STREAM
   . Returns a buffered output function)STREAM.
 function is a FUNCTION expecting one argument, a SIMPLE-STRING.
 WRITE-CHAR collects the CHARACTERs in a STRING, until a
 newline character is written or FORCE-OUTPUT/FINISH-OUTPUT is called.
 Then function is called with a SIMPLE-STRING as argument,
 that contains the characters collected so far.
 CLEAR-OUTPUT discards the characters collected so far.
(EXT:MAKE-BUFFERED-INPUT-STREAM . Returns a buffered input function
   mode)STREAM.
 function is a FUNCTION of 0 arguments that returns
 either NIL (stands for end-of-stream) or up to three values
 string, start, end.
 READ-CHAR returns the CHARACTERs of the current string one
 after another, as delimited by start and end, which default to
 0 and NIL, respectively.
 When the string is consumed, function is called again.
 The string returned by function should not be changed by the user.
 function should copy the string with COPY-SEQ or SUBSEQ before
 returning if the original string is to be modified.
 mode determines the behavior of LISTEN
 when the current string buffer is empty:
 
NILFILE-STREAM,
     i.e. function is calledTend-of-stream, i.e. one can assume that further characters will always
     arrive, without calling functionFUNCTIONFUNCTION tells, upon call, if further
     non-empty strings are to be expected.
 CLEAR-INPUT discards the rest of the current string,
 so function will be called upon the next READ-CHAR operation.
Table of Contents
Variable CUSTOM:*PRINT-CLOSURE*. An additional variable CUSTOM:*PRINT-CLOSURE* controls whether compiled and
 interpreted functions (closures) are output in detailed form.
 If CUSTOM:*PRINT-CLOSURE* is non-NIL, compiled closures are output in
 #Y syntax which the reader understands.
 CUSTOM:*PRINT-CLOSURE* is initially set to NIL.
Variable CUSTOM:*PRINT-RPARS*. An additional variable CUSTOM:*PRINT-RPARS* controls
 the output of the right (closing) parentheses.
 If CUSTOM:*PRINT-RPARS* is non-NIL, closing parentheses which do not fit onto
 the same line as the the corresponding opening parenthesis are output
 just below their corresponding opening parenthesis, in the same column.
 CUSTOM:*PRINT-RPARS* is initially set to NIL.
Variable CUSTOM:*PRINT-INDENT-LISTS*. An additional variable CUSTOM:*PRINT-INDENT-LISTS* controls the indentation of
 lists that span more than one line.
 It specifies by how many characters items within the list will be
 indented relative to the beginning of the list.
 CUSTOM:*PRINT-INDENT-LISTS* is initially set to 1.
Variable CUSTOM:*PPRINT-FIRST-NEWLINE*. An additional variable CUSTOM:*PPRINT-FIRST-NEWLINE* controls
 pretty-printing of multi-line objects.
 When CUSTOM:*PPRINT-FIRST-NEWLINE* is non-NIL,
 and the current line already has some characters on it,
 and the next object will be printed on several lines,
 and it does not start with a #\Newline,
 then a #\Newline is printed before the object.
 CUSTOM:*PPRINT-FIRST-NEWLINE* has no effect if *PRINT-PRETTY* is NIL.
 CUSTOM:*PPRINT-FIRST-NEWLINE* is initially set to T.
Characters are printed as specified in [ANSI CL standard] using
 #\, with one exception: when printer escaping is in effect,
 the space character is printed as
 “#\Space” when the
 variable CUSTOM:*PRINT-SPACE-CHAR-ANSI* is NIL.
 When CUSTOM:*PRINT-SPACE-CHAR-ANSI* is non-NIL, it is printed as
 “#\ ”; this is how
 [ANSI CL standard] specifies it.
Variable CUSTOM:*PRINT-SYMBOL-PACKAGE-PREFIX-SHORTEST*. When CUSTOM:*PRINT-SYMBOL-PACKAGE-PREFIX-SHORTEST* is non-NIL, the package
  prefix is not the PACKAGE-NAME but the shortest (nick)name as
  returned by EXT:PACKAGE-SHORTEST-NAME.  This variable is ignored when
  *PRINT-READABLY* is non-NIL.
When *PRINT-READABLY* is true, other vectors are written as
 follows: if the ARRAY-ELEMENT-TYPE is T, the syntax
 #(
 is used.  Otherwise, the syntax x0
  ... xn-1)#A( is used.element-type
 dimensions contents)
When *PRINT-READABLY* is true, other arrays are written as
 follows: if the ARRAY-ELEMENT-TYPE is T, the syntax
 # rankAcontents#A( is used.element-type dimensions
 contents)
As explicitly permitted by this section, specialized BIT and
 CHARACTER ARRAYs are printed with the innermost lists generated
 by the printing algorithm being instead printed using BIT-VECTOR and
 STRING syntax, respectively.
Variable CUSTOM:*PRINT-EMPTY-ARRAYS-ANSI*. Empty ARRAYs, i.e., arrays with no elements and zero
 ARRAY-TOTAL-SIZE (because one of its dimensions is zero) are printed
 with the readable syntax #A(, unless the variable element-type dimensions
 contents)CUSTOM:*PRINT-EMPTY-ARRAYS-ANSI* is
 non-NIL, in which case the arrays are printed using the
 [ANSI CL standard]-prescribed syntax # rankAcontents
Pathnames are printed as follows: If *PRINT-ESCAPE* is NIL,
 only the namestring is printed; otherwise it is printed with the
 #P syntax, as per the [ANSI CL standard] issue PRINT-READABLY-BEHAVIOR:CLARIFY.
 But, if *PRINT-READABLY* is true, we are in trouble as #P is
 ambiguous (which is verboten when *PRINT-READABLY* is true), while
 being mandated by the [ANSI CL standard].
 Therefore, in this case, CLISP's behavior is determined by the value
 of CUSTOM:*PRINT-PATHNAMES-ANSI*: when it is NIL, we print pathnames like this:
#-CLISP #P"..."
#+CLISP #S(PATHNAME ...)CUSTOM:*PRINT-PATHNAMES-ANSI* is non-NIL, the
 #P notation is used as per 1.5.1.4.1 Resolution of Apparent
 Conflicts in Exceptional Situations.
The #S notation for PATHNAMEs is used
  extensively in the [Common Lisp HyperSpec] (see examples for PATHNAME,
  PATHNAMEP, PARSE-NAMESTRING et al), but was decided against, see
  PATHNAME-PRINT-READ:SHARPSIGN-P.
When both *PRINT-READABLY* and CUSTOM:*PRINT-PATHNAMES-ANSI* are
  non-NIL and the namestring will be parsed to a dissimilar object
  (with the current value of CUSTOM:*PARSE-NAMESTRING-DOT-FILE*), an ERROR of type
  PRINT-NOT-READABLE is SIGNALed.
The Lisp Pretty Printer implementation is not perfect yet.
 PPRINT-LOGICAL-BLOCK does not respect *PRINT-LINES*.
A pprint
 dispatch table is a CONS of a SYMBOL
 *PRINT-PPRINT-DISPATCH* and an association list which maps types into
 priorities and print functions.
 Their use is strongly discouraged because of the performance issues:
 when *PRINT-PPRINT-DISPATCH* is non-trivial and *PRINT-PRETTY*
 is non-NIL, printing of every object requires a lookup in the table,
 which entails many calls to TYPEP (which cannot be made fast
 enough).
FORMATThe additional FORMAT instruction
 ~!
 is similar to ~/, but avoids putting a function name into a
 string, thus, even if the function is not interned in the “COMMON-LISP-USER”
 package, you might not need to specify the package explicitly.
 ( is
  equivalent to FORMAT stream "~arguments!" function object)(.FUNCALL function stream object
  colon-modifier-p
  atsign-modifier-p arguments)
The additional FORMAT instruction
 ~.
 is a kind of opposite to ~&: It outputs a conditional
 newline, by calling the function EXT:ELASTIC-NEWLINE.
 ~ outputs
 n.n-1 newlines followed by an EXT:ELASTIC-NEWLINE.
 ~0. does nothing.
FORMAT ~R and FORMAT ~:R can output only
 integers in the range |n| <
 .
 The output is in English, according to the American conventions, and
 these conventions are identical to the British conventions only in the
 range 1066|n| <
 .109
FORMAT ~:@C does not output the character itself, only the
 instruction how to type the character.
For FORMAT ~E and FORMAT ~G, the value of
 *READ-DEFAULT-FLOAT-FORMAT* does not matter if *PRINT-READABLY*
 is true.
FORMAT ~T can determine the current column of any
 built-in stream.
WRITE & WRITE-TO-STRINGThe functions WRITE and WRITE-TO-STRING have an additional
 keyword argument :CLOSURE which is used to bind
 CUSTOM:*PRINT-CLOSURE*.
PRINT-UNREADABLE-OBJECTVariable CUSTOM:*PRINT-UNREADABLE-ANSI*. The macro PRINT-UNREADABLE-OBJECT, when invoked without body forms,
 suppresses the trailing space if only the type is to be printed, and
 suppresses the leading space if only the identity is to be printed.  This
 behaviour can be turned off set setting the variable CUSTOM:*PRINT-UNREADABLE-ANSI*
 to a non-NIL value: in this case, a trailing or leading space are output,
 as prescribed by [ANSI CL standard].
*PRINT-CASE* controls the output not only of symbols, but also
 of characters and some unreadable #< objects.
In the absence of
 SYS::WRITE-FLOAT-DECIMAL
  ,
 floating point numbers are output in radix 2.  This function is defined
 in floatprint.lisp and is not available if you run
 CLISP without a memory image (which you should never do anyway!)
If *PRINT-READABLY* is true, *READ-DEFAULT-FLOAT-FORMAT*
 has no influence on the way floating point numbers are printed.
*PRINT-PRETTY* is initially NIL but set to T
 in config.lisp.  This makes screen output prettier.
 *PRINT-ARRAY* is initially set to T.
Table of Contents
When the value of ( is
 READTABLE-CASE
 readtable):INVERT, it applies to the package name and the
 symbol name of a symbol separately (not to the entire token at once).
 An alternative to the use of READTABLE-CASE is the use of the
 :CASE-SENSITIVE option of MAKE-PACKAGE and DEFPACKAGE.
recursive-p argument
  [CLHS-23.1.3.2]When non-NIL recursive-p argument is passed to a top-level READ
 call, an ERROR is SIGNALed.
Table of Contents
The compiler can be called not only by the functions COMPILE,
 COMPILE-FILE and DISASSEMBLE, but also by the declaration
 (COMPILE).
COMPILE-FILECOMPILE-FILE compiles a file to a platform-independent
 bytecode:
(COMPILE-FILEfilename&KEY:OUTPUT-FILE:LISTING:EXTERNAL-FORMAT((:WARNINGSCUSTOM:*COMPILE-WARNINGS*)CUSTOM:*COMPILE-WARNINGS*) ((:VERBOSE*COMPILE-VERBOSE*)*COMPILE-VERBOSE*) ((*COMPILE-PRINT*)*COMPILE-PRINT*))
Options for COMPILE-FILE
filename:OUTPUT-FILENIL or T or a pathname designator or an
   output STREAM.  The default is T.:LISTINGNIL or T or a pathname designator or an
   output STREAM.  The default is NIL.:EXTERNAL-FORMATEXT:ENCODING of the filename.
:WARNINGS:VERBOSE:PRINTThe variables CUSTOM:*COMPILE-WARNINGS*,
 *COMPILE-VERBOSE*, *COMPILE-PRINT* provide defaults for the
 :WARNINGS, :VERBOSE, :PRINT keyword arguments, respectively,
 and are bound by COMPILE-FILE to the values of the arguments, i.e.,
 these arguments are recursive.
For each input file (default file type: #P".lisp")
 the following files are generated:
| File | When | Default file type | Contents | 
|---|---|---|---|
| output file | only if :OUTPUT-FILEis notNIL | #P".fas" | can be loaded using the LOADfunction | 
| auxiliary output file | only if :OUTPUT-FILEis notNIL | #P".lib" | used by COMPILE-FILEwhen compiling aREQUIREform referring
    to the input file | 
| listing file | only if :LISTINGis notNIL | #P".lis" | disassembly of the output file | 
| C output file | only if :OUTPUT-FILEis notNIL | #P".c" | “FFI”; this file is created only if the source contains “FFI” forms | 
COMPILE-FILE-PATHNAMEThe default for the :OUTPUT-FILE argument is
 T, which means #P".fas".
REQUIREThe function REQUIRE receives as the optional argument either
 a PATHNAME or a LIST of PATHNAMEs: files to be LOADed
 if the required module is not already present.
At compile time, (
forms are treated specially: REQUIRE #P"foo")CUSTOM:*LOAD-PATHS* is searched for
#P"foo.lisp" and #P"foo.lib".
If the latest such file is a #P".lisp", it is compiled;
otherwise the #P".lib" is loaded.
The #P".lib" is a “header” file which contains the
constant, variable, inline and macro definitions necessary for
compilation of the files that REQUIRE this file, but not the function
definitions and calls that are not necessary for that.
Thus it is not necessary to either enclose REQUIRE forms in
EVAL-WHEN or to load the required files in the makefiles: if you have
two files, #P"foo.lisp" and #P"bar.lisp", and the
latter requires the former, you can write in your Makefile:
all: foo.fas bar.fas foo.fas: foo.lisp clisp -c foo bar.fas: bar.lisp foo.fas clisp -c bar
instead of the more cumbersome (and slower, since #P".lib"s are
usually smaller and load faster that #P".fas"s):
bar.fas: bar.lisp foo.fas
        clisp -i foo -c bar
Thus, you do not need to ( in order
to LOAD #P"foo")(.
If memory is tight, and if COMPILE-FILE #P"bar.lisp")#P"foo.lisp" contains only a few inline
functions, macros, constants or variables, this is a space and time
saver.  If #P"foo.lisp" does a lot of initializations or side effects
when being loaded, this is important as well.
LOADLOAD accepts four additional keyword arguments :ECHO,
 :COMPILING, :EXTRA-FILE-TYPES, and :OBSOLETE-ACTION.
(LOADfilename&KEY((:VERBOSE*LOAD-VERBOSE*)*LOAD-VERBOSE*) ((*LOAD-PRINT*)*LOAD-PRINT*) ((:ECHOCUSTOM:*LOAD-ECHO*)CUSTOM:*LOAD-ECHO*):IF-DOES-NOT-EXIST((:COMPILINGCUSTOM:*LOAD-COMPILING*)CUSTOM:*LOAD-COMPILING*):EXTRA-FILE-TYPES((:OBSOLETE-ACTIONCUSTOM:*LOAD-OBSOLETE-ACTION*)CUSTOM:*LOAD-OBSOLETE-ACTION*))
:VERBOSELOAD to emit a short message that a file is
    being loaded.  The default is *LOAD-VERBOSE*, which is initially
    T, but can be changed by the -v option.
 :PRINTLOAD to print the value of each form.  The
    default is *LOAD-PRINT*, which is initially NIL, but can be
    changed by the -v option.:ECHO*STANDARD-OUTPUT* (normally to the screen).  Should there be an
    error in the file, you can see at one glance where it is.
    The default is CUSTOM:*LOAD-ECHO*, which is
    initially NIL, but can be changed by the -v option.
 :COMPILINGCOMPILE-FILE - not written to a file.
    The default is CUSTOM:*LOAD-COMPILING*, which is initially
    NIL, but can be changed by the -C option.
 :EXTRA-FILE-TYPESSpecifies the LIST of additional file types
    considered for loading, in addition to CUSTOM:*SOURCE-FILE-TYPES*
    (which is initially ("lisp" "lsp" "cl"))
    and CUSTOM:*COMPILED-FILE-TYPES*
    (which is initially ("fas")).
   
When filename does not specify a unique file
    (e.g., filename is #P"foo" and both #P"foo.lisp"
    and #P"foo.fas" are found in the
    CUSTOM:*LOAD-PATHS*), then the newest file is loaded.
 
:OBSOLETE-ACTIONSpecifies the action to take when loading a
    #P".fas" with a different bytecode version from the one
    supported by this CLISP version.  The possible actions are
    
    If no file can be loaded and :IF-DOES-NOT-EXIST is non-NIL, an ERROR is SIGNALed.
    The default is CUSTOM:*LOAD-OBSOLETE-ACTION*,
    which is initially NIL.
The variables *LOAD-VERBOSE*, *LOAD-PRINT*,
CUSTOM:*LOAD-OBSOLETE-ACTION*, CUSTOM:*LOAD-COMPILING*, and CUSTOM:*LOAD-ECHO* are bound by LOAD when it
receives a corresponding keyword argument (:VERBOSE, :PRINT,
:OBSOLETE-ACTION, :COMPILING, and :ECHO), i.e., these arguments
are recursive, just like the arguments :WARNINGS, :VERBOSE, and
:PRINT for COMPILE-FILE.
When evaluation of a read form SIGNALs an ERROR, two RESTART-s are
 available:
SKIPSTOPVariable CUSTOM:*LOAD-PATHS*. The variable CUSTOM:*LOAD-PATHS* contains a list of directories where the
 files are looked for - in addition to the specified or current
 directory - by LOAD, REQUIRE, COMPILE-FILE and
 LOAD-LOGICAL-PATHNAME-TRANSLATIONS.
*FEATURES*The variable *FEATURES* initially contains the following symbols
Default *FEATURES*
:CLISP:ANSI-CL:COMMON-LISP:INTERPRETEREVAL is implemented:COMPILERCOMPILE and COMPILE-FILE are implemented
:SOCKETS:GENERIC-STREAMS:LOGICAL-PATHNAMES:FFI:GETTEXT:UNICODE:LOOPLOOP form is implemented
:CLOS:MOP:WIN32hardware = PC (clone) and operating system = Win32
  (Windows 95/98/Me/NT/2000/XP):PC386hardware = PC (clone).  It can be used as an
   indicator for the mainstream hardware characteristics (such as the
   existence of a graphics card with a non-graphics text mode,
   or the presence of a keyboard with arrows and
   Insert/Delete keys,
   or an ISA/VLB/PCI bus) or software characteristics (such as the
   Control+Alternate+Delete keyboard
   combination).:UNIXoperating system = UNIX (in this case the hardware is irrelevant!)
:BEOSoperating system = BeOS (in that case :UNIX is also present)
:CYGWIN:UNIX is also present)
:MACOSoperating system = Mac OS X (in that case :UNIX is also present)
Each module should add the appropriate keyword, e.g.,
 :SYSCALLS,
 :DIRKEY,
 :REGEXP,
 :PCRE, etc.
EXT:FEATUREP
  [CLRFI-1](EXT:FEATUREP  provides run-time access to
 the read-time conditionals form)#+ and #-.
 form is a feature exression.
EXT:COMPILED-FILE-P
  [CLRFI-2]( returns non-EXT:COMPILED-FILE-P filename)NIL
 when the file filename exists, is readable, and appears to be a
 CLISP-compiled #P".fas" file compatible with the currently used
 bytecode format.
System definition facilities (such as asdf or defsystem) can
 use it to determine whether the file needs to be recompiled.
Table of Contents
DISASSEMBLEEXT:UNCOMPILEDOCUMENTATIONDESCRIBETRACEINSPECTROOMTIMEEDAPROPOS & APROPOS-LISTDRIBBLELISP-IMPLEMENTATION-VERSIONEXT:ARGVThe debugger may be invoked through the functions
 INVOKE-DEBUGGER, BREAK, SIGNAL, ERROR, CERROR, WARN.
 The stepper is invoked through the macro STEP.
 Debugger and stepper execute subordinate read-eval-print loop (called "break loops")
 which are similar to the main read-eval-print loop except for the
 prompt and the set of available commands.
 Commands must be typed literally, in any case,
 without surrounding quotes or whitespace.
 Each command has a keyword abbreviation,
 indicated in the second column.
Table 25.1. Commands common to the main loop, the debugger and the stepper
| command | abbreviation | operation | 
|---|---|---|
| Help | :h | prints a list of available commands | 
Table 25.2. Commands common to the debugger and the stepper
| command | abbreviation | operation | 
|---|---|---|
| Abort | :a | abort to the next most recent read-eval-print loop | 
| Unwind | :uw | abort to the next most recent read-eval-print loop | 
| Quit | :q | quit to the top read-eval-print loop | 
The stack is organized into frames and other stack elements.
 Usually every invocation of an interpreted function and every
 evaluation of an interpreted form corresponds to one stack frame.
 Special forms such as LET, LET*, UNWIND-PROTECT and CATCH
 produce special kinds of stack frames.
In a break loop there is a current stack frame, which is initially the most recent stack frame but can be moved using the debugger commands Up and Down.
Evaluation of forms in a break loop occurs in the lexical environment of the current stack frame and at the same time in the dynamic environment of the debugger's caller. This means that to inspect or modify a lexical variable all you have to do is to move the current stack frame to be just below the frame that corresponds to the form or the function call that binds that variable.
There is a current stack mode which defines in how much detail the stack is shown by the stack-related debugger commands.
Table 25.3. Commands common to the debugger and the stepper
| command | abbreviation | operation | 
|---|---|---|
| Error | :e | print the last error object. | 
| Inspect | :i | INSPECTthe last error object. | 
| Mode-1 | :m1 | sets the current mode to 1: all the stack elements are considered. This mode works fine for debugging compiled functions. | 
| Mode-2 | :m2 | sets the current mode to 2: all the frames are considered. | 
| Mode-3 | :m3 | sets the current mode to 3: only lexical frames (frames that correspond to special forms that modify the lexical environment) are considered. | 
| Mode-4 | :m4 | sets the current mode to 4 (the default): only EVALandAPPLYframes are considered. Every evaluation of a form in the
    interpreter corresponds to an EVAL frame. | 
| Mode-5 | :m5 | sets the current mode to 5: only APPLYframes are
         considered. Every invocation of an interpreted function
         corresponds to oneAPPLYframe. | 
| Where | :w | shows the current stack frame. | 
| Up | :u | goes up one frame, i.e., to the caller if in mode-5 | 
| Down | :d | does down one frame, i.e., to the callee if in mode-5 | 
| Top | :t | goes to top frame, i.e., to the top-level form if in mode-4 | 
| Bottom | :b | goes to bottom (most recent) frame, i.e., most probably to the form or function that caused the debugger to be entered. | 
| Backtrace | :bt | lists the stack in current mode, bottom frame first, top frame last. | 
| Backtrace-1 | :bt1 | lists the stack in mode 1. | 
| Backtrace-2 | :bt2 | lists the stack in mode 2. | 
| Backtrace-3 | :bt3 | lists the stack in mode 3. | 
| Backtrace-4 | :bt4 | lists the stack in mode 4. | 
| Backtrace-5 | :bt5 | lists the stack in mode 5. | 
| Frame-limit | :fl | set the frame-limit: this many frames will be printed in a backtrace at most. | 
| Backtrace-l | :bl | limit of frames to print will be prompted for. | 
If the current stack frame is an EVAL or APPLY frame, the
  following commands are available as well:
Table 25.4. Commands specific to EVAL/APPLY
| command | abbreviation | operation | 
|---|---|---|
| Break+ | :br+ | sets a breakpoint in the current frame.  When the corresponding
     form or function will be left, the debugger will be entered again, with
     the variable EXT:*TRACE-VALUES*containing a list of its values. | 
| Break- | :br- | removes a breakpoint from the current frame. | 
| Redo | :rd | re-evaluates the corresponding form or function call. This command can be used to restart parts of a computation without aborting it entirely. | 
| Return | :rt | leaves the current frame. You will be prompted for the return values. | 
Table 25.5. Commands specific to the debugger
| command | abbreviation | operation | 
|---|---|---|
| Continue | :c | continues evaluation of the program. | 
Table 25.6. Commands specific to the stepper
| command | abbreviation | operation | 
|---|---|---|
| Step | :s | step into a form: evaluate this form in single step mode | 
| Next | :n | step over a form: evaluate this form at once | 
| Over | :o | step over this level: evaluate at once up to the next return | 
| Continue | :c | switch off single step mode, continue evaluation | 
The stepper is usually used like this: If some form returns a
 strange value or results in an error, call ( and navigate using the
 commands Step and Next until you
 reach the form you regard as responsible.  If you are too fast (execute
 Next once and get the error), there is no way back;
 you have to restart the entire stepper session.  If you are too slow
 (stepped into a function or a form which certainly is OK), a couple of
 Next commands or one Over command
 will help.STEP
 form)
You can set CUSTOM:*USER-COMMANDS* to a list of
 FUNCTIONs, each returning a LIST
 of bindings, i.e., either a
E.g.,
(setq CUSTOM:*USER-COMMANDS*
      (list (lambda () (list (format nil "~2%User-defined commands:")))
            (lambda ()
              (flet ((panic () (format t "don't panic, ~D~%" (random 42))))
                (list (format nil "~%panic   :p    hit the panic button!")
                      (cons "panic" #'panic)
                      (cons ":p" #'panic))))
            (lambda ()
              (let ((curses #("ouch" "yuk" "bletch")))
                (flet ((swear ()
                         (format t "~A!~%"
                                 (aref curses (random (length curses))))))
                  (list (format nil "~%swear   :e    curse")
                        (cons "swear" #'swear)
                        (cons ":e" #'swear)))))))
DISASSEMBLEEXT:UNCOMPILEDOCUMENTATIONDESCRIBETRACEINSPECTROOMTIMEEDAPROPOS & APROPOS-LISTDRIBBLELISP-IMPLEMENTATION-VERSIONEXT:ARGVDISASSEMBLEDISASSEMBLE can disassemble to machine code,
   provided that GNU gdb is present.
   In that case the argument may be a
   EXT:SYSTEM-FUNCTION, a FFI:FOREIGN-FUNCTION, a
   special operator handler, a SYMBOL denoting one of these, an
   INTEGER (address), or a STRING.
EXT:UNCOMPILEThe function EXT:UNCOMPILE does the converse of
 COMPILE: ( reverts a compiled
 EXT:UNCOMPILE function)function (name), that has been entered or loaded in the same session
 and then compiled, back to its interpreted form.
DOCUMENTATIONNo on-line documentation is available for the system functions
 (yet), but see Section 25.2.4, “Function DESCRIBE”.
DESCRIBEWhen CUSTOM:*BROWSER* is non-NIL, and CUSTOM:CLHS-ROOT returns a valid URL,
 DESCRIBE on a standard Common Lisp symbol will point your web browser to the
 appropriate [Common Lisp HyperSpec] page.
Also, when CUSTOM:*BROWSER* is non-NIL, and CUSTOM:IMPNOTES-ROOT returns a
 valid URL, DESCRIBE on symbols and packages documented in these
 implementation notes will point your web browser to the appropriate
 page.
Function CUSTOM:CLHS-ROOT. Function CUSTOM:CLHS-ROOT is defined in config.lisp.  By default it
 looks at ( and EXT:GETENV "CLHSROOT")CUSTOM:*CLHS-ROOT-DEFAULT*,
 but you may redefine it in config.lisp or RC file.
 The return value should be a STRING terminated with a "/",
 e.g., http://www.lisp.org/HyperSpec/ or /usr/doc/HyperSpec/.
 If the return value is NIL, the feature is completely disabled.
Function CUSTOM:IMPNOTES-ROOT. Function CUSTOM:IMPNOTES-ROOT is defined in config.lisp.  By default it
 looks at ( and EXT:GETENV "IMPNOTES")CUSTOM:*IMPNOTES-ROOT-DEFAULT*,
 but you may redefine it in config.lisp or RC file.
 The return value should be a STRING terminated with a "/",
 e.g., http://clisp.cons.org/impnotes/, or the path to
 the monolithic page, e.g., http://clisp.cons.org/impnotes.html
 or /usr/doc/clisp/impnotes.html.
 If the return value is NIL, the feature is completely disabled.
TRACE( makes the
 functions TRACE function ...)function, ... traced.  function should be either a symbol or
 a list (, wheresymbol &KEY
 :SUPPRESS-IF :MAX-DEPTH
 :STEP-IF
 :PRE :POST
 :PRE-BREAK-IF :POST-BREAK-IF
 :PRE-PRINT :POST-PRINT
 :PRINT)
:SUPPRESS-IF formform is true
  :MAX-DEPTH form(>
  *trace-level* form). This is useful for tracing functions that
  are use by the tracer itself, such as PRINT-OBJECT, or otherwise when
  tracing would lead to an infinite recursion.
  :STEP-IF formform is true
  :BINDINGS
   ((variable form)...)variables to the result of evaluation of
    forms around evaluation of all of the following forms
  :PRE formform before calling the function
  :POST formform after return from the function
  :PRE-BREAK-IF formform is true:POST-BREAK-IF formform is true:PRE-PRINT formform before calling the
   function:POST-PRINT formform after return from the
   function:PRINT formform both before calling
   and after return from the functionIn all these forms you can access the following variables:
EXT:*TRACE-FUNCTION*EXT:*TRACE-ARGS*EXT:*TRACE-FORM*EXT:*TRACE-VALUES*
and you can leave the function call with specified values by using
RETURN.
TRACE and UNTRACE are also applicable to functions
 ( and to macros, but not to
 locally defined functions and macros.SETF symbol)
TRACE prints this line before evaluating the form:
trace level. Trace: formtrace level. Trace: function-name ==> result
Suppose the trace level above is not enough for you to identify individual calls. You can give each call a unique id and print it:
(defun f0 (x)
  (cond ((zerop x) 1)
        ((zerop (random 2)) (* x (f0 (1- x))))
        (t (* x (f1 (1- x))))))
⇒ F0
(defun f1 (x)
  (cond ((zerop x) 1)
        ((zerop (random 2)) (* x (f0 (1- x))))
        (t (* x (f1 (1- x))))))
⇒ F1
(defvar *f0-call-count* 0)
⇒ *F0-CALL-COUNT*
(defvar *id0*)
⇒ *ID0*
(defvar *cc0*)
⇒ *CC0*
(defvar *f1-call-count* 0)
⇒ *F1-CALL-COUNT*
(defvar *id1*)
⇒ *ID1*
(defvar *cc1*)
⇒ *CC1*
(trace (f0 :bindings ((*cc0* (incf *f0-call-count*))
                      (*id0* (gensym "F0-")))
           :pre-print (list 'enter *id0* *cc0*)
           :post-print (list 'exit *id0* *cc0*))
       (f1 :bindings ((*cc1* (incf *f1-call-count*))
                      (*id1* (gensym "F1-")))
           :pre-print (list 'enter *id1* *cc1*)
           :post-print (list 'exit *id1* *cc1*)))
;; Tracing function F0.
;; Tracing function F1.
⇒ (F0 F1)
(f0 10)
1. Trace: (F0 '10)
(ENTER #:F0-2926 1)
2. Trace: (F1 '9)
(ENTER #:F1-2927 1)
3. Trace: (F0 '8)
(ENTER #:F0-2928 2)
4. Trace: (F1 '7)
(ENTER #:F1-2929 2)
5. Trace: (F1 '6)
(ENTER #:F1-2930 3)
6. Trace: (F1 '5)
(ENTER #:F1-2931 4)
7. Trace: (F1 '4)
(ENTER #:F1-2932 5)
8. Trace: (F0 '3)
(ENTER #:F0-2933 3)
9. Trace: (F1 '2)
(ENTER #:F1-2934 6)
10. Trace: (F0 '1)
(ENTER #:F0-2935 4)
11. Trace: (F1 '0)
(ENTER #:F1-2936 7)
(EXIT #:F1-2936 7)
11. Trace: F1 ==> 1
(EXIT #:F0-2935 4)
10. Trace: F0 ==> 1
(EXIT #:F1-2934 6)
9. Trace: F1 ==> 2
(EXIT #:F0-2933 3)
8. Trace: F0 ==> 6
(EXIT #:F1-2932 5)
7. Trace: F1 ==> 24
(EXIT #:F1-2931 4)
6. Trace: F1 ==> 120
(EXIT #:F1-2930 3)
5. Trace: F1 ==> 720
(EXIT #:F1-2929 2)
4. Trace: F1 ==> 5040
(EXIT #:F0-2928 2)
3. Trace: F0 ==> 40320
(EXIT #:F1-2927 1)
2. Trace: F1 ==> 362880
(EXIT #:F0-2926 1)
1. Trace: F0 ==> 3628800
⇒ 3628800
*f0-call-count*
⇒ 4
*f1-call-count*
⇒ 7
CUSTOM:*TRACE-INDENT*If you want the TRACE level to be indicated by the indentation
in addition to the printed numbers, set CUSTOM:*TRACE-INDENT* to non-NIL.
Initially it is NIL since many nested traced calls will easily
exhaust the available line length.
INSPECTThe function INSPECT takes a keyword argument
 :FRONTEND, which specifies the way CLISP will
 interact with the user, and defaults
 to CUSTOM:*INSPECT-FRONTEND*.
Available :FRONTENDs for
   INSPECT in CLISP
:TTY*TERMINAL-IO*
    stream.  Please use the :h command to get the
    list of all available commands.:HTTPA window in your Web browser (specified by the
    :BROWSER keyword argument) is opened and it is controlled by
    CLISP via a SOCKET:SOCKET-STREAM, using the HTTP protocol.
    You should be able to use all the standard browser features.
Since CLISP is not multitasking at this time, you will not
    be able to do anything else during an INSPECT session.  Please click on
    the quit link to terminate the session.
Please be aware though, that once you terminate an INSPECT
    session, all links in all INSPECT windows in your browser will become
    obsolete and using them in a new INSPECT session will result in
    unpredictable behavior.
The function INSPECT also takes a keyword argument :BROWSER,
 which specifies the browser used by the :HTTP
 front-end and defaults to CUSTOM:*INSPECT-BROWSER*.
The function INSPECT binds some
 pretty-printer variables:
 
| Variable | Bound to | 
|---|---|
| *PRINT-LENGTH* | CUSTOM:*INSPECT-PRINT-LENGTH* | 
| *PRINT-LEVEL* | CUSTOM:*INSPECT-PRINT-LEVEL* | 
| *PRINT-LINES* | CUSTOM:*INSPECT-PRINT-LINES* | 
User variable
 CUSTOM:*INSPECT-LENGTH*
 specifies the number of sequence elements printed in detail when a
 sequence is inspected.
ROOMThe function ROOM returns two values: the number of bytes
 currently occupied by Lisp objects, and the number of bytes that can be
 allocated before the next regular garbage-collection occurs.
The function
 EXT:GC
  
 starts a global garbage-collection and its return value has the same meaning as
 the second value of ROOM.
TIMEThe timing data printed by the macro TIME includes:
 
| the real time (“wall” time), | 
| the run time (processor time for this process), | 
| the number of bytes allocated, and | 
| the number of garbage-collections performed, if any. | 
The macro EXT:TIMES (mnemonic:
 “TIME and Space”)
 is like the macro TIME: ( evaluates the
 EXT:TIMES form)form, and, as a side effect, outputs detailed information about the
 memory allocations caused by this evaluation.  It also prints
 everything printed by TIME.
EDThe function ED calls the external editor specified by the value
 of (
 or, failing that, the value of the variable
 EXT:GETENV "EDITOR")CUSTOM:*EDITOR* (set in config.lisp).
 If the argument is a function name which was defined in the current
 session (not loaded from a file), the program text to be edited is a
 pretty-printed version (without comments) of the text which was used to
 define the function.
Default Time Zone
CUSTOM:*DEFAULT-TIME-ZONE*
   contains the default time zone used by ENCODE-UNIVERSAL-TIME and
   DECODE-UNIVERSAL-TIME.  It is initially set to -1
   (which means 1 hour east of Greenwich, i.e., Mid European Time).
The time zone in a decoded time does not necessarily have be an
 INTEGER, but (as FLOAT or RATIONAL number)
 it should be a multiple of 1/3600.
GET-INTERNAL-RUN-TIME returns the amount of run time
 consumed by the current CLISP process since its startup.
SHORT-SITE-NAME, LONG-SITE-NAME
   should be defined in a site-specific config.lisp file.
   The default implementations try to read the value of the environment variable
   ORGANIZATION, and, failing that,
   call uname.
SHORT-SITE-NAME, LONG-SITE-NAME
   should be defined in a site-specific config.lisp file.
   The default implementations try to read the registry.
MACHINE-TYPE, MACHINE-VERSION,
   MACHINE-INSTANCE and SHORT-SITE-NAME, LONG-SITE-NAME should be
   defined by every user in his user-specific config.lisp file.
APROPOS & APROPOS-LISTThe search performed by APROPOS and APROPOS-LIST is
 case-insensitive.
Variable CUSTOM:*APROPOS-DO-MORE*. You can make APROPOS print more information about the symbols it
 found by setting CUSTOM:*APROPOS-DO-MORE* to a list containing some of
 :FUNCTION, :VARIABLE, :TYPE, and :CLASS
 or just set it to T to get all of the values.
Variable CUSTOM:*APROPOS-MATCHER*. You can make APROPOS and APROPOS-LIST be more flexible in
 their search by setting CUSTOM:*APROPOS-MATCHER* to a FUNCTION of one
 argument, a pattern (a STRING), returning a new FUNCTION of one
 argument, a SYMBOL name (also a STRING),
 which returns non-NIL when the symbol name matches the pattern
 for the purposes of APROPOS.
 When CUSTOM:*APROPOS-MATCHER* is NIL, SEARCH is used.
 Some modules come with functions which can be used for
 CUSTOM:*APROPOS-MATCHER*, e.g., REGEXP:REGEXP-MATCHER,
 WILDCARD:WILDCARD-MATCHER,
 PCRE:PCRE-MATCHER.
DRIBBLEIf DRIBBLE is called with an argument, and dribbling is already
 enabled, a warning is printed, and the new dribbling request is
 ignored.
Dribbling is implemented via a kind (but not a recognizable subtype)
 of TWO-WAY-STREAM, named EXT:DRIBBLE-STREAM.
 If you have a source bidirectional STREAM x and you want all transactions
 (input and output) on x to be copied to the target output STREAM y,
 you can do 
(DEFVAR*loggable*x) (SETQx(MAKE-SYNONYM-STREAM'*loggable*)) (DEFUNtoggle-logging (&OPTIONALs) (MULTIPLE-VALUE-BIND(so ta) (dribble-toggle *loggable* s) (WHEN(STREAMPso) (SETQ*loggable* so)) ta)) (toggle-loggingy) ; start logging ... (toggle-logging) ; finish logging ... (toggle-loggingy) ; restart logging ... (toggle-logging) ; finish logging (CLOSEy)
    (EXT:DRIBBLE-STREAM stream)stream is a EXT:DRIBBLE-STREAM, returns two values:
    the source and the target streams.  Otherwise returns NIL.
 
    (EXT:DRIBBLE-STREAM-P stream)stream is a EXT:DRIBBLE-STREAM, returns T, otherwise
    returns NIL.
    (EXT:DRIBBLE-STREAM-SOURCE stream)stream is a EXT:DRIBBLE-STREAM, returns its
    source stream, otherwise signals a TYPE-ERROR.
 
    (EXT:DRIBBLE-STREAM-TARGET stream)stream is a EXT:DRIBBLE-STREAM, returns its
    target stream, otherwise signals a TYPE-ERROR.
 
     (EXT:MAKE-DRIBBLE-STREAM
     source target)EXT:DRIBBLE-STREAM.
 
    (EXT:DRIBBLE-TOGGLE stream
    &OPTIONAL pathname)stream is a EXT:DRIBBLE-STREAM and pathname is NIL,
    writes a dribble termination note to the stream's target
    STREAM and returns stream's source and target
    STREAMs;
    when stream is not a EXT:DRIBBLE-STREAM and pathname is non-NIL,
    creates a new EXT:DRIBBLE-STREAM, dribbling from stream to pathname,
    writes a dribble initialization note to pathname,
    and return the EXT:DRIBBLE-STREAM (the second value is the target STREAM);
    otherwise WARN that no appropriate action may be taken.
    pathname may be an open output STREAM or a pathname designator.
    See above for the sample usage.
    See also src/dribble.lisp in
    the CLISP source tree.
DRIBBLEDRIBBLE works by operating on *TERMINAL-IO*,
 thus is does not work when CLISP acts as a script interpreter
 (see Section 32.5.2, “Scripting with CLISP”).
Traditionally, Common Lisp implementations set *STANDARD-INPUT*,
 *STANDARD-OUTPUT*, and *ERROR-OUTPUT* to a SYNONYM-STREAM
 pointing to *TERMINAL-IO*, and CLISP is no exception.
 Thus changing *TERMINAL-IO* to a dribble stream affects all
 standard i/o.
On the other hand, when CLISP acts as a script interpreter,
 it adheres to the UNIX <stdio.h>
 conventions, thus *STANDARD-INPUT*,
 *STANDARD-OUTPUT*, and *ERROR-OUTPUT* are normal FILE-STREAMs,
 and thus are not affected by DRIBBLE (*TERMINAL-IO* - and
 thus ( - is still affected).
 The [ANSI CL standard] explicitly permits this behavior by stating
 PRINT ... T)
DRIBBLEis intended primarily for interactive debugging; its effect cannot be relied upon when used in a program.
LISP-IMPLEMENTATION-VERSIONLISP-IMPLEMENTATION-VERSION returns
 the numeric version (like 3.14), and
 the release date (like "1999-07-21").
 When running on the same machine on which CLISP was built, it appends
  the binary build and memory image dump date in universal time
  (like 3141592654).
 When running on a different machine, it appends the MACHINE-INSTANCE
  of the machine on which it was built.
EXT:ARGVThis function will return a fresh SIMPLE-VECTOR of
 STRING command line arguments passed to the runtime, including
 those already processed by CLISP.
 Use EXT:*ARGS* instead of this function to get the arguments for your program.
No notes.
No notes.
This is the list of [ANSI CL standard] issues and their current status in CLISP, i.e., whether CLISP supports code that makes use of the functionality specified by the vote.
X3J13 Issues
CALL-NEXT-METHOD in compiled code (items 11,12)
 QUOTE).~F, ~E,
    ~G, ~$ also bind *PRINT-BASE* to 10 and
    *PRINT-RADIX* to NILTHE, no for APPLY (spec not clear)
 CUSTOM:*PARSE-NAMESTRING-ANSI* is non-NIL
 CUSTOM:*PARSE-NAMESTRING-ANSI* is non-NIL
 CUSTOM:*SEQUENCE-COUNT-ANSI* is non-NIL;
    otherwise negative :COUNT values are not allowed.
 READ-DELIMITED-LIST still
    constructs a LISTTable of Contents
Table of Contents
DEFCLASSCLASS-NAMECLOS:CLASS-DIRECT-SUPERCLASSESCLOS:CLASS-DIRECT-SLOTSCLOS:CLASS-DIRECT-DEFAULT-INITARGSCLOS:CLASS-PRECEDENCE-LISTCLOS:CLASS-DIRECT-SUBCLASSESCLOS:CLASS-SLOTSCLOS:CLASS-DEFAULT-INITARGSCLOS:CLASS-FINALIZED-PCLOS:CLASS-PROTOTYPE(SETF CLASS-NAME)CLOS:ENSURE-CLASSCLOS:ENSURE-CLASS-USING-CLASSCLOS:FINALIZE-INHERITANCEMAKE-INSTANCEALLOCATE-INSTANCECLOS:VALIDATE-SUPERCLASSCLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGSCLOS:DIRECT-SLOT-DEFINITION-CLASSCLOS:COMPUTE-CLASS-PRECEDENCE-LISTCLOS:COMPUTE-SLOTSCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITIONCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGSCLOS:EFFECTIVE-SLOT-DEFINITION-CLASSCLOS:COMPUTE-DEFAULT-INITARGSCLOS:GENERIC-FUNCTION-NAMECLOS:GENERIC-FUNCTION-METHODSCLOS:GENERIC-FUNCTION-LAMBDA-LISTCLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDERCLOS:GENERIC-FUNCTION-DECLARATIONSCLOS:GENERIC-FUNCTION-METHOD-CLASSCLOS:GENERIC-FUNCTION-METHOD-COMBINATION(SETF CLOS:GENERIC-FUNCTION-NAME)ENSURE-GENERIC-FUNCTIONCLOS:ENSURE-GENERIC-FUNCTION-USING-CLASSADD-METHODREMOVE-METHODCLOS:COMPUTE-APPLICABLE-METHODSCLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSESCLOS:COMPUTE-EFFECTIVE-METHODCLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTIONCLOS:MAKE-METHOD-LAMBDACLOS:COMPUTE-DISCRIMINATING-FUNCTIONCLOS:STANDARD-INSTANCE-ACCESSCLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESSCLOS:SET-FUNCALLABLE-INSTANCE-FUNCTIONCLOS:SLOT-VALUE-USING-CLASS(SETF CLOS:SLOT-VALUE-USING-CLASS)CLOS:SLOT-BOUNDP-USING-CLASSCLOS:SLOT-MAKUNBOUND-USING-CLASSThe CLOS specification ([ANSI CL standard] Chanpter 7) describes the standard Programmer Interface for the Common Lisp Object System (CLOS). This document extends that specification by defining a metaobject protocol for CLOS - that is, a description of CLOS itself as an extensible CLOS program. In this description, the fundamental elements of CLOS programs (classes, slot definitions, generic functions, methods, specializers and method combinations) are represented by first-class objects. The behavior of CLOS is provided by these objects, or, more precisely, by methods specialized to the classes of these objects.
Because these objects represent pieces of CLOS programs, and because their behavior provides the behavior of the CLOS language itself, they are considered meta-level objects or metaobjects. The protocol followed by the metaobjects to provide the behavior of CLOS is called the CLOS “Metaobject Protocol” (MOP).
The description of functions follows the same form as used in the CLOS specification. The description of generic functions is similar to that in the CLOS specification, but some minor changes have been made in the way methods are presented.
The following is an example of the format for the syntax description of a generic function:
(gf1xy&OPTIONALv&KEYk)
This description indicates that gf1 is a
generic function with two required parameters, x and y, an
optional parameter v and a keyword parameter k.
The description of a generic function includes a description of its behavior. This provides the general behavior, or protocol of the generic function. All methods defined on the generic function, both portable and specified, must have behavior consistent with this description.
Every generic function described here is an instance of the class
STANDARD-GENERIC-FUNCTION and uses the STANDARD method
combination.
The description of a generic function also includes descriptions of the specified methods for that generic function. In the description of these methods, a method signature is used to describe the parameters and parameter specializers of each method. The following is an example of the format for a method signature:
(gf1 (x CLASS) y &OPTIONAL v &KEY k)
This signature indicates that this primary method on the generic
function gf1 has two required parameters, named
x and y.  In addition, there is an optional parameter v and
a keyword parameter k.  This signature also indicates that the
method's parameter specializers are the classes CLASS and T.
The description of each method includes a description of the behavior particular to that method.
An abbreviated syntax is used when referring to a method defined
elsewhere in the document.  This abbreviated syntax includes the name of
the generic function, the qualifiers, and the parameter specializers.  A
reference to the method with the signature shown above is written as:
gf1 (CLASS T)
The package exporting the Meta-Object Protocol symbols is unspecified.
The symbols specified by the Meta-Object Protocol are
  exported from the package “CLOS” and EXT:RE-EXPORTed from the package
  “EXT”.
The package exporting the Meta-Object Protocol symbols is different in other implementations: In SBCL it is the package “SB-MOP”; in OpenMCL it is the package “OPENMCL-MOP”.
For each kind of program element there is a corresponding
 basic metaobject class
  .
These are the classes: CLASS, CLOS:SLOT-DEFINITION,
GENERIC-FUNCTION, METHOD and METHOD-COMBINATION.
A metaobject class
is a subclass of exactly one of these classes.
The results are undefined if an attempt is made to define a CLASS
that is a subclass of more than one basic metaobject class.
A metaobject
is an instance of a metaobject class.
Each metaobject represents one program element.  Associated with
each metaobject is the information required to serve its role.  This
includes information that might be provided directly in a user interface
macro such as DEFCLASS or DEFMETHOD.  It also includes information
computed indirectly from other metaobjects such as that computed from
class inheritance or the full set of methods associated with a generic
function.
Much of the information associated with a metaobject is in the form of connections to other metaobjects. This interconnection means that the role of a metaobject is always based on that of other metaobjects. As an introduction to this interconnected structure, this section presents a partial enumeration of the kinds of information associated with each kind of metaobject. More detailed information is presented later.
A class metaobject determines the structure and the default behavior of its instances. The following information is associated with class metaobjects:
STRING or NIL.See also Section 29.3, “Classes”
A slot definition metaobject
  
 contains information about the definition of a slot.
There are two kinds of slot definition metaobjects:
A direct
 slot definition metaobject is used to represent the direct definition of a slot in a class.
This corresponds roughly to the slot specifiers found in DEFCLASS forms.
An effective
 slot definition metaobject is used to represent information, including inherited
 information, about a slot which is accessible in instances of a
 particular class.
Associated with each class metaobject is a list of direct slot definition metaobjects representing the slots defined directly in the class. Also associated with each class metaobject is a list of effective slot definition metaobjects representing the set of slots accessible in instances of that class.
The following information is associated with both direct and effective slot definitions metaobjects:
DEFCLASS form.DEFCLASS form.  The
  initialization form together with its lexical environment is available
  as a function of no arguments which, when called, returns the result
  of evaluating the initialization form in its lexical environment. This
  is called the initfunction of the slot.
STRING or NIL.Certain other information is only associated with direct slot definition metaobjects. This information applies only to the direct definition of the slot in the class (it is not inherited).
DEFCLASS form are broken down
  into their equivalent readers and writers in the direct slot
  definition.Information, including inherited information, which applies to the definition of a slot in a particular class in which it is accessible is associated only with effective slot definition metaobjects.
See also Section 29.4, “Slot Definitions”
A generic function metaobject contains information about a generic function over and above the information associated with each of the generic function's methods.
LIST.
The “declarations” are available as a list of declaration specifiers.
There is a slight misnomer in the naming of functions and options in this document: Where the term “declaration” is used, actually a declaration specifier is meant.
STRING or NIL.See also Section 29.5, “Generic Functions”
A method metaobject
   contains information about a specific METHOD.
LIST of of non-NIL atoms.LIST.
FUNCTION.  This
  function can be applied to arguments and a list of next methods using
  APPLY or FUNCALL.STRING or NIL.See also Section 29.6, “Methods”
A specializer metaobject
   represents the specializers of a METHOD.
 class metaobjects are themselves specializer metaobjects.  A special
 kind of specializer metaobject is used for EQL specializers.
See also Section 29.8, “Specializers”
A method combination metaobject represents the information about the method combination being used by a generic function.
This document does not specify the structure of method combination metaobjects.
See also Section 29.9, “Method Combinations”
The inheritance structure of the specified metaobject classes is
 shown in Table 29.1, “Direct Superclass Relationships
  Among The Specified Metaobject Classes”. The class of every class
 shown is STANDARD-CLASS except for the classes T and FUNCTION,
 which are instances of the class BUILT-IN-CLASS, and the classes
 GENERIC-FUNCTION and STANDARD-GENERIC-FUNCTION, which are
 instances of the class CLOS:FUNCALLABLE-STANDARD-CLASS.
Table 29.1. Direct Superclass Relationships Among The Specified Metaobject Classes
Each class with a “yes” in the “Abstract”
column is an abstract class and is not intended to
be instantiated.  The results are undefined if an attempt is made to
make an instance of one of these classes with MAKE-INSTANCE.
Each class with a “yes” in the “Subclassable” column can be used as direct superclass for portable programs. It is not meaningful to subclass a class that has a “no” in this column.
The class METHOD is also subclassable: It
  is possible to create subclasses of METHOD that do not inherit
  from STANDARD-METHOD.
The class CLOS:FUNCALLABLE-STANDARD-OBJECT's class
  precedence list contains FUNCTION before STANDARD-OBJECT, not
  after STANDARD-OBJECT.
  This is the most transparent way to realize the [ANSI CL standard] requirement
  (see the [ANSI CL standard] section 4.2.2
   “Type Relationships”)
  that GENERIC-FUNCTION's class precedence list contains
  FUNCTION before STANDARD-OBJECT.
The classes STANDARD-CLASS, CLOS:STANDARD-DIRECT-SLOT-DEFINITION, CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION,
 STANDARD-METHOD, CLOS:STANDARD-READER-METHOD,
 CLOS:STANDARD-WRITER-METHOD and STANDARD-GENERIC-FUNCTION are called
 standard metaobject
   classes.
 For each kind of metaobject, this is the class the user interface
 macros presented in the CLOS use by default.  These are also the
 classes on which user specializations are normally based.
The classes BUILT-IN-CLASS, CLOS:FUNCALLABLE-STANDARD-CLASS and
 CLOS:FORWARD-REFERENCED-CLASS are special-purpose class metaobject classes.
 Built-in classes are instances of the class BUILT-IN-CLASS.
 The class CLOS:FUNCALLABLE-STANDARD-CLASS provides a special kind of
 instances described in Section 29.10.2, “Funcallable Instances”.
 When the definition of a class references another class which has not
 yet been defined, an instance of CLOS:FORWARD-REFERENCED-CLASS is used as
 a stand-in until the class is actually defined.
CLOS:FORWARD-REFERENCED-CLASS in CLISPThe class CLOS:FORWARD-REFERENCED-CLASS is implemented in a way
  that fixes several flaws in the [AMOP] specification.
It is not a subclass of CLASS and CLOS:SPECIALIZER, just a
  subclass of CLOS:METAOBJECT, because forward references to classes are
  not classes and cannot be used as specializers of methods.  An [AMOP]
  compatibility mode is provided, however, if you set the variable
  CUSTOM:*FORWARD-REFERENCED-CLASS-MISDESIGN*
    to T.
  In this mode, CLOS:FORWARD-REFERENCED-CLASS is formally a subclass of
  CLASS and CLOS:SPECIALIZER, but the behaviour of
  CLOS:FORWARD-REFERENCED-CLASS instances is the same.
The [AMOP] says that the first argument of CLOS:ENSURE-CLASS-USING-CLASS can
  be a CLOS:FORWARD-REFERENCED-CLASS.
  But from the description of CLOS:ENSURE-CLASS, it is clear that it can
  only be a class returned by FIND-CLASS, and [ANSI CL standard] FIND-CLASS
  cannot return a CLOS:FORWARD-REFERENCED-CLASS.
The [AMOP] says that CLOS:ENSURE-CLASS-USING-CLASS creates a
  CLOS:FORWARD-REFERENCED-CLASS for not-yet-defined class symbols among the
  direct-superclasses list.  But this leads to many
  CLOS:FORWARD-REFERENCED-CLASS with the same name (since they cannot be
  stored and retrieved through FIND-CLASS), and since CHANGE-CLASS
  preserves the EQ-ness, after the class is defined, we have many
  class objects with the same name.
In the direct-superclasses list of non-finalized classes,
  CLOS:FORWARD-REFERENCED-CLASS instances can occur, denoting classes that
  have not yet been defined. When or after such a class gets defined,
  the CLOS:FORWARD-REFERENCED-CLASS instance is replaced with the real
  class.  CLISP uses simple object replacement, not CHANGE-CLASS, in
  this process.
The class STANDARD-OBJECT is the default direct
superclass of the class STANDARD-CLASS.  When an instance
of the class STANDARD-CLASS is created, and no direct superclasses are
explicitly specified, it defaults to the class STANDARD-OBJECT.  In
this way, any behavior associated with the class STANDARD-OBJECT
will be inherited, directly or indirectly, by all instances of the class
STANDARD-CLASS.  A subclass of STANDARD-CLASS may have a different
class as its default direct superclass, but that class must be a
subclass of the class STANDARD-OBJECT.
The same is true for CLOS:FUNCALLABLE-STANDARD-CLASS and
CLOS:FUNCALLABLE-STANDARD-OBJECT.
The class CLOS:SPECIALIZER captures only the most basic behavior of
method specializers, and is not itself intended to be instantiated.  The
class CLASS is a direct subclass of CLOS:SPECIALIZER reflecting the
property that classes by themselves can be used as method specializers.
The class CLOS:EQL-SPECIALIZER is used for EQL specializers.
The purpose of the Metaobject Protocol is to provide users with a powerful mechanism for extending and customizing the basic behavior of the CLOS. As an object-oriented description of the basic CLOS behavior, the Metaobject Protocol makes it possible to create these extensions by defining specialized subclasses of existing metaobject classes.
The Metaobject Protocol provides this capability without interfering with the implementor's ability to develop high-performance implementations. This balance between user extensibility and implementor freedom is mediated by placing explicit restrictions on each. Some of these restrictions are general---they apply to the entire class graph and the applicability of all methods. These are presented in this section.
The following additional terminology is used to present these restrictions:
i is interposed
  between two other classes k1 and k2 if and only if there is
  some path, following direct superclasses, from the class k1 to the
  class k2 which includes i.x1 ... xn, are defined in this
  specification as the classes k1 ... kn, but in the
  implementation, one or more of the specializers
  xl, is a superclass of the class
  given in the specification kl.
For a given generic function and set of arguments, a
  method k2 extends a method k1 if and
  only if:
  
k1 and
     k2 are both associated with the given generic function
     k1 and k2 are both applicable to the given
     arguments,k2 is executed
     before k1,k1 will be executed if and only if
   CALL-NEXT-METHOD is invoked from within the body of k2 and
   CALL-NEXT-METHOD is invoked from within the body
     of k2, thereby causing k1 to be executed.
  For a given generic function and set of arguments, a
  method k2 overrides a method k1 if and
  only if conditions i
  through iv above hold and,
  instead of v,
  
CALL-NEXT-METHOD is not invoked from within the
     body of k2, thereby preventing k1 from being executed.
Portable programs are allowed to define subclasses of specified classes, and are permitted to define methods on specified generic functions, with the following restrictions:
EQL specializer whose associated value is an instance of a specified
class.CALL-NEXT-METHOD.Portable programs may define methods that override specified methods only when the description of the specified method explicitly allows this. Typically, when a method is allowed to be overridden, a small number of related methods will need to be overridden as well.
An example of this is the specified methods on the generic
functions CLOS:ADD-DEPENDENT, CLOS:REMOVE-DEPENDENT and CLOS:MAP-DEPENDENTS.
Overriding a specified method on one of these generic functions requires
that the corresponding method on the other two generic functions be
overridden as well.
Portable methods on specified generic functions
specialized to portable metaobject classes must be defined before any
instances of those classes (or any subclasses) are created, either
directly or indirectly by a call to MAKE-INSTANCE.  Methods can be
defined after instances are created by ALLOCATE-INSTANCE however.
Portable metaobject classes cannot be redefined.
The purpose of this last restriction is to permit implementations to provide performance optimizations by analyzing, at the time the first instance of a metaobject class is initialized, what portable methods will be applicable to it. This can make it possible to optimize calls to those specified generic functions which would have no applicable portable methods.
When a metaobject class is redefined,
  CLISP issues a WARNING that the redefinition has no effect.
  To avoid this warning, place all metaobject class definitions in a
  separate file, compile it in a separate session
  (because DEFCLASS in CLISP is evaluated at compile time too;
  see Section 29.2.3.2, “Compile-file Processing of Specific User Interface Macros”),
  and then LOAD it only once per session.
The results are undefined if any of these restrictions are violated.
The specification technology used in this document needs further development. The concepts of object-oriented protocols and subclass specialization are intuitively familiar to programmers of object-oriented systems; the protocols presented here fit quite naturally into this framework. Nonetheless, in preparing this document, we have found it difficult to give specification-quality descriptions of the protocols in a way that makes it clear what extensions users can and cannot write. Object-oriented protocol specification is inherently about specifying leeway, and this seems difficult using current technology.
Implementations are allowed latitude to modify the structure of specified classes and methods. This includes: the interposition of implementation-specific classes; the promotion of specified methods; and the consolidation of two or more specified methods into a single method specialized to interposed classes.
Any such modifications are permitted only so long as for any
portable class k that is a subclass of one or more specified classes
k1 ... kn, the following conditions are met:
k, the
  classes k1 ... kn must appear in the same order as they would
  have if no implementation-specific modifications had been made.
k may inherit, by virtue of
  being a direct or indirect subclass of a specified class, any slot for
  which the name is a symbol accessible in the “COMMON-LISP-USER” package or
  exported by any package defined in the [ANSI CL standard].A list in which the first element is one of the symbols
DEFCLASS, DEFMETHOD, DEFGENERIC, DEFINE-METHOD-COMBINATION,
CLOS:GENERIC-FUNCTION, CLOS:GENERIC-FLET or CLOS:GENERIC-LABELS, and which has proper
syntax for that macro is called a user interface macro
form.  This document provides an extended specification of
the DEFCLASS, DEFMETHOD and DEFGENERIC macros.
The user interface macros DEFCLASS, DEFGENERIC and DEFMETHOD
can be used not only to define metaobjects that are instances of the
corresponding standard metaobject class, but also to define metaobjects
that are instances of appropriate portable metaobject classes.  To make
it possible for portable metaobject classes to properly process the
information appearing in the macro form, this document provides a
limited specification of the processing of these macro forms.
User interface macro forms can be evaluated or compiled and later executed. The effect of evaluating or executing a user interface macro form is specified in terms of calls to specified functions and generic functions which provide the actual behavior of the macro. The arguments received by these functions and generic functions are derived in a specified way from the macro form.
Converting a user interface macro form into the arguments to the appropriate functions and generic functions has two major aspects: the conversion of the macro argument syntax into a form more suitable for later processing, and the processing of macro arguments which are forms to be evaluated (including method bodies).
In the syntax of the DEFCLASS macro, the initform
and default-initarg-initial-value-form
arguments are forms which will be evaluated one or more times after the
macro form is evaluated or executed.  Special processing must be done on
these arguments to ensure that the lexical scope of the forms is
captured properly.  This is done by building a function of zero
arguments which, when called, returns the result of evaluating the form
in the proper lexical environment.
In the syntax of the DEFMETHOD macro
the forms argument is a list of forms that
comprise the body of the method definition.  This list of forms must be
processed specially to capture the lexical scope of the macro form.  In
addition, the lexical functions available only in the body of methods
must be introduced.  To allow this and any other special processing
(such as slot access optimization), a specializable protocol is used for
processing the body of methods.
This is discussed in Section 29.6.3.1.1, “Processing Method Bodies”.
It is a common practice for Common Lisp compilers, while processing a file
or set of files, to maintain information about the definitions that have
been compiled so far.  Among other things, this makes it possible to
ensure that a global macro definition (DEFMACRO form) which appears in
a file will affect uses of the macro later in that file.  This
information about the state of the compilation is called the
COMPILE-FILE environment.
When compiling files containing CLOS definitions, it is useful
to maintain certain additional information in the COMPILE-FILE environment.
This can make it possible to issue various kinds of warnings (e.g.,
lambda list congruence) and to do various performance optimizations that
would not otherwise be possible.
At this time, there is such significant variance in the way
existing Common Lisp implementations handle COMPILE-FILE environments that it
would be premature to specify this mechanism.  Consequently, this
document specifies only the behavior of evaluating or executing user
interface macro forms. What functions and generic functions are called
during COMPILE-FILE processing of a user interface macro form is not
specified.  Implementations are free to define and document their own
behavior.  Users may need to check implementation-specific behavior
before attempting to compile certain portable programs.
DEFCLASSSection 29.3.1, “Macro DEFCLASS”
CLISP evaluates DEFCLASS forms also at
     compile time.
DEFMETHODSection 29.6.3.1, “Macro DEFMETHOD”
CLISP does not evaluate DEFMETHOD
     forms at compile time except as necessary for signature checking.
 
DEFGENERICSection 29.5.3.1, “Macro DEFGENERIC”
CLISP does not evaluate DEFGENERIC
     forms at compile time except as necessary for signature checking.
Like other objects, metaobjects can be created by calling
MAKE-INSTANCE.  The initialization arguments passed to MAKE-INSTANCE
are used to initialize the metaobject in the usual way.  The set of
legal initialization arguments, and their interpretation, depends on the
kind of metaobject being created.  Implementations and portable programs
are free to extend the set of legal initialization arguments.  Detailed
information about the initialization of each kind of metaobject are
provided in the appropriate sections:
DEFCLASSCLASS-NAMECLOS:CLASS-DIRECT-SUPERCLASSESCLOS:CLASS-DIRECT-SLOTSCLOS:CLASS-DIRECT-DEFAULT-INITARGSCLOS:CLASS-PRECEDENCE-LISTCLOS:CLASS-DIRECT-SUBCLASSESCLOS:CLASS-SLOTSCLOS:CLASS-DEFAULT-INITARGSCLOS:CLASS-FINALIZED-PCLOS:CLASS-PROTOTYPE(SETF CLASS-NAME)CLOS:ENSURE-CLASSCLOS:ENSURE-CLASS-USING-CLASSCLOS:FINALIZE-INHERITANCEMAKE-INSTANCEALLOCATE-INSTANCECLOS:VALIDATE-SUPERCLASSCLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGSCLOS:DIRECT-SLOT-DEFINITION-CLASSCLOS:COMPUTE-CLASS-PRECEDENCE-LISTCLOS:COMPUTE-SLOTSCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITIONCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGSCLOS:EFFECTIVE-SLOT-DEFINITION-CLASSCLOS:COMPUTE-DEFAULT-INITARGSDEFCLASSThe evaluation or execution of a DEFCLASS form results in a call
to the CLOS:ENSURE-CLASS function. The arguments received by CLOS:ENSURE-CLASS
are derived from the DEFCLASS form in a defined way.  The exact
macro-expansion of the DEFCLASS form is not defined, only the
relationship between the arguments to the DEFCLASS macro and the
arguments received by the CLOS:ENSURE-CLASS function.  Examples of typical
DEFCLASS forms and sample expansions are shown in the following two
 examples:
A DEFCLASS form with
  standard slot and class options and an expansion of it that would
  result in the proper call to CLOS:ENSURE-CLASS.
(defclass plane (moving-object graphics-object)
  ((altitude :initform 0 :accessor plane-altitude)
   (speed))
  (:default-initargs :engine *jet*))
(ensure-class 'plane
  ':direct-superclasses '(moving-object graphics-object)
  ':direct-slots (list (list ':name 'altitude
                             ':initform '0
                             ':initfunction #'(lambda () 0)
                             ':readers '(plane-altitude)
                             ':writers '((setf plane-altitude)))
                       (list ':name 'speed))
  ':direct-default-initargs (list (list ':engine
                                        '*jet*
                                        #'(lambda () *jet*))))
A DEFCLASS form
  with non-standard class and slot options, and an expansion of it which
  results in the proper call to CLOS:ENSURE-CLASS.  Note that the order of
  the slot options has not affected the order of the properties in the
  canonicalized slot specification, but has affected the order of the elements
  in the lists which are the values of those properties.
(defclass sst (plane)
  ((mach mag-step 2
         locator sst-mach
         locator mach-location
         :reader mach-speed
         :reader mach))
  (:metaclass faster-class)
  (another-option foo bar))
(ensure-class 'sst
  ':direct-superclasses '(plane)
  ':direct-slots (list (list ':name 'mach
                             ':readers '(mach-speed mach)
                             'mag-step '2
                             'locator '(sst-mach mach-location)))
  ':metaclass 'faster-class
  'another-option '(foo bar))
name argument to DEFCLASS
   becomes the value of the first argument to CLOS:ENSURE-CLASS.  This is
   the only positional argument accepted by CLOS:ENSURE-CLASS; all other
   arguments are keyword arguments.:DIRECT-SUPERCLASSES argument to DEFCLASS
  becomes the value of the :DIRECT-SUPERCLASSES keyword argument to
  CLOS:ENSURE-CLASS.The :DIRECT-SLOTS argument to DEFCLASS becomes
  the value of the :DIRECT-SLOTS keyword argument to CLOS:ENSURE-CLASS.
  Special processing of this value is done to regularize the form of
  each slot specification and to properly capture the lexical scope of
  the initialization forms.  This is done by converting each slot
  specification to a property list called a
  canonicalized slot specification.
  The resulting list of canonicalized slot specifications is the value
  of the :DIRECT-SLOTS keyword argument.
Canonicalized slot
  specifications are later used as the keyword arguments to a generic
  function which will, in turn, pass them to MAKE-INSTANCE for use as
  a set of initialization arguments.  Each canonicalized slot specification is
  formed from the corresponding slot specification as follows:
  
:NAME
     property.  This property appears in every
     canonicalized slot specification.:INITFORM slot option is present in
     the slot specification, then both the :INITFORM and
     :INITFUNCTION properties are present in the canonicalized slot specification.
     The value of the :INITFORM property is the
     initialization form.  The value of the :INITFUNCTION property is
     a function of zero arguments which, when called, returns the result
     of evaluating the initialization form in its proper lexical environment.
   :INITFORM slot option is not present in
     the slot specification, then either the :INITFUNCTION property
     will not appear, or its value will be false.  In such cases, the
     value of the :INITFORM property, or whether it appears, is
     unspecified.:INITARGS property is a list
     of the values of each :INITARG slot option.  If there are no
     :INITARG slot options, then either the :INITARGS property
     will not appear or its value will be the empty list.
   :READERS property is a list of
     the values of each :READER and :ACCESSOR slot option.  If
     there are no :READER or :ACCESSOR slot options, then either
     the :READERS property will not appear or its value will be the
     empty list.:WRITERS property is a list of
     the values specified by each :WRITER and :ACCESSOR slot
     option.  The value specified by a :WRITER slot option is just
     the value of the slot option.  The value specified by an
     :ACCESSOR slot option is a two element list: the first element
     is the symbol SETF, the second element is the value of the slot
     option.  If there are no :WRITER or :ACCESSOR slot options,
     then either the :WRITERS property will not appear or its value
     will be the empty list.:DOCUMENTATION property is the
     value of the :DOCUMENTATION slot option.  If there is no
     :DOCUMENTATION slot option, then either the :DOCUMENTATION
     property will not appear or its value will be false.
   :ALLOCATION and :TYPE), but also any other options and
     values appearing in the slot specification.  If one of these slot
     options appears more than once, the value of the property will be a
     list of the specified values.The default initargs class
  option, if it is present in the DEFCLASS form, becomes the value of
  the :DIRECT-DEFAULT-INITARGS keyword argument to CLOS:ENSURE-CLASS.
  Special processing of this value is done to properly capture the
  lexical scope of the default value forms.  This is done by converting
  each default initarg in the class option into a
  canonicalized default initialization argument.
  The resulting list of canonicalized default initialization arguments is the value of
  the :DIRECT-DEFAULT-INITARGS keyword argument to CLOS:ENSURE-CLASS.
 
A canonicalized default initarg is a list of three elements. The first element is the name; the second is the actual form itself; and the third is a function of zero arguments which, when called, returns the result of evaluating the default value form in its proper lexical environment.
If a default initargs
    class option is not present in the DEFCLASS form,
    :DIRECT-DEFAULT-INITARGS NIL is passed to CLOS:ENSURE-CLASS.
This is needed to
 fulfill the [ANSI CL standard] requirement (see Section 4.6, “Redefining Classes
  [CLHS-4.3.6]”) that
 the resulting CLASS object reflects the DEFCLASS form.
The metaclass class
  option, if it is present in the DEFCLASS form, becomes the value of
  the :METACLASS keyword argument to CLOS:ENSURE-CLASS.
If a metaclass
   class option is not present in the DEFCLASS form,
   :METACLASS STANDARD-CLASS is passed to CLOS:ENSURE-CLASS.
This is needed to
 fulfill the [ANSI CL standard] requirement (see Section 4.6, “Redefining Classes
  [CLHS-4.3.6]”) that
 the resulting CLASS object reflects the DEFCLASS form.
The documentation class
  option, if it is present in the DEFCLASS form, becomes the value of
  the :DOCUMENTATION keyword argument to CLOS:ENSURE-CLASS.
If a documentation
    class option is not present in the DEFCLASS form,
    :DIRECT-DEFAULT-INITARGS NIL is passed to CLOS:ENSURE-CLASS.
This is needed to
 fulfill the [ANSI CL standard] requirement (see Section 4.6, “Redefining Classes
  [CLHS-4.3.6]”) that
 the resulting CLASS object reflects the DEFCLASS form.
Any other class options become the value of keyword
  arguments with the same name.  The value of the keyword argument is
  the tail of the class option.  An ERROR is SIGNALed if any class
  option appears more than once in the DEFCLASS form.
The default initargs of the
    metaclass are added at the end of the list
    of arguments to pass to CLOS:ENSURE-CLASS.
This is needed to
 fulfill the [ANSI CL standard] requirement (see Section 4.6, “Redefining Classes
  [CLHS-4.3.6]”) that
 the resulting CLASS object reflects the DEFCLASS form.
In the call to CLOS:ENSURE-CLASS, every element of its arguments
appears in the same left-to-right order as the corresponding element of
the DEFCLASS form, except that the order of the properties of
canonicalized slot specifications is unspecified.  The values of
properties in canonicalized slot specifications do follow this ordering
requirement.  Other ordering relationships in the keyword arguments to
CLOS:ENSURE-CLASS are unspecified.
The result of the call to CLOS:ENSURE-CLASS is returned as the result
of evaluating or executing the DEFCLASS form.
CLASS-NAMECLOS:CLASS-DIRECT-SUPERCLASSESCLOS:CLASS-DIRECT-SLOTSCLOS:CLASS-DIRECT-DEFAULT-INITARGSCLOS:CLASS-PRECEDENCE-LISTCLOS:CLASS-DIRECT-SUBCLASSESCLOS:CLASS-SLOTSCLOS:CLASS-DEFAULT-INITARGSCLOS:CLASS-FINALIZED-PCLOS:CLASS-PROTOTYPEIn this and the following sections, the “reader” generic functions which simply return information associated with a particular kind of metaobject are presented together. General information is presented first, followed by a description of the purpose of each, and ending with the specified methods for these generic functions.
The reader generic functions which simply return information associated with class metaobjects are presented together in this section.
Each of the reader generic functions for class metaobjects has the same
syntax, accepting one required argument called class, which must be
a class metaobject; otherwise, an ERROR is SIGNALed.  An ERROR is also SIGNALed if
the class metaobject has not been initialized.
These generic functions can be called by the user or the implementation.
For any of these generic functions which returns a list, such lists will not be mutated by the implementation. The results are undefined if a portable program allows such a list to be mutated.
CLASS-NAME(CLASS-NAME class)Returns the name of class.  This value can be any Lisp object,
but is usually a symbol, or NIL if the class has no name.  This is the
defaulted value of the :NAME initialization argument that was
associated with the class during initialization or reinitialization.
(Also see (SETF CLASS-NAME).)
CLOS:CLASS-DIRECT-SUPERCLASSES(CLOS:CLASS-DIRECT-SUPERCLASSES class)Returns a list of the direct superclasses of class.  The
elements of this list are class metaobjects.  The empty list is returned if
class has no direct superclasses.  This is the defaulted value of
the :DIRECT-SUPERCLASSES initialization argument that was associated
with the class during initialization or reinitialization.
For a class that has not yet been finalized,
 the returned list may contain CLOS:FORWARD-REFERENCED-CLASS instances as
 placeholder for classes that were not yet defined when finalization of
 the class was last attempted.
CLOS:CLASS-DIRECT-SLOTS(CLOS:CLASS-DIRECT-SLOTS class)Returns a set of the direct slots of class.  The elements of
this set are direct slot definition metaobjects.  If the class has no direct slots, the empty set
is returned.  This is the defaulted value of the :DIRECT-SLOTS
initialization argument that was associated with the class during
initialization and reinitialization.
CLOS:CLASS-DIRECT-DEFAULT-INITARGSReturns a list of the direct default initialization arguments for
class.  Each element of this list is a canonicalized default initialization argument.
The empty list is returned if class has no
direct default initialization arguments.  This is the defaulted value of
the :DIRECT-DEFAULT-INITARGS initialization argument that was
associated with the class during initialization or reinitialization.
CLOS:CLASS-PRECEDENCE-LIST(CLOS:CLASS-PRECEDENCE-LIST class)Returns the class precedence list of class.
 The elements of this list are class metaobjects.
During class finalization CLOS:FINALIZE-INHERITANCE calls
CLOS:COMPUTE-CLASS-PRECEDENCE-LIST to compute the class precedence list of the class.  That
value is associated with the class metaobject and is returned by CLOS:CLASS-PRECEDENCE-LIST.
This generic function SIGNALs an ERROR if class has not been finalized.
CLOS:CLASS-DIRECT-SUBCLASSES(CLOS:CLASS-DIRECT-SUBCLASSES class)Returns a set of the direct subclasses of class. The elements
of this set are class metaobjects that all mention this class among their direct
superclasses.  The empty set is returned if class has no direct
subclasses.  This value is maintained by the generic functions
CLOS:ADD-DIRECT-SUBCLASS and CLOS:REMOVE-DIRECT-SUBCLASS.
The set of direct subclasses of a class is
 internally managed as a EXT:WEAK-LIST. Therefore the existence of
 the CLOS:CLASS-DIRECT-SUBCLASSES function does not prevent otherwise
 unreferenced classes from being garbage-collected.
CLOS:CLASS-SLOTS(CLOS:CLASS-SLOTS class)Returns a possibly empty set of the slots accessible in instances
of class.  The elements of this set are effective slot definition metaobjects.
During class finalization CLOS:FINALIZE-INHERITANCE calls
CLOS:COMPUTE-SLOTS to compute the slots of the class.  That value is
associated with the class metaobject and is returned by CLOS:CLASS-SLOTS.
This generic function SIGNALs an ERROR if class has not been finalized.
CLOS:CLASS-DEFAULT-INITARGS(CLOS:CLASS-DEFAULT-INITARGS class)Returns a list of the default initialization arguments for class.
 Each element of this list is a canonicalized default initialization argument.
 The empty list is returned if class has no
 default initialization arguments.
During finalization CLOS:FINALIZE-INHERITANCE calls
CLOS:COMPUTE-DEFAULT-INITARGS to compute the default initialization
arguments for the class.  That value is associated with the class metaobject and
is returned by CLOS:CLASS-DEFAULT-INITARGS.
This generic function SIGNALs an ERROR if class has not been
finalized.
CLOS:CLASS-FINALIZED-P(CLOS:CLASS-FINALIZED-P class)Returns true if class has been finalized.  Returns false
otherwise.  Also returns false if the class has not been initialized.
CLOS:CLASS-PROTOTYPE(CLOS:CLASS-PROTOTYPE class)Returns a prototype instance of class.  Whether the instance
is initialized is not specified.  The results are undefined if a
portable program modifies the binding of any slot of a prototype instance.
This generic function SIGNALs an ERROR if class has not been finalized.
This allows non-consing[3]
  access to slots with allocation :CLASS:
(defclass counter () ((count :allocation :class :initform 0 :reader how-many))) (defmethod initialize-instance :after ((obj counter) &rest args) (incf (slot-value obj 'count))) (defclass counted-object (counter) ((name :initarg :name)))
 Now one can find out how many COUNTED-OBJECTs
 have been created by using
  (HOW-MANY (:
  CLOS:CLASS-PROTOTYPE (FIND-CLASS 'COUNTER)))
(MAKE-INSTANCE'counted-object :name 'foo) ⇒#<COUNTED-OBJECT #x203028C9>(HOW-MANY (CLOS:CLASS-PROTOTYPE(FIND-CLASS'counter))) ⇒1(MAKE-INSTANCE'counted-object :name 'bar) ⇒#<COUNTED-OBJECT #x20306CB1>(HOW-MANY (CLOS:CLASS-PROTOTYPE(FIND-CLASS'counter))) ⇒2
The specified methods for the class metaobject reader generic functions are presented below.
Each entry in the table indicates a method on one of the reader generic functions, specialized to a specified class. The number in each entry is a reference to the full description of the method. The full descriptions appear after the table.
Class Reader Methods
CLOS:FINALIZE-INHERITANCE
    (STANDARD-CLASS)CLOS:FINALIZE-INHERITANCE
    (CLOS:FUNCALLABLE-STANDARD-CLASS)SIGNALs an ERROR.CLOS:ADD-DIRECT-SUBCLASS(CLASS
    CLASS)CLOS:REMOVE-DIRECT-SUBCLASS
    (CLASS CLASS)Class finalization is the process of computing the information a class inherits from its superclasses and preparing to actually allocate instances of the class. The class finalization process includes computing the class's class precedence list, the full set of slots accessible in instances of the class and the full set of default initialization arguments for the class. These values are associated with the class metaobject and can be accessed by calling the appropriate reader. In addition, the class finalization process makes decisions about how instances of the class will be implemented.
To support forward-referenced superclasses, and to account for the
fact that not all classes are actually instantiated, class finalization
is not done as part of the initialization of the class metaobject.  Instead,
finalization is done as a separate protocol, invoked by calling the
generic function CLOS:FINALIZE-INHERITANCE.  The exact point at which
CLOS:FINALIZE-INHERITANCE is called depends on the class of the class metaobject; for
STANDARD-CLASS it is called sometime after all the classes
superclasses are defined, but no later than when the first instance of
the class is allocated (by ALLOCATE-INSTANCE).
The first step of class finalization is computing the class
precedence list.  Doing this first allows subsequent steps to access the
class precedence list.  This step is performed by calling the generic
function CLOS:COMPUTE-CLASS-PRECEDENCE-LIST.  The value returned from this call is associated
with the class metaobject and can be accessed by calling the CLOS:CLASS-PRECEDENCE-LIST generic
function.
The second step is computing the full set of slots that will be
accessible in instances of the class.  This step is performed by calling
the generic function CLOS:COMPUTE-SLOTS.  The result of this call is a list
of effective slot definition metaobjects.  This value is associated with the class metaobject and can
be accessed by calling the CLOS:CLASS-SLOTS generic function.
The behavior of CLOS:COMPUTE-SLOTS is itself layered, consisting of
calls to CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS and CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION.
The final step of class finalization is computing the full set of
initialization arguments for the class.  This is done by calling the
generic function CLOS:COMPUTE-DEFAULT-INITARGS.  The value returned by this
generic function is associated with the class metaobject and can be
accessed by calling CLOS:CLASS-DEFAULT-INITARGS.
If the class was previously finalized, CLOS:FINALIZE-INHERITANCE may
call MAKE-INSTANCES-OBSOLETE.  The circumstances under which this
happens are described in the [ANSI CL standard] section
 Section 4.6, “Redefining Classes
  [CLHS-4.3.6]”.
Forward-referenced classes, which provide a temporary definition
for a class which has been referenced but not yet defined, can never be
finalized.  An ERROR is SIGNALed if CLOS:FINALIZE-INHERITANCE is called on a
forward-referenced class.
A class metaobject can be created by calling MAKE-INSTANCE.
 The initialization arguments establish the definition of the class.
 A class metaobject can be redefined by calling REINITIALIZE-INSTANCE.
 Some classes of class metaobject do not support redefinition;
 in these cases, REINITIALIZE-INSTANCE SIGNALs an ERROR.
Initialization of a class metaobject must be done by calling MAKE-INSTANCE
and allowing it to call INITIALIZE-INSTANCE.  Reinitialization of a
class metaobject must be done by calling REINITIALIZE-INSTANCE.  Portable
programs must not 
INITIALIZE-INSTANCE directly to
    initialize a class metaobject;SHARED-INITIALIZE directly to
    initialize or reinitialize a class metaobject;CHANGE-CLASS to change the class of any
    class metaobject or to turn a non-class object into a
    class metaobject.Since metaobject classes may not be redefined,
 no behavior is specified for the result of calls to
 UPDATE-INSTANCE-FOR-REDEFINED-CLASS on class metaobjects.
 Since the class of class metaobjects may not be changed,
 no behavior is specified for the result of calls to
 UPDATE-INSTANCE-FOR-DIFFERENT-CLASS on class metaobjects.
During initialization or reinitialization, each initialization argument is checked for errors and then associated with the class metaobject. The value can then be accessed by calling the appropriate accessor as shown in Table 29.2, “Initialization arguments and accessors for class metaobjects”.
This section begins with a description of the error checking and processing of each initialization argument. This is followed by a table showing the generic functions that can be used to access the stored initialization arguments. Initialization behavior specific to the different specified class metaobject classes comes next. The section ends with a set of restrictions on portable methods affecting class metaobject initialization and reinitialization.
In these descriptions, the phrase “this argument defaults to
value” means that when that initialization argument is not
supplied, initialization or reinitialization is performed as if
value had been supplied.  For some initialization arguments this
could be done by the use of default initialization arguments, but
whether it is done this way is not specified.  Implementations are free
to define default initialization arguments for specified class metaobject classes.
Portable programs are free to define default initialization arguments
for portable subclasses of the class CLASS.
Unless there is a specific note to the contrary, then during reinitialization, if an initialization argument is not supplied, the previously stored value is left unchanged.
The :DIRECT-DEFAULT-INITARGS argument is a list
   of canonicalized default initialization arguments.
An ERROR is SIGNALed if this value is not a proper list, or if any
   element of the list is not a canonicalized default initialization argument.
If the class metaobject is being initialized, this argument defaults to the empty list.
 The :DIRECT-SLOTS argument is a list of
   canonicalized slot specifications.
An ERROR is SIGNALed if this value is not a proper list or if any
   element of the list is not a canonicalized slot specification.
  
After error checking, this value is converted to a
   list of direct slot definition metaobjects before it is associated with the class metaobject.  Conversion
   of each canonicalized slot specification to a direct slot definition metaobject is a two-step process.
   First, the generic function CLOS:DIRECT-SLOT-DEFINITION-CLASS is called with the class metaobject and
   the canonicalized slot specification to determine the class of the new
   direct slot definition metaobject; this permits both the class metaobject and the
   canonicalized slot specification to control the resulting direct slot definition metaobject class.
   Second, MAKE-INSTANCE is applied to the direct slot definition metaobject class and the
   canonicalized slot specification.
   This conversion could be implemented as shown in the
   following code:
(DEFUNconvert-to-direct-slot-definition (class canonicalized-slot) (APPLY#'MAKE-INSTANCE(APPLY#'CLOS:DIRECT-SLOT-DEFINITION-CLASSclass canonicalized-slot) canonicalized-slot))
If the class metaobject is being initialized, this argument defaults to the empty list.
Once the direct slot definition metaobjects have been created, the specified reader and
   writer methods are created.  The generic functions
   CLOS:READER-METHOD-CLASS and CLOS:WRITER-METHOD-CLASS are called to
   determine the classes of the method metaobjects created.
 The :DIRECT-SUPERCLASSES argument is a list of
   class metaobjects.  Classes which do not support multiple inheritance
   signal an error if the list contains more than one element.
An ERROR is SIGNALed if this value is not a proper list or if
   CLOS:VALIDATE-SUPERCLASS applied to class and any element of this
   list returns false.
When the class metaobject is being initialized, and this argument is
   either not supplied or is the empty list, this argument defaults as
   follows: if the class is an instance of STANDARD-CLASS or one of
   its subclasses the default value is a list of the class
   STANDARD-OBJECT; if the class is an instance of
   CLOS:FUNCALLABLE-STANDARD-CLASS or one of its subclasses the default
   value is a list of the class
   CLOS:FUNCALLABLE-STANDARD-OBJECT.
If the class is an instance of
    STRUCTURE-CLASS or one of its subclasses the default value is a
    list of the class STRUCTURE-OBJECT
After any defaulting of the value, the generic function
   CLOS:ADD-DIRECT-SUBCLASS is called once for each element of the list.
  
When the class metaobject is being reinitialized and this
   argument is supplied, the generic function CLOS:REMOVE-DIRECT-SUBCLASS
   is called once for each class metaobject in the previously stored value but not
   in the new value; the generic function CLOS:ADD-DIRECT-SUBCLASS is
   called once for each class metaobject in the new value but not in the
   previously stored value.
:DOCUMENTATION argument is
 a STRING or NIL. An ERROR is SIGNALed if it is not. This argument default
 to NIL during initialization.The :NAME argument is an object.
If the class is being initialized, this argument defaults to
   NIL.
After the processing and defaulting of initialization arguments described above, the value of each initialization argument is associated with the class metaobject. These values can then be accessed by calling the corresponding generic function. The correspondences are as follows:
Table 29.2. Initialization arguments and accessors for class metaobjects
| Initialization Argument | Generic Function | 
|---|---|
| :DIRECT-DEFAULT-INITARGS | CLOS:CLASS-DIRECT-DEFAULT-INITARGS | 
| :DIRECT-SLOTS | CLOS:CLASS-DIRECT-SLOTS | 
| :DIRECT-SUPERCLASSES | CLOS:CLASS-DIRECT-SUPERCLASSES | 
| :DOCUMENTATION | DOCUMENTATION | 
| :NAME | CLASS-NAME | 
Instances of the class STANDARD-CLASS support multiple
inheritance and reinitialization.  Instances of the class
CLOS:FUNCALLABLE-STANDARD-CLASS support multiple inheritance and
reinitialization.  For forward referenced classes, all of the
initialization arguments default to NIL.
Instances of the class STRUCTURE-CLASS do
  not support multiple inheritance and reinitialization.
Since built-in classes cannot be created or reinitialized by the
user, an ERROR is SIGNALed if INITIALIZE-INSTANCE or REINITIALIZE-INSTANCE
are called to initialize or reinitialize a derived instance of the class
BUILT-IN-CLASS.
It is not specified which methods provide the initialization and reinitialization behavior described above. Instead, the information needed to allow portable programs to specialize this behavior is presented as a set of restrictions on the methods a portable program can define. The model is that portable initialization methods have access to the class metaobject when either all or none of the specified initialization has taken effect.
These restrictions govern the methods that a portable program can
 define on the generic functions INITIALIZE-INSTANCE,
 REINITIALIZE-INSTANCE, and SHARED-INITIALIZE.
 These restrictions apply only to methods on these generic functions for
 which the first specializer is a subclass of the class CLASS.
 Other portable methods on these generic functions are not affected by
 these restrictions.
SHARED-INITIALIZE.For INITIALIZE-INSTANCE and REINITIALIZE-INSTANCE:
   
The results are undefined if any of these restrictions are violated.
class metaobjects created with MAKE-INSTANCE are usually
 anonymous; that is, they have no proper name.
An anonymous class metaobject can be given a proper name using
( and
SETF FIND-CLASS)(.SETF CLASS-NAME)
When a class metaobject is created with MAKE-INSTANCE, it is initialized
in the usual way.  The initialization arguments passed to
MAKE-INSTANCE are use to establish the definition of the class.  Each
initialization argument is checked for errors and associated with the
class metaobject.  The initialization arguments correspond roughly to the
arguments accepted by the DEFCLASS macro, and more closely to the
arguments accepted by the CLOS:ENSURE-CLASS function.
Some class metaobject classes allow their instances to be
 redefined.  When permissible, this is done by calling
 REINITIALIZE-INSTANCE.  This is discussed in the
 next section.
An example of creating an anonymous class directly using
MAKE-INSTANCE follows:
(flet ((zero () 0)
       (propellor () *propellor*))
  (make-instance 'standard-class
    :name '(my-class foo)
    :direct-superclasses (list (find-class 'plane)
                               another-anonymous-class)
    :direct-slots `((:name x
                     :initform 0
                     :initfunction ,#'zero
                     :initargs (:x)
                     :readers (position-x)
                     :writers ((setf position-x)))
                    (:name y
                     :initform 0
                     :initfunction ,#'zero
                     :initargs (:y)
                     :readers (position-y)
                     :writers ((setf position-y))))
    :direct-default-initargs `((:engine *propellor* ,#'propellor))))
Some class metaobject classes allow their instances to be reinitialized.
This is done by calling REINITIALIZE-INSTANCE.  The initialization
arguments have the same interpretation as in class initialization.
If the class metaobject was finalized before the call to REINITIALIZE-INSTANCE,
CLOS:FINALIZE-INHERITANCE will be called again once all the initialization
arguments have been processed and associated with the class metaobject.
In addition, once finalization is complete, any dependents of the
class metaobject will be updated by calling CLOS:UPDATE-DEPENDENT.
(SETF CLASS-NAME)CLOS:ENSURE-CLASSCLOS:ENSURE-CLASS-USING-CLASSCLOS:FINALIZE-INHERITANCEMAKE-INSTANCEALLOCATE-INSTANCECLOS:VALIDATE-SUPERCLASSCLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGSCLOS:DIRECT-SLOT-DEFINITION-CLASSCLOS:COMPUTE-CLASS-PRECEDENCE-LISTCLOS:COMPUTE-SLOTSCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITIONCLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGSCLOS:EFFECTIVE-SLOT-DEFINITION-CLASSCLOS:COMPUTE-DEFAULT-INITARGS(SETF CLASS-NAME)((SETF CLASS-NAME) new-name
 class)classnew-namenew-name argument.This function changes the name of class to new-name.
   This value is usually a symbol, or NIL if the class has no name.
This function works by calling REINITIALIZE-INSTANCE with
   class as its first argument, the symbol :NAME as its second
   argument and new-name as its third argument.
CLOS:ENSURE-CLASS(CLOS:ENSURE-CLASS name &KEY
    &ALLOW-OTHER-KEYS)nameSYMBOL.CLOS:ENSURE-CLASS-USING-CLASS,
      others are processed during initialization of the class metaobject
      (as described in Section 29.3.5.1, “Initialization of class metaobjects”).
This function is called to define or redefine a
   class with the specified name, and can be called by the user or the
   implementation.  It is the functional equivalent of DEFCLASS, and
   is called by the expansion of the DEFCLASS macro.
The behavior of this function is actually implemented by the
   generic function CLOS:ENSURE-CLASS-USING-CLASS.  When CLOS:ENSURE-CLASS is called,
   it immediately calls CLOS:ENSURE-CLASS-USING-CLASS and returns that result as its
   own.
The first argument to CLOS:ENSURE-CLASS-USING-CLASS is computed as
   follows:
name names a class (FIND-CLASS returns a
      class when called with name) use that class.NIL.
   The second argument is name.  The remaining arguments are the
   complete set of keyword arguments received by the CLOS:ENSURE-CLASS
   function.
CLOS:ENSURE-CLASS-USING-CLASS(CLOS:ENSURE-CLASS-USING-CLASS class name &KEY
    :DIRECT-DEFAULT-INITARGS :DIRECT-SLOTS :DIRECT-SUPERCLASSES
    :NAME :METACLASS &ALLOW-OTHER-KEYS)
 classNIL.name:METACLASSSTANDARD-CLASS.  If a class name is supplied, it is interpreted
      as the class with that name.  If a class name is supplied, but
      there is no such class, an ERROR is SIGNALed.:DIRECT-SUPERCLASSESERROR is SIGNALed if this argument is not a
      proper list.This generic function is called to define or modify
   the definition of a named class.  It is called by the CLOS:ENSURE-CLASS
   function.  It can also be called directly.
The first step performed by this generic function is to compute the set of initialization arguments which will be used to create or reinitialize the named class. The initialization arguments are computed from the full set of keyword arguments received by this generic function as follows:
:METACLASS argument is not included in the
      initialization arguments.If the :DIRECT-SUPERCLASSES argument was received
      by this generic function, it is converted into a list of class metaobjects.
      This conversion does not affect the structure of the supplied
      :DIRECT-SUPERCLASSES argument.  For each element in the
      :DIRECT-SUPERCLASSES argument:
Otherwise an instance of the class
         CLOS:FORWARD-REFERENCED-CLASS is created and used.
         The proper name of the newly created forward referenced
         class metaobject is set to the element.
A new CLOS:FORWARD-REFERENCED-CLASS
          instance is only created when one for the given class name
          does not yet exist; otherwise the existing one is reused.
          See Implementation of class CLOS:FORWARD-REFERENCED-CLASS in CLISP.
If the class argument is NIL, a new class metaobject is created
   by calling the MAKE-INSTANCE generic function with the value of the
   :METACLASS argument as its first argument, and the previously
   computed initialization arguments.  The proper name of the
   newly created class metaobject is set to name.  The newly created class metaobject is
   returned.
If the class argument is a forward referenced class,
   CHANGE-CLASS is called to change its class to the value specified
   by the :METACLASS argument.  The class metaobject is then reinitialized with
   the previously initialization arguments.  (This is a documented
   violation of the general constraint that CHANGE-CLASS may not be
   used with class metaobjects.)
    The class argument cannot be a forward referenced class. See
    Implementation of class CLOS:FORWARD-REFERENCED-CLASS in CLISP.
If the class of the class argument is not the same as the
   class specified by the :METACLASS argument, an ERROR is SIGNALed.
Otherwise, the class metaobject class is redefined by calling the
   REINITIALIZE-INSTANCE generic function with class and the
   initialization arguments.  The class argument is then
   returned.
Methods
(CLOS:ENSURE-CLASS-USING-CLASS
   (class CLASS) name &KEY :METACLASS
   :DIRECT-SUPERCLASSES &ALLOW-OTHER-KEYS)This method implements the behavior of the generic
   function in the case where the class argument is a class.
This method can be overridden.
(CLOS:ENSURE-CLASS-USING-CLASS
   (class CLOS:FORWARD-REFERENCED-CLASS) name &KEY :METACLASS
   :DIRECT-SUPERCLASSES &ALLOW-OTHER-KEYS)This method implements the behavior of the generic
   function in the case where the class argument is a forward
   referenced class.
This method does not exist.
   See Implementation of class CLOS:FORWARD-REFERENCED-CLASS in CLISP.
   Use the method specialized on NULL instead.
(CLOS:ENSURE-CLASS-USING-CLASS
   (class NULL) name &KEY :METACLASS
   :DIRECT-SUPERCLASSES &ALLOW-OTHER-KEYS)class argument is NIL.
CLOS:FINALIZE-INHERITANCE(CLOS:FINALIZE-INHERITANCE
     class)classThis generic function is called to finalize a class metaobject. This is described in Section 29.3.4, “Class Finalization Protocol”
After CLOS:FINALIZE-INHERITANCE returns, the class metaobject is
   finalized and the result of calling CLOS:CLASS-FINALIZED-P on the class metaobject
   will be true.
Methods
(CLOS:FINALIZE-INHERITANCE
   (class STANDARD-CLASS))(CLOS:FINALIZE-INHERITANCE
   (class CLOS:FUNCALLABLE-STANDARD-CLASS))(CLOS:FINALIZE-INHERITANCE
   (class CLOS:FORWARD-REFERENCED-CLASS))SIGNALs an ERROR.
MAKE-INSTANCE(MAKE-INSTANCE class &REST
    initargs)classinitargsclass.
MAKE-INSTANCE creates and
   returns a new instance of the given class.  Its behavior and use is
   described in the [ANSI CL standard].
Methods
(MAKE-INSTANCE
   (class SYMBOL) &REST initargs)MAKE-INSTANCE
   recursively on the arguments (FIND-CLASS
   class) and initargs.(MAKE-INSTANCE (class
   STANDARD-CLASS) &REST initargs)(MAKE-INSTANCE (class
   CLOS:FUNCALLABLE-STANDARD-CLASS) &REST initargs)MAKE-INSTANCE described in the [ANSI CL standard] section
   7.1
    “Object Creation and Initialization”.
ALLOCATE-INSTANCE(ALLOCATE-INSTANCE class
     &REST initargs)classinitargsclass
This generic function is called to create a new, uninitialized instance of a class. The interpretation of the concept of an uninitialized instance depends on the class metaobject class.
Before allocating the new instance, CLOS:CLASS-FINALIZED-P is
   called to see if class has been finalized.  If it has not been
   finalized, CLOS:FINALIZE-INHERITANCE is called before the new instance
   is allocated.
Methods
(ALLOCATE-INSTANCE
   (class STANDARD-CLASS) &REST initargs:INSTANCE.  These slots are unbound.
   Slots with any other allocation are ignored by this method (no
   ERROR is SIGNALed).(ALLOCATE-INSTANCE
   (class CLOS:FUNCALLABLE-STANDARD-CLASS)
   &REST initargs)This method allocates storage in the instance for
   each slot with allocation :INSTANCE.  These slots are unbound.
   Slots with any other allocation are ignored by this method (no
   ERROR is SIGNALed).
The funcallable instance function of the instance is
   undefined - the results are undefined if the instance is applied to
   arguments before CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION has been used
   to set the funcallable instance function.
(ALLOCATE-INSTANCE
   (class BUILT-IN-CLASS) &REST initargs)SIGNALs an ERROR.
CLOS:VALIDATE-SUPERCLASS(CLOS:VALIDATE-SUPERCLASS class
    superclass)classsuperclassBOOLEAN.This generic function is called to determine whether
   the class superclass is suitable for use as a superclass of
   class.
This generic function can be be called by the implementation or user code. It is called during class metaobject initialization and reinitialization, before the direct superclasses are stored. If this generic function returns false, the initialization or reinitialization will signal an error.
Methods
(CLOS:VALIDATE-SUPERCLASS
   (class CLASS) (superclass CLASS))This method returns true in three situations:
superclass argument is the class named T,
   class argument is the same
     as the class of the superclass argument, or
   STANDARD-CLASS and the class of the other is
     CLOS:FUNCALLABLE-STANDARD-CLASS.In all other cases, this method returns false.
This method can be overridden.
This method also returns true in a fourth situation:
class argument is a subclass
      of the class of the superclass argument.
 Remarks. Defining a method on CLOS:VALIDATE-SUPERCLASS requires detailed
 knowledge of of the internal protocol followed by each of the two
 class metaobject classes.  A method on CLOS:VALIDATE-SUPERCLASS which returns true
 for two different class metaobject classes declares that they are
 compatible.
CLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGS(CLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGS class &REST
     slot-spec)classslot-specThis generic function determines the initialization
   arguments for the direct slot definition for a slot in a class.
   It is called during initialization of a class.  The resulting
   initialization arguments are passed to CLOS:DIRECT-SLOT-DEFINITION-CLASS and then to
   MAKE-INSTANCE.
This generic function uses the supplied canonicalized slot specification.
   The value of :NAME in the returned initargs is the same as the value
   of :NAME in the supplied slot-spec argument.
Methods
(CLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGS
   (class STANDARD-CLASS) &REST slot-spec)(CLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGS (class
   CLOS:FUNCALLABLE-STANDARD-CLASS) &REST slot-spec)This method returns slot-spec unmodified.
This method can be overridden.
CLOS:DIRECT-SLOT-DEFINITION-CLASS(CLOS:DIRECT-SLOT-DEFINITION-CLASS class &REST
    initargs)classinitargsCLOS:DIRECT-SLOT-DEFINITION.
When a class is initialized, each of the canonicalized slot specifications must be converted to a direct slot definition metaobject. This generic function is called to determine the class of that direct slot definition metaobject.
The initargs argument is simply the
   canonicalized slot specification for the slot.
Methods
(CLOS:DIRECT-SLOT-DEFINITION-CLASS
    (class STANDARD-CLASS) &REST initargs)(CLOS:DIRECT-SLOT-DEFINITION-CLASS (class
    CLOS:FUNCALLABLE-STANDARD-CLASS) &REST initargs)These methods return the class CLOS:STANDARD-DIRECT-SLOT-DEFINITION.
  
These methods can be overridden.
CLOS:COMPUTE-CLASS-PRECEDENCE-LIST(CLOS:COMPUTE-CLASS-PRECEDENCE-LIST
     class)classThis generic-function is called to determine the class precedence list of a class.
The result is a list which contains each of class and its
   superclasses once and only once.  The first element of the list is
   class and the last element is the class named T.
All methods on this generic function must compute the class
   precedence list as a function of the ordered direct superclasses of
   the superclasses of class.  The results are undefined if the
   rules used to compute the class precedence list depend on any other
   factors.
When a class is finalized, CLOS:FINALIZE-INHERITANCE calls this
   generic function and associates the returned value with the class metaobject.
   The value can then be accessed by calling CLOS:CLASS-PRECEDENCE-LIST.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
Methods
(CLOS:COMPUTE-CLASS-PRECEDENCE-LIST (class
   CLASS))This method computes the class precedence list according to the rules described in the [ANSI CL standard] section 4.3.5 “Determining the Class Precedence List”.
This method SIGNALs an ERROR if class or any of its superclasses
  is a forward referenced class.
This method can be overridden.
CLOS:COMPUTE-SLOTS(CLOS:COMPUTE-SLOTS class)
 classThis generic function computes a set of effective
   slot definition metaobjects for the class class.  The result is a list of effective slot definition metaobjects:
   one for each slot that will be accessible in instances of class.
  
This generic function proceeds in 3 steps:
The first step collects the full set of direct slot
   definitions from the superclasses of class.
The direct slot definitions are then collected into
   individual lists, one list for each slot name associated with any of
   the direct slot definitions.  The slot names are compared with
   EQL.  Each such list is then sorted into class precedence list
   order.  Direct slot definitions coming from classes earlier in the
   class precedence list of class appear before those coming from
   classes later in the class precedence list.  For each slot name, the
   generic function CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION is called to compute an effective slot
   definition.  The result of CLOS:COMPUTE-SLOTS is a list of these
   effective slot definitions, in unspecified order.
In the final step, the location for each effective slot definition is set. This is done by specified around-methods; portable methods cannot take over this behavior. For more information on the slot definition locations, see Section 29.10.1, “Instance Structure Protocol”.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
Methods
(CLOS:COMPUTE-SLOTS
   (class STANDARD-CLASS))(CLOS:COMPUTE-SLOTS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS)}These methods implement the specified behavior of the generic function.
These methods can be overridden.
(CLOS:COMPUTE-SLOTS
   :AROUND (class STANDARD-CLASS))(CLOS:COMPUTE-SLOTS :AROUND
   (class CLOS:FUNCALLABLE-STANDARD-CLASS))CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION class name direct-slot-definitions)
 classnamedirect-slot-definitionsThis generic function determines the effective slot
   definition for a slot in a class.  It is called by CLOS:COMPUTE-SLOTS
   once for each slot accessible in instances of class.
This generic function uses the supplied list of direct slot definition metaobjects to compute the inheritance of slot properties for a single slot. The returned effective slot definition represents the result of computing the inheritance. The name of the new effective slot definition is the same as the name of the direct slot definitions supplied.
The class of the effective slot definition metaobject is determined by calling
   CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS.  The effective slot definition is then created by
   calling MAKE-INSTANCE.  The initialization arguments passed in this
   call to MAKE-INSTANCE are used to initialize the new effective slot definition metaobject.
   See Section 29.4, “Slot Definitions” for details.
Methods
(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION (class
   STANDARD-CLASS) name direct-slot-definitions)(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION (class
   CLOS:FUNCALLABLE-STANDARD-CLASS) name direct-slot-definitions)This method implements the inheritance and defaulting of slot options following the rules described in the [ANSI CL standard] section 7.5.3 “Inheritance of Slots and Options”.
This method can be extended, but the value returned by the extending method must be the value returned by this method.
The initialization arguments that are passed
  to CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS and MAKE-INSTANCE are computed through a call to
  CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS.  It is the CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS method that
  implements the inheritance rules.
CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS class direct-slot-definitions)
 classdirect-slot-definitionsThis generic function determines the initialization
   arguments for the effective slot definition for a slot in a class.
   It is called by CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION.  The resulting initialization arguments
   are passed to CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS and then to MAKE-INSTANCE.
This generic function uses the supplied list of direct slot definition metaobjects to
   compute the inheritance of slot properties for a single slot.  The
   returned effective slot definition initargs represent the result of
   computing the inheritance.  The value of :NAME in the returned
   initargs is the same as the name of the direct slot definitions
   supplied.
Methods
(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS
   (class STANDARD-CLASS) direct-slot-definitions)(CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS (class
   CLOS:FUNCALLABLE-STANDARD-CLASS) direct-slot-definitions)This method implements the inheritance and defaulting of slot options following the rules described in the [ANSI CL standard] section 7.5.3 “Inheritance of Slots and Options”.
This method can be extended.
CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS(CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS class &REST
    initargs)classinitargsCLOS:EFFECTIVE-SLOT-DEFINITION-CLASS.
CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION to
   determine the class of the resulting effective slot definition metaobject.  The initargs
   argument is the set of initialization arguments and values that will
   be passed to MAKE-INSTANCE when the effective slot definition metaobject is created.
Methods
(CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS
   (class STANDARD-CLASS) &REST initargs)(CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS (class
   CLOS:FUNCALLABLE-STANDARD-CLASS) &REST initargs)These methods return the class CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION.
  
These methods can be overridden.
CLOS:COMPUTE-DEFAULT-INITARGS(CLOS:COMPUTE-DEFAULT-INITARGS
    class)classThis generic-function is called to determine the default initialization arguments for a class.
The result is a list of canonicalized default initialization arguments, with no duplication among initialization argument names.
All methods on this generic function must compute the default initialization arguments as a function of only:
class,
     andThe results are undefined if the rules used to compute the default initialization arguments depend on any other factors.
When a class is finalized, CLOS:FINALIZE-INHERITANCE calls this
  generic function and associates the returned value with the class metaobject.
  The value can then be accessed by calling
  CLOS:CLASS-DEFAULT-INITARGS.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
Methods
(CLOS:COMPUTE-DEFAULT-INITARGS
   (class STANDARD-CLASS))(CLOS:COMPUTE-DEFAULT-INITARGS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS))These methods compute the default initialization arguments according to the rules described in the [ANSI CL standard] section 7.1.3 “Defaulting of Initialization Arguments”.
These methods signal an error if class or any of its
   superclasses is a forward referenced class.
These methods can be overridden.
CLOS:ADD-DIRECT-SUBCLASS(CLOS:ADD-DIRECT-SUBCLASS superclass
    subclass)superclasssubclassThis generic function is called to maintain a set of
   backpointers from a class to its direct subclasses.  This generic
   function adds subclass to the set of direct subclasses of
   superclass.
When a class is initialized, this generic function is called once for each direct superclass of the class.
When a class is reinitialized, this generic function is
   called once for each added direct superclass of the class.  The
   generic function CLOS:REMOVE-DIRECT-SUBCLASS is called once for each
   deleted direct superclass of the class.
Methods
(CLOS:ADD-DIRECT-SUBCLASS
   (superclass CLASS) (subclass CLASS))No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
CLOS:REMOVE-DIRECT-SUBCLASS(CLOS:REMOVE-DIRECT-SUBCLASS superclass
    subclass)superclasssubclassThis generic function is called to maintain a set of
   backpointers from a class to its direct subclasses.  It removes
   subclass from the set of direct subclasses of superclass.  No
   ERROR is SIGNALed if subclass is not in this set.
Whenever a class is reinitialized, this generic function is called once with each deleted direct superclass of the class.
Methods
(CLOS:REMOVE-DIRECT-SUBCLASS
   (superclass CLASS) (subclass CLASS))No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
CLOS:SLOT-DEFINITION-NAMECLOS:SLOT-DEFINITION-ALLOCATIONCLOS:SLOT-DEFINITION-INITFORMCLOS:SLOT-DEFINITION-INITFUNCTIONCLOS:SLOT-DEFINITION-TYPECLOS:SLOT-DEFINITION-INITARGSCLOS:SLOT-DEFINITION-NAMECLOS:SLOT-DEFINITION-ALLOCATIONCLOS:SLOT-DEFINITION-INITFORMCLOS:SLOT-DEFINITION-INITFUNCTIONCLOS:SLOT-DEFINITION-TYPECLOS:SLOT-DEFINITION-INITARGSThe reader generic functions which simply return information associated with slot definition metaobjects are presented together here in the format described in Section 29.3.3, “Introspection: Readers for class metaobjects”.
Each of the reader generic functions for slot definition metaobjects has the same
syntax, accepting one required argument called slot, which must be a
slot definition metaobject; otherwise, an ERROR is SIGNALed. An ERROR is also SIGNALed if the slot definition metaobject
has not been initialized.
These generic functions can be called by the user or the implementation.
For any of these generic functions which returns a list, such lists will not be mutated by the implementation. The results are undefined if a portable program allows such a list to be mutated.
CLOS:SLOT-DEFINITION-NAMECLOS:SLOT-DEFINITION-ALLOCATIONCLOS:SLOT-DEFINITION-INITFORMCLOS:SLOT-DEFINITION-INITFUNCTIONCLOS:SLOT-DEFINITION-TYPECLOS:SLOT-DEFINITION-INITARGSCLOS:SLOT-DEFINITION-NAME(CLOS:SLOT-DEFINITION-NAME slot)Returns the name of slot.  This value is a symbol that can be
used as a variable name.  This is the value of the :NAME
initialization argument that was associated with the slot definition metaobject during
initialization.
CLOS:SLOT-DEFINITION-ALLOCATIONReturns the allocation of slot.  This is a symbol.  This is
the defaulted value of the :ALLOCATION initialization argument that
was associated with the slot definition metaobject during initialization.
CLOS:SLOT-DEFINITION-INITFORMReturns the initialization form of slot.  This can be any
form.  This is the defaulted value of the :INITFORM initialization
argument that was associated with the slot definition metaobject during initialization.
When slot has no initialization form, the value returned is
unspecified (however, CLOS:SLOT-DEFINITION-INITFUNCTION is guaranteed to return
NIL).
CLOS:SLOT-DEFINITION-INITFUNCTIONReturns the initialization function of slot.  This value is
either a function of no arguments, or NIL, indicating that the slot
has no initialization function.  This is the defaulted value of the
:INITFUNCTION initialization argument that was associated with the
slot definition metaobject during initialization.
CLOS:SLOT-DEFINITION-TYPE(CLOS:SLOT-DEFINITION-TYPE slot)Returns the type of slot.  This is a type specifier name.
This is the defaulted value of the :TYPE initialization argument that
was associated with the slot definition metaobject during initialization.
CLOS:SLOT-DEFINITION-INITARGSReturns the set of initialization argument keywords for slot.
This is the defaulted value of the :INITARGS initialization argument
that was associated with the slot definition metaobject during initialization.
The specified methods for the slot definition metaobject readers
(CLOS:SLOT-DEFINITION-NAME
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-ALLOCATION
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-INITFORM
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-INITFUNCTION
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-TYPE
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-INITARGS
    (slot-definition CLOS:STANDARD-SLOT-DEFINITION))The following additional reader generic functions are defined for direct slot definition metaobjects.
CLOS:SLOT-DEFINITION-READERS(CLOS:SLOT-DEFINITION-READERS direct-slot-definition)Returns a (possibly empty) set of readers of the direct-slot-definition.  This
value is a list of function names.  This is the defaulted value of the
:READERS initialization argument that was associated with the direct
slot definition metaobject during initialization.
CLOS:SLOT-DEFINITION-WRITERS(CLOS:SLOT-DEFINITION-WRITERS direct-slot-definition)Returns a (possibly empty) set of writers of the direct-slot-definition.  This
value is a list of function names.  This is the defaulted value of the
:WRITERS initialization argument that was associated with the direct
slot definition metaobject during initialization.
(CLOS:SLOT-DEFINITION-READERS
    (direct-slot-definition CLOS:STANDARD-DIRECT-SLOT-DEFINITION))(CLOS:SLOT-DEFINITION-WRITERS
    (direct-slot-definition CLOS:STANDARD-DIRECT-SLOT-DEFINITION))
The following reader generic function is defined for effective slot definition metaobjects.
CLOS:SLOT-DEFINITION-LOCATION(CLOS:SLOT-DEFINITION-LOCATION effective-slot-definition)Returns the location of effective-slot-definition.  The meaning and interpretation
 of this value is described in Section 29.10.1, “Instance Structure Protocol”.
(CLOS:SLOT-DEFINITION-LOCATION
    (effective-slot-definition CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))CLOS:COMPUTE-SLOTS :AROUND
     (STANDARD-CLASS)CLOS:COMPUTE-SLOTS :AROUND
     (CLOS:FUNCALLABLE-STANDARD-CLASS)A slot definition metaobject can be created by calling MAKE-INSTANCE.  The
initialization arguments establish the definition of the slot
definition.  A slot definition metaobject cannot be redefined; calling
REINITIALIZE-INSTANCE SIGNALs an ERROR.
Initialization of a slot definition metaobject must be done by calling MAKE-INSTANCE
and allowing it to call INITIALIZE-INSTANCE.
 Portable programs must not...
INITIALIZE-INSTANCE directly to
    initialize a slot definition metaobject;SHARED-INITIALIZE directly to
    initialize a slot definition metaobject;CHANGE-CLASS to change the class of any
    slot definition metaobject or to turn a non-slot-definition object into a
    slot definition metaobject.Since metaobject classes may not be redefined, no behavior is
 specified for the result of calls to
 UPDATE-INSTANCE-FOR-REDEFINED-CLASS on slot definition metaobjects.  Since the class of a
 slot definition metaobject cannot be changed, no behavior is specified for the result of
 calls to UPDATE-INSTANCE-FOR-DIFFERENT-CLASS on slot definition metaobjects.
During initialization, each initialization argument is checked for errors and then associated with the slot definition metaobject. The value can then be accessed by calling the appropriate accessor as shown in Table 29.3, “Initialization arguments and accessors for slot definition metaobjects”.
This section begins with a description of the error checking and processing of each initialization argument. This is followed by a table showing the generic functions that can be used to access the stored initialization arguments.
In these descriptions, the phrase “this argument defaults to
value” means that when that initialization argument is not
supplied, initialization is performed as if value had been supplied.
For some initialization arguments this could be done by the use of
default initialization arguments, but whether it is done this way is not
specified.  Implementations are free to define default initialization
arguments for specified slot definition metaobject classes.  Portable programs are free to
define default initialization arguments for portable subclasses of the
class CLOS:SLOT-DEFINITION.
The :NAME argument is a slot name.  An ERROR is SIGNALed
   if this argument is not a symbol which can be used as a variable
   name.  An ERROR is SIGNALed if this argument is not supplied.
:INITFORM argument is a form. The
   :INITFORM argument defaults to NIL.  An ERROR is SIGNALed if the
   :INITFORM argument is supplied, but the :INITFUNCTION argument
   is not supplied.:INITFUNCTION argument is a function of zero
   arguments which, when called, evaluates the :INITFORM in the
   appropriate lexical environment.  The :INITFUNCTION argument
   defaults to false.  An ERROR is SIGNALed if the :INITFUNCTION argument is
   supplied, but the :INITFORM argument is not supplied.:TYPE argument is a type specifier name.  An
   ERROR is SIGNALed otherwise.  The :TYPE argument defaults to the symbol T.
 :ALLOCATION argument is a SYMBOL.  An
   ERROR is SIGNALed otherwise.  The :ALLOCATION argument defaults to the
   symbol :INSTANCE.:INITARGS argument is a LIST of SYMBOLs.
   An ERROR is SIGNALed if this argument is not a proper list, or if any
   element of this list is not a SYMBOL.  The :INITARGS argument
   defaults to the empty list.:READERS and :WRITERS arguments are
   LISTs of function names.  An ERROR is SIGNALed if they are not
   proper lists, or if any element is not a valid function name.
   They default to the empty list.  An ERROR is SIGNALed if either of these
   arguments is supplied and the metaobject is not a CLOS:DIRECT-SLOT-DEFINITION.
 :DOCUMENTATION argument is
 a STRING or NIL. An ERROR is SIGNALed if it is not. This argument default
 to NIL during initialization.After the processing and defaulting of initialization arguments described above, the value of each initialization argument is associated with the slot definition metaobject. These values can then be accessed by calling the corresponding generic function. The correspondences are as follows:
Table 29.3. Initialization arguments and accessors for slot definition metaobjects
| Initialization Argument | Generic Function | 
|---|---|
| :NAME | CLOS:SLOT-DEFINITION-NAME | 
| :INITFORM | CLOS:SLOT-DEFINITION-INITFORM | 
| :INITFUNCTION | CLOS:SLOT-DEFINITION-INITFUNCTION | 
| :TYPE | CLOS:SLOT-DEFINITION-TYPE | 
| :ALLOCATION | CLOS:SLOT-DEFINITION-ALLOCATION | 
| :INITARGS | CLOS:SLOT-DEFINITION-INITARGS | 
| :READERS | CLOS:SLOT-DEFINITION-READERS | 
| :WRITERS | CLOS:SLOT-DEFINITION-WRITERS | 
| :DOCUMENTATION | DOCUMENTATION | 
It is not specified which methods provide the initialization and reinitialization behavior described above. Instead, the information needed to allow portable programs to specialize this behavior is presented as a set of restrictions on the methods a portable program can define. The model is that portable initialization methods have access to the slot definition metaobject when either all or none of the specified initialization has taken effect.
These restrictions govern the methods that a portable program can
define on the generic functions INITIALIZE-INSTANCE,
REINITIALIZE-INSTANCE, and SHARED-INITIALIZE.  These restrictions
apply only to methods on these generic functions for which the first
specializer is a subclass of the class CLOS:SLOT-DEFINITION.  Other portable
methods on these generic functions are not affected by these
restrictions.
SHARED-INITIALIZE or REINITIALIZE-INSTANCE.For INITIALIZE-INSTANCE:
   
The results are undefined if any of these restrictions are violated.
CLOS:GENERIC-FUNCTION-NAMECLOS:GENERIC-FUNCTION-METHODSCLOS:GENERIC-FUNCTION-LAMBDA-LISTCLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDERCLOS:GENERIC-FUNCTION-DECLARATIONSCLOS:GENERIC-FUNCTION-METHOD-CLASSCLOS:GENERIC-FUNCTION-METHOD-COMBINATION(SETF CLOS:GENERIC-FUNCTION-NAME)ENSURE-GENERIC-FUNCTIONCLOS:ENSURE-GENERIC-FUNCTION-USING-CLASSADD-METHODREMOVE-METHODCLOS:COMPUTE-APPLICABLE-METHODSCLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSESCLOS:COMPUTE-EFFECTIVE-METHODCLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTIONCLOS:MAKE-METHOD-LAMBDACLOS:COMPUTE-DISCRIMINATING-FUNCTIONCLOS:GENERIC-FUNCTION-NAMECLOS:GENERIC-FUNCTION-METHODSCLOS:GENERIC-FUNCTION-LAMBDA-LISTCLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDERCLOS:GENERIC-FUNCTION-DECLARATIONSCLOS:GENERIC-FUNCTION-METHOD-CLASSCLOS:GENERIC-FUNCTION-METHOD-COMBINATIONThe reader generic functions which simply return information associated with generic function metaobjects are presented together here in the format described in Section 29.3.3, “Introspection: Readers for class metaobjects”.
Each of the reader generic functions for generic function metaobjects has the same
syntax, accepting one required argument called generic-function, which must be a
generic function metaobject; otherwise, an ERROR is SIGNALed.  An ERROR is also SIGNALed if the
generic function metaobject has not been initialized.
These generic functions can be called by the user or the implementation.
For any of these generic functions which returns a list, such lists will not be mutated by the implementation. The results are undefined if a portable program allows such a list to be mutated.
CLOS:GENERIC-FUNCTION-NAME(CLOS:GENERIC-FUNCTION-NAME generic-function)Returns the name of the generic function, or NIL if the generic
function has no name.  This is the defaulted value of the :NAME
initialization argument that was associated with the generic function metaobject during
initialization or reinitialization.
 (See also (SETF CLOS:GENERIC-FUNCTION-NAME).)
CLOS:GENERIC-FUNCTION-METHODS(CLOS:GENERIC-FUNCTION-METHODS generic-function)Returns the set of methods currently connected to the generic
function.  This is a set of method metaobjects.  This value is maintained by the
generic functions ADD-METHOD and REMOVE-METHOD.
CLOS:GENERIC-FUNCTION-LAMBDA-LIST(CLOS:GENERIC-FUNCTION-LAMBDA-LIST generic-function)Returns the lambda list of the generic function.  This is the
defaulted value of the :LAMBDA-LIST initialization argument that was
associated with the generic function metaobject during initialization or reinitialization.
An ERROR is SIGNALed if the lambda list has yet to be supplied.
CLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDER(CLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDER generic-function)Returns the argument precedence order of the generic function.
This value is a list of symbols, a permutation of the required
parameters in the lambda list of the generic function.  This is the
defaulted value of the :ARGUMENT-PRECEDENCE-ORDER initialization
argument that was associated with the generic function metaobject during initialization or
reinitialization.
An ERROR is SIGNALed if the lambda list has not yet been
  supplied.
CLOS:GENERIC-FUNCTION-DECLARATIONS(CLOS:GENERIC-FUNCTION-DECLARATIONS generic-function)Returns a possibly empty list of the “declarations”
of the generic function.  The elements of this list are
declaration specifiers.  This list is the defaulted value of the
:DECLARATIONS initialization argument that was associated with the
generic function metaobject during initialization or reinitialization.
CLOS:GENERIC-FUNCTION-METHOD-CLASS(CLOS:GENERIC-FUNCTION-METHOD-CLASS generic-function)Returns the default method class of the generic function.  This
class must be a subclass of the class METHOD.  This is the defaulted
value of the :METHOD-CLASS initialization argument that was
associated with the generic function metaobject during initialization or reinitialization.
CLOS:GENERIC-FUNCTION-METHOD-COMBINATION(CLOS:GENERIC-FUNCTION-METHOD-COMBINATION generic-function)Returns the method combination of the generic function.  This is a
method combination metaobject.  This is the defaulted value of the :METHOD-COMBINATION
initialization argument that was associated with the generic function metaobject during
initialization or reinitialization.
The specified methods for the generic function metaobject reader generic functions
(CLOS:GENERIC-FUNCTION-NAME
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-LAMBDA-LIST
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDER
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-DECLARATIONS
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-METHOD-CLASS
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-METHOD-COMBINATION
   (generic-function STANDARD-GENERIC-FUNCTION))(CLOS:GENERIC-FUNCTION-METHODS
   (generic-function STANDARD-GENERIC-FUNCTION))No behavior is specified for this method beyond that which is specified for the generic function.
The value returned by this method is maintained by
   ADD-METHOD(STANDARD-GENERIC-FUNCTION
    STANDARD-METHOD)REMOVE-METHOD(STANDARD-GENERIC-FUNCTION
    STANDARD-METHOD)
DEFGENERICThe evaluation or execution of a DEFGENERIC form results in a
call to the ENSURE-GENERIC-FUNCTION function. The arguments received by ENSURE-GENERIC-FUNCTION
are derived from the DEFGENERIC form in a defined way.  As with
DEFCLASS and DEFMETHOD, the exact macro-expansion of the
DEFGENERIC form is not defined, only the relationship between the
arguments to the macro and the arguments received by ENSURE-GENERIC-FUNCTION.
function-name
argument to DEFGENERIC becomes the first argument to ENSURE-GENERIC-FUNCTION.
This is the only positional argument accepted by ENSURE-GENERIC-FUNCTION; all other
arguments are keyword arguments.lambda-list argument
to DEFGENERIC becomes the value of the :LAMBDA-LIST keyword
argument to ENSURE-GENERIC-FUNCTION.For each of the options
:ARGUMENT-PRECEDENCE-ORDER, :DOCUMENTATION, :GENERIC-FUNCTION-CLASS and
:METHOD-CLASS, the value of the option becomes the value of the
keyword argument with the same name.  If the option does not appear in
the macro form, the keyword argument does not appear in the resulting
call to ENSURE-GENERIC-FUNCTION.
If the option does not appear in the macro form, the
  keyword argument appears in the resulting call to ENSURE-GENERIC-FUNCTION, with a
  default value: the lambda list for
  :ARGUMENT-PRECEDENCE-ORDER, NIL for :DOCUMENTATION, the class
  STANDARD-GENERIC-FUNCTION for :GENERIC-FUNCTION-CLASS, the class STANDARD-METHOD
  for :METHOD-CLASS. This is needed to make the generic function reflect
  the DEFGENERIC form.
For the option :DECLARE, the list
of “declarations” becomes the value of the :DECLARATIONS
keyword argument.  If the :DECLARE option does not
appear in the macro form, the :DECLARATIONS keyword argument does not
appear in the call to ENSURE-GENERIC-FUNCTION.
If the :DECLARE option does not appear in
  the macro form, the :DECLARATIONS keyword argument appears in the
  resulting call to ENSURE-GENERIC-FUNCTION, with a default value of NIL.  This is
  needed to make the generic function reflect the DEFGENERIC form.
 
The handling of the :METHOD-COMBINATION option is
not specified.
If the :METHOD-COMBINATION option does not
  appear in the macro form, the :METHOD-COMBINATION keyword argument
  still appears in the resulting call to ENSURE-GENERIC-FUNCTION, but in a position
  where it can be overridden by user-defined initargs and default initargs.
 
The :DECLARE keyword is
  recognized as equivalent to the :DECLARATIONS keyword, for
  compatibility with ENSURE-GENERIC-FUNCTION in [ANSI CL standard].  If both :DECLARE and
  :DECLARATIONS keyword arguments are specified, an ERROR is SIGNALed.
Any other generic function options become the value of
   keyword arguments with the same name. The value of the keyword
   argument is the tail of the generic function option. An ERROR is SIGNALed if
   any generic function option appears more than once in the
   DEFGENERIC form.
The default initargs of the
   generic-function-class are added at the
   end of the list of arguments to pass to ENSURE-GENERIC-FUNCTION. This is needed to
   make the generic function reflect the DEFGENERIC form.
User-defined options. Any other options become the value of keyword arguments with
    the same name.  The value of the keyword argument is the tail of the
    option.  An ERROR is SIGNALed if any option appears more than once in the
    DEFGENERIC form.
The result of the call to ENSURE-GENERIC-FUNCTION is returned as the result of
evaluating or executing the DEFGENERIC form.
Associated with each generic function is its discriminating function. Each time the generic function is called, the discriminating function is called to provide the behavior of the generic function. The discriminating function receives the full set of arguments received by the generic function. It must lookup and execute the appropriate methods, and return the appropriate values.
The discriminating function is computed by the highest layer of
the generic function invocation protocol, CLOS:COMPUTE-DISCRIMINATING-FUNCTION.
Whenever a generic function metaobject is initialized, reinitialized, or a method is added or
removed, the discriminating function is recomputed.
The new discriminating function is then stored with
CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION.
Discriminating functions call CLOS:COMPUTE-APPLICABLE-METHODS
and CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES to compute the methods
applicable to the generic functions arguments.  Applicable methods are
combined by CLOS:COMPUTE-EFFECTIVE-METHOD to produce
an effective method.
Provisions are made to allow memoization of the method applicability and
effective methods computations.  (See the description of
CLOS:COMPUTE-DISCRIMINATING-FUNCTION for details.)
The body of method definitions are processed by
CLOS:MAKE-METHOD-LAMBDA.  The result of this generic function is a lambda expression
which is processed by either COMPILE or COMPILE-FILE to produce
a method function.  The arguments received by the
method function are controlled by the CALL-METHOD forms appearing in
the effective methods.  By default, method functions accept two
arguments: a list of arguments to the generic function, and a list of
next methods.  The list of next methods corresponds to the next methods
argument to CALL-METHOD.  If CALL-METHOD appears with additional
arguments, these will be passed to the method functions as well; in
these cases, CLOS:MAKE-METHOD-LAMBDA must have created the method lambdas
to expect additional arguments.
See The generic function CLOS:MAKE-METHOD-LAMBDA is not implemented.
A generic function metaobject can be created by calling MAKE-INSTANCE.  The
initialization arguments establish the definition of the generic
function.  A generic function metaobject can be redefined by calling REINITIALIZE-INSTANCE.
Some classes of generic function metaobject do not support redefinition; in these cases,
REINITIALIZE-INSTANCE SIGNALs an ERROR.
Initialization of a generic function metaobject must be done by calling MAKE-INSTANCE
and allowing it to call INITIALIZE-INSTANCE.  Reinitialization of a
generic-function metaobject must be done by calling
REINITIALIZE-INSTANCE.  Portable programs must not
INITIALIZE-INSTANCE directly to
    initialize a generic function metaobject;SHARED-INITIALIZE directly to
    initialize or reinitialize a generic function metaobject;CHANGE-CLASS to change the class of any
    generic function metaobject or to turn a non-generic-function object into a
    generic function metaobject.Since metaobject classes may not be redefined,
 no behavior is specified for the result of calls to
 UPDATE-INSTANCE-FOR-REDEFINED-CLASS on generic function metaobjects.
 Since the class of a generic function metaobject may not be changed,
 no behavior is specified for the results of calls to
 UPDATE-INSTANCE-FOR-DIFFERENT-CLASS on generic function metaobjects.
During initialization or reinitialization, each initialization argument is checked for errors and then associated with the generic function metaobject. The value can then be accessed by calling the appropriate accessor as shown in Table 29.4, “Initialization arguments and accessors for generic function metaobjects”.
This section begins with a description of the error checking and processing of each initialization argument. This is followed by a table showing the generic functions that can be used to access the stored initialization arguments. The section ends with a set of restrictions on portable methods affecting generic function metaobject initialization and reinitialization.
In these descriptions, the phrase “this argument defaults to
value” means that when that initialization argument is not
supplied, initialization or reinitialization is performed as if
value had been supplied.  For some initialization arguments this
could be done by the use of default initialization arguments, but
whether it is done this way is not specified.  Implementations are free
to define default initialization arguments for specified generic function metaobject classes.
Portable programs are free to define default initialization arguments
for portable subclasses of the class GENERIC-FUNCTION.
Unless there is a specific note to the contrary, then during reinitialization, if an initialization argument is not supplied, the previously stored value is left unchanged.
The :ARGUMENT-PRECEDENCE-ORDER argument is a list
   of symbols.
An ERROR is SIGNALed if this argument appears but the :LAMBDA-LIST
   argument does not appear.  An ERROR is SIGNALed if this value is not a proper list
   or if this value is not a permutation of the symbols from the
   required arguments part of the :LAMBDA-LIST initialization
   argument.
When the generic function is being initialized or
   reinitialized, and this argument is not supplied, but the
   :LAMBDA-LIST argument is supplied, this value defaults to the
   symbols from the required arguments part of the :LAMBDA-LIST
   argument, in the order they appear in that argument.  If neither
   argument is supplied, neither are initialized (see the description of
   :LAMBDA-LIST.)
The :DECLARATIONS argument is a list of declaration specifiers.
  
An ERROR is SIGNALed if this value is not a proper list or
   if each of its elements is not a legal declaration specifier.
When the generic function is being initialized, and this argument is not supplied, it defaults to the empty list.
:DOCUMENTATION argument is
 a STRING or NIL. An ERROR is SIGNALed if it is not. This argument default
 to NIL during initialization.The :LAMBDA-LIST argument is a lambda list.
An ERROR is SIGNALed if this value is not a proper generic function
   lambda list.
When the generic function is being initialized, and this argument is not supplied, the generic function's lambda list is not initialized. The lambda list will be initialized later, either when the first method is added to the generic function, or a later reinitialization of the generic function.
:METHOD-COMBINATION argument is a method combination metaobject.
 The :METHOD-CLASS argument is a class metaobject.
  
An ERROR is SIGNALed if this value is not a subclass of the
   class METHOD.
When the generic function is being initialized, and this
   argument is not supplied, it defaults to the class STANDARD-METHOD.
 
  The :NAME argument is an object.
If the generic function is being initialized, this argument
   defaults to NIL.
After the processing and defaulting of initialization arguments described above, the value of each initialization argument is associated with the generic function metaobject. These values can then be accessed by calling the corresponding generic function. The correspondences are as follows:
Table 29.4. Initialization arguments and accessors for generic function metaobjects
| Initialization Argument | Generic Function | 
|---|---|
| :ARGUMENT-PRECEDENCE-ORDER | CLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDER | 
| :DECLARATIONS | CLOS:GENERIC-FUNCTION-DECLARATIONS | 
| :DOCUMENTATION | DOCUMENTATION | 
| :LAMBDA-LIST | CLOS:GENERIC-FUNCTION-LAMBDA-LIST | 
| :METHOD-COMBINATION | CLOS:GENERIC-FUNCTION-METHOD-COMBINATION | 
| :METHOD-CLASS | CLOS:GENERIC-FUNCTION-METHOD-CLASS | 
| :NAME | CLOS:GENERIC-FUNCTION-NAME | 
It is not specified which methods provide the initialization and reinitialization behavior described above. Instead, the information needed to allow portable programs to specialize this behavior is presented as a set of restrictions on the methods a portable program can define. The model is that portable initialization methods have access to the generic function metaobject when either all or none of the specified initialization has taken effect.
These restrictions govern the methods that a portable program can
define on the generic functions INITIALIZE-INSTANCE,
REINITIALIZE-INSTANCE, and SHARED-INITIALIZE.  These restrictions
apply only to methods on these generic functions for which the first
specializer is a subclass of the class GENERIC-FUNCTION.  Other
portable methods on these generic functions are not affected by these
restrictions.
SHARED-INITIALIZE.For INITIALIZE-INSTANCE and REINITIALIZE-INSTANCE:
   
The results are undefined if any of these restrictions are violated.
(SETF CLOS:GENERIC-FUNCTION-NAME)ENSURE-GENERIC-FUNCTIONCLOS:ENSURE-GENERIC-FUNCTION-USING-CLASSADD-METHODREMOVE-METHODCLOS:COMPUTE-APPLICABLE-METHODSCLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSESCLOS:COMPUTE-EFFECTIVE-METHODCLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTIONCLOS:MAKE-METHOD-LAMBDACLOS:COMPUTE-DISCRIMINATING-FUNCTION(SETF CLOS:GENERIC-FUNCTION-NAME)((SETF CLOS:GENERIC-FUNCTION-NAME) new-name generic-function)
generic-functionnew-nameNIL.
new-name argument.This function changes the name of generic-function to new-name.
   This value is usually a function name or NIL, if the generic function
   is to have no name.
This function works by calling REINITIALIZE-INSTANCE with
   generic-function as its first argument, the symbol :NAME as its second argument
   and new-name as its third argument.
ENSURE-GENERIC-FUNCTION(ENSURE-GENERIC-FUNCTION function-name &KEY
     &ALLOW-OTHER-KEYS)function-nameCLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS, others are
      processed during initialization of the generic function metaobject
      (as described in Section 29.5.3.3, “Initialization of generic function metaobjects”).
This function is called to define a globally named generic function or to specify or modify options and declarations that pertain to a globally named generic function as a whole. It can be called by the user or the implementation.
It is the functional equivalent of DEFGENERIC, and is
   called by the expansion of the DEFGENERIC and DEFMETHOD macros.
  
The behavior of this function is actually
   implemented by the generic function CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS.  When ENSURE-GENERIC-FUNCTION
   is called, it immediately calls CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS and returns that
   result as its own.
The first argument to CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS is computed as follows:
   
function-name names a non-generic
      function, a macro, or a special form, an ERROR is SIGNALed.
    function-name names a generic function, that
      generic function metaobject is used.NIL is used.
   The second argument is function-name.  The remaining arguments
   are the complete set of keyword arguments received by ENSURE-GENERIC-FUNCTION.
CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS(CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS generic-function function-name &KEY
    :ARGUMENT-PRECEDENCE-ORDER :DECLARATIONS :DOCUMENTATION
    :GENERIC-FUNCTION-CLASS :LAMBDA-LIST :METHOD-CLASS :METHOD-COMBINATION
    :NAME &ALLOW-OTHER-KEYS)generic-functionNIL.function-name:GENERIC-FUNCTION-CLASSSTANDARD-GENERIC-FUNCTION.  If a class name is supplied, it is
      interpreted as the class with that name.  If a class name is
      supplied, but there is no such class, an ERROR is SIGNALed.
   see Section 29.5.3.3, “Initialization of generic function metaobjects”.
The :DECLARE keyword is recognized as
       equivalent to the :DECLARATIONS keyword, for compatibility
       with ENSURE-GENERIC-FUNCTION in [ANSI CL standard].
The generic function CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS is called to
   define or modify the definition of a globally named generic function.
   It is called by the ENSURE-GENERIC-FUNCTION function.  It can also be called
   directly.
The first step performed by this generic function is to compute the set of initialization arguments which will be used to create or reinitialize the globally named generic function. These initialization arguments are computed from the full set of keyword arguments received by this generic function as follows:
:GENERIC-FUNCTION-CLASS
      argument is not included in the initialization arguments.
    :METHOD-CLASS argument was received by
      this generic function, it is converted into a class metaobject.
      This is done by looking up the class name with FIND-CLASS.  If
      there is no such class, an ERROR is SIGNALed.If the generic-function argument is NIL, an instance of the class
   specified by the :GENERIC-FUNCTION-CLASS argument is created by
   calling MAKE-INSTANCE with the previously computed initialization
   arguments.  The function name function-name is set to name the generic
   function.  The newly created generic function metaobject is returned.
  
If the class of the generic-function argument is not the same
   as the class specified by the :GENERIC-FUNCTION-CLASS argument, an ERROR is SIGNALed.
The description of ENSURE-GENERIC-FUNCTION in [ANSI CL standard]
   specifies that in this case, CHANGE-CLASS is called if the class of the
   generic-function argument and the class specified by the :GENERIC-FUNCTION-CLASS argument are
   compatible. Given the description of ENSURE-GENERIC-FUNCTION, this also applies to the
   CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS function. CLISP's implementation calls CHANGE-CLASS
   always, and leaves it to the CHANGE-CLASS function to signal an error if
   needed.
Otherwise the generic function generic-function is redefined by calling
   the REINITIALIZE-INSTANCE generic function with generic-function and the
   initialization arguments.  The generic-function argument is then returned.
Methods
(CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS
   (generic-function GENERIC-FUNCTION) function-name &KEY
   :GENERIC-FUNCTION-CLASS &ALLOW-OTHER-KEYS)This method implements the behavior of the generic
   function in the case where function-name names an existing generic
   function.
This method can be overridden.
(CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS
   (generic-function NULL) function-name &KEY :GENERIC-FUNCTION-CLASS
   &ALLOW-OTHER-KEYS)function-name names no function, generic
   function, macro or special form.
ADD-METHOD(ADD-METHOD generic-function method)
 generic-functionmethodgeneric-function argument.This generic function associates an unattached method with a generic function.
An ERROR is SIGNALed if the lambda list of the method is not
   congruent with the lambda list of the generic function.
An ERROR is SIGNALed if the method is already associated with some
   other generic function.
If the given method agrees with an existing method of the
   generic function on parameter specializers and qualifiers, the
   existing method is removed by calling REMOVE-METHOD before the
   new method is added.  See the [ANSI CL standard] section
   7.6.3 “Agreement on
     Parameter Specializers and Qualifiers”
   for a definition of agreement in this context.
Associating the method with the generic function then proceeds in four steps:
method to the set returned by
      CLOS:GENERIC-FUNCTION-METHODS and arrange for CLOS:METHOD-GENERIC-FUNCTION to return generic-function;
    CLOS:ADD-DIRECT-METHOD for each of the method's
    specializers;CLOS:COMPUTE-DISCRIMINATING-FUNCTION and
      install its result with CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION; and
    The generic function ADD-METHOD can be called by the user
   or the implementation.
Methods
(ADD-METHOD
   (generic-function STANDARD-GENERIC-FUNCTION)
   (method STANDARD-METHOD))(ADD-METHOD
   (generic-function STANDARD-GENERIC-FUNCTION)
   (method METHOD))REMOVE-METHOD(REMOVE-METHOD generic-function method)
generic-functionmethodgeneric-function argument.This generic function breaks the association between a generic function and one of its methods.
No ERROR is SIGNALed if the method is not among the methods of the
   generic function.
Breaking the association between the method and the generic function proceeds in four steps:
method from the set returned by
      CLOS:GENERIC-FUNCTION-METHODS and arrange for CLOS:METHOD-GENERIC-FUNCTION to return NIL;
    CLOS:REMOVE-DIRECT-METHOD for each of the
      method's specializers;CLOS:COMPUTE-DISCRIMINATING-FUNCTION and
      install its result with CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION;
      andThe generic function REMOVE-METHOD can be called by the
   user or the implementation.
Methods
(REMOVE-METHOD
   (generic-function STANDARD-GENERIC-FUNCTION)
   (method STANDARD-METHOD))(REMOVE-METHOD
   (generic-function STANDARD-GENERIC-FUNCTION)
   (method METHOD))CLOS:COMPUTE-APPLICABLE-METHODS(CLOS:COMPUTE-APPLICABLE-METHODS
     generic-function arguments)generic-functionargumentsThis generic function determines the method applicability of a generic function given a list of required arguments. The returned list of method metaobjects is sorted by precedence order with the most specific method appearing first. If no methods are applicable to the supplied arguments the empty list is returned.
When a generic function is invoked, the discriminating
   function must determine the ordered list of methods applicable to the
   arguments.  Depending on the generic function and the arguments, this
   is done in one of three ways: using a memoized value; calling
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES; or calling
   CLOS:COMPUTE-APPLICABLE-METHODS.
   (Refer to the description of CLOS:COMPUTE-DISCRIMINATING-FUNCTION for
   the details of this process.)
The arguments argument is permitted to contain more elements
   than the generic function accepts required arguments; in these cases
   the extra arguments will be ignored.  An ERROR is SIGNALed if arguments
   contains fewer elements than the generic function accepts required
   arguments.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
Methods
(CLOS:COMPUTE-APPLICABLE-METHODS
   (generic-function STANDARD-GENERIC-FUNCTION) arguments)This method SIGNALs an ERROR if any method of the generic
   function has a specializer which is neither a class metaobject nor an
   EQL specializer metaobject.
Otherwise, this method computes the sorted list of applicable methods according to the rules described in the [ANSI CL standard] section 7.6.6 “Method Selection and Combination”
This method can be overridden.  Because of the consistency
   requirements between this generic function and
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES, doing so may require also overriding
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES
    (STANDARD-GENERIC-FUNCTION T)
Remarks. 
See also the [ANSI CL standard] function COMPUTE-APPLICABLE-METHODS.
CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES(CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES
    generic-function classes)generic-functionclassesBOOLEANThis generic function is called to attempt to determine the method applicability of a generic function given only the classes of the required arguments.
If it is possible to completely determine the ordered list of applicable methods based only on the supplied classes, this generic function returns that list as its primary value and true as its second value. The returned list of method metaobjects is sorted by precedence order, the most specific method coming first. If no methods are applicable to arguments with the specified classes, the empty list and true are returned.
If it is not possible to completely determine the ordered list of applicable methods based only on the supplied classes, this generic function returns an unspecified primary value and false as its second value.
When a generic function is invoked, the discriminating
   function must determine the ordered list of methods applicable to the
   arguments.  Depending on the generic function and the arguments, this
   is done in one of three ways: using a memoized value; calling
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES; or calling
   CLOS:COMPUTE-APPLICABLE-METHODS.  (Refer to the description of
   CLOS:COMPUTE-DISCRIMINATING-FUNCTION for the details of this process.)
  
The following consistency relationship between
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES and CLOS:COMPUTE-APPLICABLE-METHODS must
   be maintained: for any given generic function and set of arguments,
   if CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES returns a second value of true,
   the primary value must be equal to the value that would be returned by
   a corresponding call to CLOS:COMPUTE-APPLICABLE-METHODS.  The results
   are undefined if a portable method on either of these generic
   functions causes this consistency to be violated.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
Methods
(CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES
   (generic-function STANDARD-GENERIC-FUNCTION) classes)If any method of the generic function has a
   specializer which is neither a class metaobject nor an EQL
   specializer metaobject, this method SIGNALs an ERROR.
In cases where the generic function has no methods with
   EQL specializers, or has no methods with EQL specializers
   that could be applicable to arguments of the supplied classes, this
   method returns the ordered list of applicable methods as its first
   value and true as its second value.
Otherwise this method returns an unspecified primary value and false as its second value.
This method can be overridden. Because of the consistency
   requirements between this generic function and
   CLOS:COMPUTE-APPLICABLE-METHODS, doing so may require also overriding
   CLOS:COMPUTE-APPLICABLE-METHODS
    (STANDARD-GENERIC-FUNCTION T) 
This generic function exists to allow user extensions which alter method lookup rules, but which base the new rules only on the classes of the required arguments, to take advantage of the class-based method lookup memoization found in many implementations. (There is of course no requirement for an implementation to provide this optimization.)
Such an extension can be implemented by two methods, one on this
generic function and one on CLOS:COMPUTE-APPLICABLE-METHODS.  Whenever
the user extension is in effect, the first method will return a second
value of true.  This should allow the implementation to absorb these
cases into its own memoization scheme.
To get appropriate performance, other kinds of extensions may
require methods on CLOS:COMPUTE-DISCRIMINATING-FUNCTION which implement
their own memoization scheme.
CLOS:COMPUTE-EFFECTIVE-METHOD(CLOS:COMPUTE-EFFECTIVE-METHOD generic-function method-combination
    methods)generic-functionmethod-combinationmethodsThis generic function is called to determine the effective method from a sorted list of method metaobjects.
An effective method is a form that describes how the
    applicable methods are to be combined.  Inside of effective method
    forms are CALL-METHOD forms which indicate that a particular
    method is to be called.  The arguments to the CALL-METHOD form
    indicate exactly how the method function of the method should be
    called.  (See CLOS:MAKE-METHOD-LAMBDA for more details about method
    functions.)
An effective method option has the same interpretation and
    syntax as either the :ARGUMENTS or the :GENERIC-FUNCTION option in the long form
    of DEFINE-METHOD-COMBINATION.
More information about the form and interpretation of
    effective methods and effective method options can be found under
    the description of the DEFINE-METHOD-COMBINATION macro in the
    CLOS specification.
This generic function can be called by the user or the implementation. It is called by discriminating functions whenever a sorted list of applicable methods must be converted to an effective method.
Methods
(CLOS:COMPUTE-EFFECTIVE-METHOD
   (generic-function STANDARD-GENERIC-FUNCTION) method-combination methods)This method computes the effective method according
   to the rules of the method combination type implemented by method-combination.
This method can be overridden.
The second return value may contain only one
  :ARGUMENTS option and only one :GENERIC-FUNCTION option. When overriding a
  CLOS:COMPUTE-EFFECTIVE-METHOD method, before adding an :ARGUMENTS or
  :GENERIC-FUNCTION option, you therefore need to check whether it this option is
  already present.
CLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTION(CLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTION
    generic-function methods arguments)generic-functionmethodsargumentsThis function is called to determine the effective method
   from a sorted list of method metaobjects, and convert it to a function.
   The arguments are a set of arguments to which the methods are applicable,
   and are used solely for error message purposes.
This function calls CLOS:COMPUTE-EFFECTIVE-METHOD using the generic-function's
   method combination, wraps local macro definitions for CALL-METHOD and
   MAKE-METHOD around it, handles the :ARGUMENTS and :GENERIC-FUNCTION options,
   and compiles the resulting form to a function.
CLOS:MAKE-METHOD-LAMBDA(CLOS:MAKE-METHOD-LAMBDA generic-function
    method lambda-expression environment)
 generic-functionmethodlambda-expressionenvironment&ENVIRONMENT argument to
     macro expansion functions.This generic function is called to produce a lambda expression which can itself be used to produce a method function for a method and generic function with the specified classes. The generic function and method the method function will be used with are not required to be the given ones. Moreover, the method metaobject may be uninitialized.
Either the function COMPILE, the special form FUNCTION or
   the function COERCE must be used to convert the lambda expression a
   method function.  The method function itself can be applied to
   arguments with APPLY or FUNCALL.
When a method is actually called by an effective method, its
   first argument will be a list of the arguments to the generic
   function.  Its remaining arguments will be all but the first argument
   passed to CALL-METHOD.  By default, all method functions must
   accept two arguments: the list of arguments to the generic function
   and the list of next methods.
For a given generic function and method class, the applicable
   methods on CLOS:MAKE-METHOD-LAMBDA and CLOS:COMPUTE-EFFECTIVE-METHOD must
   be consistent in the following way: each use of CALL-METHOD
   returned by the method on CLOS:COMPUTE-EFFECTIVE-METHOD must have the
   same number of arguments, and the method lambda returned by the
   method on CLOS:MAKE-METHOD-LAMBDA must accept a corresponding number of
   arguments.
Note that the system-supplied implementation of
   CALL-NEXT-METHOD is not required to handle extra arguments to the
   method function.  Users who define additional arguments to the method
   function must either redefine or forego CALL-NEXT-METHOD.  (See the
   example below.)
When the method metaobject is created with MAKE-INSTANCE, the method
   function must be the value of the :FUNCTION initialization
   argument.  The additional initialization arguments, returned as the
   second value of this generic function, must also be passed in this
   call to MAKE-INSTANCE.
Methods
(CLOS:MAKE-METHOD-LAMBDA
   (generic-function STANDARD-GENERIC-FUNCTION)
   (method STANDARD-METHOD)
   lambda-expression environment)This method returns a method lambda which accepts two arguments, the list of arguments to the generic function, and the list of next methods. What initialization arguments may be returned in the second value are unspecified.
This method can be overridden.
This example shows how to define a kind of method which, from
within the body of the method, has access to the actual method metaobject for the
method.  This simplified code overrides whatever method combination is
specified for the generic function, implementing a simple method
combination supporting only primary methods, CALL-NEXT-METHOD and
NEXT-METHOD-P.  (In addition, its a simplified version of
CALL-NEXT-METHOD which does no error checking.)
Notice that the extra lexical function bindings get wrapped around
the body before CALL-NEXT-METHOD is called.  In this way, the user's
definition of CALL-NEXT-METHOD and NEXT-METHOD-P are sure to
override the system's definitions.
(defclass my-generic-function (standard-generic-function)
  ()
  (:default-initargs :method-class (find-class 'my-method)))
(defclass my-method (standard-method) ())
(defmethod make-method-lambda ((gf my-generic-function)
                               (method my-method)
                               lambda-expression
                               environment)
  (declare (ignore environment))
  `(lambda (args next-methods this-method)
     (,(call-next-method gf method
         `(lambda ,(cadr lambda-expression)
            (flet ((this-method () this-method)
                   (call-next-method (&REST cnm-args)
                     (funcall (method-function (car next-methods))
                              (or cnm-args args)
                              (cdr next-methods)
                              (car next-methods)))
                   (next-method-p ()
                     (not (null next-methods))))
              ,@(cddr lambda-expression)))
          environment)
       args next-methods)))
(defmethod compute-effective-method ((gf my-generic-function)
                                     method-combination
                                     methods)
  `(call-method ,(car methods) ,(cdr methods) ,(car methods)))
The generic function CLOS:MAKE-METHOD-LAMBDA is not implemented. Its specification is misdesigned: it mixes compile time and
   execution time behaviour. The essential problem is: where could the
   generic-function argument come from?
   
DEFMETHOD form occurs in a source file, is
      CLOS:MAKE-METHOD-LAMBDA then called at compile time or at load time?
      If it was called at compile time, there's no possible value for
      the first argument, since the class of the generic function to
      which the method will belong is not known until load time.  If it
      was called at load time, it would mean that the method's source
      code could only be compiled at load time, not earlier - which
      defeats the purpose of COMPILE-FILEREMOVE-METHOD and then added through ADD-METHOD to a
      different generic function, possibly belonging to a different
      generic function class, would CLOS:MAKE-METHOD-LAMBDA then be called
      again or not? If no, then CLOS:MAKE-METHOD-LAMBDA's first argument is
      useless. If yes, then the source code of every method would have
      to be present at runtime, and its lexical environment as well.
 CALL-METHOD always expect
      exactly two arguments: the method and a list of next methods.
    CLOS:COMPUTE-DISCRIMINATING-FUNCTION(CLOS:COMPUTE-DISCRIMINATING-FUNCTION
    generic-function)generic-functionThis generic function is called to determine the discriminating function for a generic function. When a generic function is called, the installed discriminating function is called with the full set of arguments received by the generic function, and must implement the behavior of calling the generic function: determining the ordered set of applicable methods, determining the effective method, and running the effective method.
To determine the ordered set of applicable methods, the
   discriminating function first calls CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES.
   If CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES returns a second value of false,
   the discriminating function then calls CLOS:COMPUTE-APPLICABLE-METHODS.
  
When CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES returns a second
   value of true, the discriminating function is permitted to memoize
   the primary value as follows.  The discriminating function may
   reuse the list of applicable methods without calling
   CLOS:COMPUTE-APPLICABLE-METHODS-USING-CLASSES again provided that:
   
   Determination of the effective method is done by calling
   CLOS:COMPUTE-EFFECTIVE-METHOD.  When the effective method is run, each
   method's function is called, and receives as arguments:
   
CALL-METHOD form indicating that the method should be called.
   
   (See CLOS:MAKE-METHOD-LAMBDA for more information about how method
   functions are called.)
The generic function CLOS:COMPUTE-DISCRIMINATING-FUNCTION is
   called, and its result installed, by ADD-METHOD, REMOVE-METHOD,
   INITIALIZE-INSTANCE and REINITIALIZE-INSTANCE.
Methods
(CLOS:COMPUTE-DISCRIMINATING-FUNCTION
    (generic-function STANDARD-GENERIC-FUNCTION))No behavior is specified for this method beyond that which is specified for the generic function.
This method can be overridden.
Overriding methods can make use of the function
  CLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTION.  It is more convenient to call
  CLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTION than CLOS:COMPUTE-EFFECTIVE-METHOD
  because the in the latter case one needs a lot of “glue
   code” for implementing the local macros CALL-METHOD and
  MAKE-METHOD, and this glue code is implementation dependent because
  it needs
CLOS:COMPUTE-EFFECTIVE-METHOD.
The reader generic functions which simply return information associated with method metaobjects are presented together here in the format described in Section 29.3.3, “Introspection: Readers for class metaobjects”.
Each of these reader generic functions have the same syntax,
accepting one required argument called method, which must be a
method metaobject; otherwise, an ERROR is SIGNALed.  An ERROR is also SIGNALed
if the method metaobject has not been initialized.
These generic functions can be called by the user or the implementation.
For any of these generic functions which returns a list, such lists will not be mutated by the implementation. The results are undefined if a portable program allows such a list to be mutated.
CLOS:METHOD-SPECIALIZERS(CLOS:METHOD-SPECIALIZERS method)Returns a list of the specializers of method.  This value is a
list of specializer metaobjects.  This is the value of the
:SPECIALIZERS initialization argument that was associated with the
method during initialization.
METHOD-QUALIFIERS(METHOD-QUALIFIERS method)Returns a (possibly empty) list of the qualifiers of method.
This value is a list of non-NIL atoms.  This is the defaulted value of
the :QUALIFIERS initialization argument that was associated with the
method during initialization.
CLOS:METHOD-LAMBDA-LIST(CLOS:METHOD-LAMBDA-LIST method)Returns the (unspecialized) lambda list of method.  This value
is a Common Lisp lambda list.  This is the value of the :LAMBDA-LIST
initialization argument that was associated with the method during
initialization.
CLOS:METHOD-GENERIC-FUNCTION(CLOS:METHOD-GENERIC-FUNCTION method)Returns the generic function that method is currently
connected to, or NIL if it is not currently connected to any generic
function.  This value is either a generic function metaobject or NIL.
When a method is first created it is not connected to any generic
function.  This connection is maintained by the generic functions
ADD-METHOD and REMOVE-METHOD.
CLOS:METHOD-FUNCTION(CLOS:METHOD-FUNCTION method)Returns the method function of method.  This is the
value of the :FUNCTION initialization argument that was associated
with the method during initialization.
The specified methods for the method metaobject readers
(CLOS:METHOD-SPECIALIZERS
   (method STANDARD-METHOD))(METHOD-QUALIFIERS
   (method STANDARD-METHOD))(CLOS:METHOD-LAMBDA-LIST
   (method STANDARD-METHOD))(CLOS:METHOD-FUNCTION
   (method STANDARD-METHOD))(CLOS:METHOD-GENERIC-FUNCTION
   (method STANDARD-METHOD))No behavior is specified for this method beyond that which is specified for the generic function.
The value returned by this method is maintained by
  ADD-METHOD(STANDARD-GENERIC-FUNCTION
   STANDARD-METHOD)REMOVE-METHOD(STANDARD-GENERIC-FUNCTION
   STANDARD-METHOD)
DEFMETHODThe evaluation or execution of a DEFMETHOD form requires first
that the body of the method be converted to a method function.
This process is described
below.
The result of this process is a method function and a set of additional
initialization arguments to be used when creating the new method.
Given these two values, the evaluation or execution of a DEFMETHOD
form proceeds in three steps.
The first step ensures the existence of a generic function with
the specified name.  This is done by calling the function ENSURE-GENERIC-FUNCTION.
The first argument in this call is the generic function name specified
in the DEFMETHOD form.
The second step is the creation of the new method metaobject by calling
MAKE-INSTANCE.  The class of the new method metaobject is determined by calling
CLOS:GENERIC-FUNCTION-METHOD-CLASS on the result of the call to ENSURE-GENERIC-FUNCTION from the
first step.
The initialization arguments received by the call to MAKE-INSTANCE
are as follows:
:QUALIFIERS initialization
argument is a list of the qualifiers which appeared in the DEFMETHOD
form.  No special processing is done on these values.  The order of the
elements of this list is the same as in the DEFMETHOD form.
:LAMBDA-LIST initialization
argument is the unspecialized lambda list from the DEFMETHOD form.
:SPECIALIZERS initialization
argument is a list of the specializers for the method.  For specializers
which are classes, the specializer is the class metaobject itself.  In
the case of EQL specializers, it will be an CLOS:EQL-SPECIALIZER
metaobject obtained by calling CLOS:INTERN-EQL-SPECIALIZER on the result of
evaluating the EQL specializer form in the lexical environment of the
DEFMETHOD form.:FUNCTION initialization
argument is the method function.The value of the :DECLARATIONS initialization
argument is a list of the declaration specifiers from the
DEFMETHOD form.  If there are no declarations in the macro form, this
initialization argument either does not appear, or appears with a value
of the empty list.
No :DECLARATIONS initialization argument is
  provided, because method initialization does not support a :DECLARATIONS
  argument, and because the method function is already completely provided
  through the :FUNCTION initialization argument.
:DOCUMENTATION initialization
argument is the documentation string from the DEFMETHOD form.  If
there is no documentation string in the macro form this initialization
argument either does not appear, or appears with a value of false.
In the third step, ADD-METHOD is called to add the newly created
method to the set of methods associated with the generic function metaobject.
The result of the call to ADD-METHOD is returned as the result
of evaluating or executing the DEFMETHOD form.
An example showing a typical DEFMETHOD form and a sample
expansion is shown in the following example:
An example DEFMETHOD form and one possible correct
  expansion. In the expansion, method-lambda
  is the result of calling CLOS:MAKE-METHOD-LAMBDA as described in
  Section 29.6.3.1.1, “Processing Method Bodies”.
  The initargs appearing after :FUNCTION are assumed to be additional
  initargs returned from the call to CLOS:MAKE-METHOD-LAMBDA.
(defmethod move :before ((p position) (l (eql 0))
                         &OPTIONAL (visiblyp t)
                         &KEY color)
  (set-to-origin p)
  (when visiblyp (show-move p 0 color)))
(let ((#:g001 (ensure-generic-function 'move)))
  (add-method #:g001
    (make-instance (generic-function-method-class #:g001)
                   :qualifiers '(:before)
                   :specializers (list (find-class 'position)
                                       (intern-eql-specializer 0))
                   :lambda-list '(p l &OPTIONAL (visiblyp t)
                                      &KEY color)
                   :function (function method-lambda)
                   'additional-initarg-1 't
                   'additional-initarg-2 '39)))
The processing of the method body for this method is shown below.
Before a method can be created, the list of forms comprising the method body must be converted to a method function. This conversion is a two step process.
The body of methods can also appear in the
:METHOD option of DEFGENERIC forms.  Initial methods are
not considered by any of the protocols specified in this document.
During macro-expansion of the DEFMETHOD macro shown in
  the previous example code
  similar to this would be run to produce the method lambda and
  additional initargs.  In this example, environment is the macroexpansion
  environment of the DEFMETHOD macro form.
(let ((gf (ensure-generic-function 'move)))
  (make-method-lambda
    gf
    (class-prototype (generic-function-method-class gf))
    '(lambda (p l &OPTIONAL (visiblyp t) &KEY color)
       (set-to-origin p)
       (when visiblyp (show-move p 0 color)))
    environment))
The first step occurs during macro-expansion of the macro form. In this step, the method lambda list, declarations and body are converted to a lambda expression called a method lambda. This conversion is based on information associated with the generic function definition in effect at the time the macro form is expanded.
The generic function definition is obtained by calling ENSURE-GENERIC-FUNCTION
with a first argument of the generic function name specified in the
macro form.  The :LAMBDA-LIST keyword argument is not passed in this
call.
Given the generic function, production of the method lambda
proceeds by calling CLOS:MAKE-METHOD-LAMBDA.  The first argument in this
call is the generic function obtained as described above.  The second
argument is the result of calling CLOS:CLASS-PROTOTYPE on the result of
calling CLOS:GENERIC-FUNCTION-METHOD-CLASS on the generic function.  The
third argument is a lambda expression formed from the method lambda list,
declarations and body.  The fourth argument is the macro-expansion
environment of the macro form; this is the value of the
&ENVIRONMENT argument to the DEFMETHOD macro.
The generic function CLOS:MAKE-METHOD-LAMBDA returns two values.  The
first is the method lambda itself.  The second is a list of
initialization arguments and values.  These are included in the
initialization arguments when the method is created.
In the second step, the method lambda is converted to a function
which properly captures the lexical scope of the macro form.  This is
done by having the method lambda appear in the macro-expansion as the
argument of the FUNCTION special form.  During the subsequent
evaluation of the macro-expansion, the result of the FUNCTION special
form is the method function.
See The generic function CLOS:MAKE-METHOD-LAMBDA is not implemented.
An example of creating a generic function and a method metaobject, and then adding the method to the generic function is shown below. This example is comparable to the method definition shown above:
(let* ((gf (make-instance 'standard-generic-function
                          :lambda-list '(p l &OPTIONAL visiblyp &KEY)))
       (method-class (generic-function-method-class gf)))
  (multiple-value-bind (lambda initargs)
       (make-method-lambda
         gf
         (class-prototype method-class)
         '(lambda (p l &OPTIONAL (visiblyp t) &KEY color)
            (set-to-origin p)
            (when visiblyp (show-move p 0 color)))
         nil)
    (add-method gf
                (apply #'make-instance method-class
                       :function (compile nil lambda)
                       :specializers (list (find-class 'position)
                                           (intern-eql-specializer 0))
                       :qualifiers ()
                       :lambda-list '(p l &OPTIONAL (visiblyp t)
                                          &KEY color)
                       initargs))))
Methods created through DEFMETHOD have a faster calling
  convention than methods created through a portable MAKE-INSTANCE
  invocation.
A method metaobject can be created by calling MAKE-INSTANCE.
The initialization arguments establish the definition of the method.
A method metaobject cannot be redefined;
calling REINITIALIZE-INSTANCE SIGNALs an ERROR.
Initialization of a method metaobject must be done by calling MAKE-INSTANCE
and allowing it to call INITIALIZE-INSTANCE.  Portable programs must
not
INITIALIZE-INSTANCE directly to
    initialize a method metaobject;SHARED-INITIALIZE directly to
    initialize a method metaobject;CHANGE-CLASS to change the class of any
    method metaobject or to turn a non-method object into a method metaobject.
Since metaobject classes may not be redefined,
 no behavior is specified for the result of calls to
 UPDATE-INSTANCE-FOR-REDEFINED-CLASS on method metaobjects.
 Since the class of a method metaobject cannot be changed,
 no behavior is specified for the result of calls to
 UPDATE-INSTANCE-FOR-DIFFERENT-CLASS on method metaobjects.
During initialization, each initialization argument is checked for errors and then associated with the method metaobject. The value can then be accessed by calling the appropriate accessor as shown in Table 29.5, “Initialization arguments and accessors for method metaobjects”.
This section begins with a description of the error checking and processing of each initialization argument. This is followed by a table showing the generic functions that can be used to access the stored initialization arguments. The section ends with a set of restrictions on portable methods affecting method metaobject initialization.
In these descriptions, the phrase “this argument defaults to
value” means that when that initialization argument is not
supplied, initialization is performed as if value had been supplied.
For some initialization arguments this could be done by the use of
default initialization arguments, but whether it is done this way is not
specified.  Implementations are free to define default initialization
arguments for specified method metaobject classes.  Portable programs
are free to define default initialization arguments for portable
subclasses of the class METHOD.
:QUALIFIERS argument is a list of method
   qualifiers.  An ERROR is SIGNALed if this value is not a proper list, or if
   any element of the list is not a non-null atom. This argument
   defaults to the empty list.:LAMBDA-LIST argument is the unspecialized
   lambda list of the method.  An ERROR is SIGNALed if this value is not a
   proper lambda list. If this value is not supplied, an ERROR is SIGNALed.
 :SPECIALIZERS argument is a list of the
   specializer metaobjects for the method.  An ERROR is SIGNALed if this value
   is not a proper list, or if the length of the list differs from the
   number of required arguments in the :LAMBDA-LIST argument, or if
   any element of the list is not a specializer metaobject.  If this
   value is not supplied, an ERROR is SIGNALed.:FUNCTION argument is a method function.  It
   must be compatible with the methods on CLOS:COMPUTE-EFFECTIVE-METHOD
   defined for this class of method and generic function with which it
   will be used.  That is, it must accept the same number of arguments
   as all uses of CALL-METHOD that will call it supply.  (See
   CLOS:COMPUTE-EFFECTIVE-METHOD and CLOS:MAKE-METHOD-LAMBDA for more information.)
   An ERROR is SIGNALed if this argument is not supplied.CLOS:STANDARD-ACCESSOR-METHOD, the :SLOT-DEFINITION
   initialization argument must be provided.  Its value is the direct
   slot definition metaobject which defines this accessor method.  An ERROR is SIGNALed if the value
   is not an instance of a subclass of CLOS:DIRECT-SLOT-DEFINITION.:DOCUMENTATION argument is a string or NIL.
   An ERROR is SIGNALed if this value is not a string or NIL.  This argument
   defaults to NIL.After the processing and defaulting of initialization arguments described above, the value of each initialization argument is associated with the method metaobject. These values can then be accessed by calling the corresponding generic function. The correspondences are as follows:
Table 29.5. Initialization arguments and accessors for method metaobjects
| Initialization Argument | Generic Function | 
|---|---|
| :QUALIFIERS | METHOD-QUALIFIERS | 
| :LAMBDA-LIST | CLOS:METHOD-LAMBDA-LIST | 
| :SPECIALIZERS | CLOS:METHOD-SPECIALIZERS | 
| :FUNCTION | CLOS:METHOD-FUNCTION | 
| :SLOT-DEFINITION | CLOS:ACCESSOR-METHOD-SLOT-DEFINITION | 
| :DOCUMENTATION | DOCUMENTATION | 
It is not specified which methods provide the initialization behavior described above. Instead, the information needed to allow portable programs to specialize this behavior is presented in as a set of restrictions on the methods a portable program can define. The model is that portable initialization methods have access to the method metaobject when either all or none of the specified initialization has taken effect.
These restrictions govern the methods that a portable program can
define on the generic functions INITIALIZE-INSTANCE,
REINITIALIZE-INSTANCE, and SHARED-INITIALIZE.  These restrictions
apply only to methods on these generic functions for which the first
specializer is a subclass of the class METHOD.  Other portable
methods on these generic functions are not affected by these
restrictions.
SHARED-INITIALIZE or REINITIALIZE-INSTANCE.For INITIALIZE-INSTANCE:
   
The results are undefined if any of these restrictions are violated.
CLOS:EXTRACT-LAMBDA-LIST(CLOS:EXTRACT-LAMBDA-LIST specialized-lambda-list)
specialized-lambda-listDEFMETHOD.
This function takes a specialized lambda list and returns the lambda list with the specializers removed. This is a non-destructive operation. Whether the result shares any structure with the argument is unspecified.
If the specialized-lambda-list argument does not have legal syntax,
   an ERROR is SIGNALed.  This syntax checking does not check the syntax of the
   actual specializer names, only the syntax of the lambda list and
   where the specializers appear.
(CLOS:EXTRACT-LAMBDA-LIST'((p position))) ⇒(P)(CLOS:EXTRACT-LAMBDA-LIST'((p position) x y)) ⇒(P X Y)(CLOS:EXTRACT-LAMBDA-LIST'(a (b (eql x)) c&RESTi)) ⇒(A B C&OPTIONALI)
CLOS:EXTRACT-SPECIALIZER-NAMES(CLOS:EXTRACT-SPECIALIZER-NAMES
    specialized-lambda-list)specialized-lambda-listDEFMETHOD.
This function takes a specialized lambda list and returns its specializer names. This is a non-destructive operation. Whether the result shares structure with the argument is unspecified.
The list returned by this function will not be mutated by the implementation. The results are undefined if a portable program mutates the list returned by this function.
The result of this function will be a list with a
   number of elements equal to the number of required arguments in
   specialized-lambda-list.  Specializers are defaulted to the symbol T.
  
If the specialized-lambda-list argument does not have legal
   syntax, an ERROR is SIGNALed.  This syntax checking does not check the syntax
   of the actual specializer names, only the syntax of the lambda list
   and where the specializers appear.
(CLOS:EXTRACT-SPECIALIZER-NAMES'((p position))) ⇒(POSITION)(CLOS:EXTRACT-SPECIALIZER-NAMES'((p position) x y)) ⇒(POSITION T T)(CLOS:EXTRACT-SPECIALIZER-NAMES'(a (b (eql x)) c&RESTi)) ⇒(T (EQL X) T)
CLOS:ACCESSOR-METHOD-SLOT-DEFINITION(CLOS:ACCESSOR-METHOD-SLOT-DEFINITION method)This accessor can only be called on accessor methods.  It returns
the direct slot definition metaobject that defined this method.  This is the value of the
:SLOT-DEFINITION initialization argument associated with the method during
initialization.
The specified methods for the accessor method metaobject readers
(CLOS:ACCESSOR-METHOD-SLOT-DEFINITION
   (method CLOS:STANDARD-ACCESSOR-METHOD))CLOS:READER-METHOD-CLASS(CLOS:READER-METHOD-CLASS class direct-slot-definition
    &REST initargs)classdirect-slot-definitioninitargsThis generic function is called to determine the
   class of reader methods created during class initialization and
   reinitialization.  The result must be a subclass of
   CLOS:STANDARD-READER-METHOD.
The initargs argument must be the same as will be passed
   to MAKE-INSTANCE to create the reader method.  The initargs
   must include :SLOT-DEFINITION with slot-definition as its value.
Methods
(CLOS:READER-METHOD-CLASS
   (class STANDARD-CLASS) (direct-slot-definition CLOS:STANDARD-DIRECT-SLOT-DEFINITION)
   &REST initargs)(CLOS:READER-METHOD-CLASS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) (direct-slot-definition CLOS:STANDARD-DIRECT-SLOT-DEFINITION)
   &REST initargs)These methods return the class
   CLOS:STANDARD-READER-METHOD.
These methods can be overridden.
CLOS:WRITER-METHOD-CLASS(CLOS:WRITER-METHOD-CLASS class
    direct-slot &REST initargs)
 classdirect-slotinitargsThis generic function is called to determine the
   class of writer methods created during class initialization and
   reinitialization.  The result must be a subclass of
   CLOS:STANDARD-WRITER-METHOD.
The initargs argument must be the same as will be passed
   to MAKE-INSTANCE to create the reader method.  The initargs
   must include :SLOT-DEFINITION with CLOS:SLOT-DEFINITION as its value.
Methods
(CLOS:WRITER-METHOD-CLASS
    (class STANDARD-CLASS)
    (direct-slot CLOS:STANDARD-DIRECT-SLOT-DEFINITION)
    &REST initargs)(CLOS:WRITER-METHOD-CLASS
    (class CLOS:FUNCALLABLE-STANDARD-CLASS)
    (direct-slot CLOS:STANDARD-DIRECT-SLOT-DEFINITION)
    &REST initargs)These methods returns the class
  CLOS:STANDARD-WRITER-METHOD.
These methods can be overridden.
CLOS:EQL-SPECIALIZER-OBJECT(CLOS:EQL-SPECIALIZER-OBJECT
    eql-specializer)
eql-specializerEQL specializer metaobject.
This function returns the object associated with
   eql-specializer during initialization.
   The value is guaranteed to be EQL to the value originally passed
   to CLOS:INTERN-EQL-SPECIALIZER, but it is not necessarily EQ to that
   value.
This function SIGNALs an ERROR if
   eql-specializer is not an EQL
   specializer.
CLOS:INTERN-EQL-SPECIALIZER(CLOS:INTERN-EQL-SPECIALIZER
    object)objectEQL specializer metaobject for object.
EQL specializer
   metaobject for object, creating one if necessary.  Two calls to
   CLOS:INTERN-EQL-SPECIALIZER with EQL arguments will return the same
   (i.e., EQ) value.Remarks. The result of calling CLOS:EQL-SPECIALIZER-OBJECT on the result of a
call to CLOS:INTERN-EQL-SPECIALIZER is only guaranteed to be EQL to the
original object argument, not necessarily EQ.
CLOS:SPECIALIZER-DIRECT-METHODS(CLOS:SPECIALIZER-DIRECT-METHODS
    specializer)specializerspecializer as a specializer.  The elements of this set are
   method metaobjects.  This value is maintained by the generic
   functions CLOS:ADD-DIRECT-METHOD and CLOS:REMOVE-DIRECT-METHOD.
Methods
(CLOS:SPECIALIZER-DIRECT-METHODS
   (specializer CLASS))No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:SPECIALIZER-DIRECT-METHODS
   (specializer CLOS:EQL-SPECIALIZER))CLOS:SPECIALIZER-DIRECT-GENERIC-FUNCTIONS(CLOS:SPECIALIZER-DIRECT-GENERIC-FUNCTIONS
    specializer)specializerspecializer
   as a specializer.  The elements of this set are generic function metaobjects.  This value
   is maintained by the generic functions CLOS:ADD-DIRECT-METHOD and
   CLOS:REMOVE-DIRECT-METHOD.Methods
(CLOS:SPECIALIZER-DIRECT-GENERIC-FUNCTIONS
   (specializer CLASS))No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:SPECIALIZER-DIRECT-GENERIC-FUNCTIONS
   (specializer CLOS:EQL-SPECIALIZER))CLOS:ADD-DIRECT-METHOD(CLOS:ADD-DIRECT-METHOD
     specializer method)specializermethodThis generic function is called to maintain a set of
   backpointers from a specializer to the set of methods specialized to
   it.  If method is already in the set, it is not added again (no
   ERROR is SIGNALed).
This set can be accessed as a list by calling the generic
   function CLOS:SPECIALIZER-DIRECT-METHODS.  Methods are removed from the
   set by CLOS:REMOVE-DIRECT-METHOD.
The generic function CLOS:ADD-DIRECT-METHOD is called by
   ADD-METHOD whenever a method is added to a generic function.  It is
   called once for each of the specializers of the method.  Note that in
   cases where a specializer appears more than once in the specializers
   of a method, this generic function will be called more than once with
   the same specializer as argument.
The results are undefined if the specializer argument
   is not one of the specializers of the method argument.
Methods
(CLOS:ADD-DIRECT-METHOD
   (specializer CLASS) (method METHOD))This method implements the behavior of the generic function for class specializers.
No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:ADD-DIRECT-METHOD
   (specializer CLOS:EQL-SPECIALIZER)
   (method METHOD))This method implements the behavior of the generic
   function for EQL specializers.
No behavior is specified for this method beyond that which is specified for the generic function.
CLOS:REMOVE-DIRECT-METHOD(CLOS:REMOVE-DIRECT-METHOD specializer
    method)specializermethodThis generic function is called to maintain a set of
   backpointers from a specializer to the set of methods specialized to
   it.  If method is in the set it is removed.  If it is not, no
   ERROR is SIGNALed.
This set can be accessed as a list by calling the generic
   function CLOS:SPECIALIZER-DIRECT-METHODS.  Methods are added to the set
   by CLOS:ADD-DIRECT-METHOD.
The generic function CLOS:REMOVE-DIRECT-METHOD is called by
   REMOVE-METHOD whenever a method is removed from a generic function.
   It is called once for each of the specializers of the method.  Note
   that in cases where a specializer appears more than once in the
   specializers of a method, this generic function will be called more
   than once with the same specializer as argument.
The results are undefined if the specializer argument is
   not one of the specializers of the method argument.
Methods
(CLOS:REMOVE-DIRECT-METHOD
   (specializer CLASS) (method METHOD))This method implements the behavior of the generic function for class specializers.
No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:REMOVE-DIRECT-METHOD
   (specializer CLOS:EQL-SPECIALIZER)
   (method METHOD))This method implements the behavior of the generic
   function for EQL specializers.
No behavior is specified for this method beyond that which is specified for the generic function.
CLOS:FIND-METHOD-COMBINATION(CLOS:FIND-METHOD-COMBINATION generic-function
    method-combination-type-name
    method-combination-options)
generic-functionmethod-combination-type-namemethod-combination-optionsRemarks. Further details of method combination metaobjects are not specified.
CLOS:STANDARD-INSTANCE-ACCESSCLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESSCLOS:SET-FUNCALLABLE-INSTANCE-FUNCTIONCLOS:SLOT-VALUE-USING-CLASS(SETF CLOS:SLOT-VALUE-USING-CLASS)CLOS:SLOT-BOUNDP-USING-CLASSCLOS:SLOT-MAKUNBOUND-USING-CLASSThe instance structure protocol is responsible for implementing
the behavior of the slot access functions like SLOT-VALUE and
(.SETF SLOT-VALUE)
For each CLOS slot access function other than SLOT-EXISTS-P,
there is a corresponding generic function which actually provides the
behavior of the function.  When called, the slot access function finds
the pertinent effective slot definition metaobject, calls the corresponding generic function and
returns its result.  The arguments passed on to the generic function
include one additional value, the class of the object argument,
which always immediately precedes the object argument.
Table 29.6. The correspondence between slot access function and underlying slot access generic function
| Slot Access Function | Corresponding Slot Access Generic Function | 
|---|---|
| SLOT-VALUEobjectslot-name | CLOS:SLOT-VALUE-USING-CLASSclassobjectslot | 
| (new-valueobjectslot-name | (SETF CLOS:SLOT-VALUE-USING-CLASS)new-valueclassobjectslot | 
| SLOT-BOUNDPobjectslot-name | CLOS:SLOT-BOUNDP-USING-CLASSclassobjectslot | 
| SLOT-MAKUNBOUNDobjectslot-name | CLOS:SLOT-MAKUNBOUND-USING-CLASSclassobjectslot | 
At the lowest level, the instance structure protocol provides only limited mechanisms for portable programs to control the implementation of instances and to directly access the storage associated with instances without going through the indirection of slot access. This is done to allow portable programs to perform certain commonly requested slot access optimizations.
In particular, portable programs can control the implementation
of, and obtain direct access to, slots with allocation :INSTANCE and
type T.  These are called directly accessible
slots.
The relevant specified around-method on CLOS:COMPUTE-SLOTS determines
the implementation of instances by deciding how each slot in the
instance will be stored.  For each directly accessible slot, this method
allocates a location and associates it with the
effective slot definition metaobject.  The location can be accessed by calling the CLOS:SLOT-DEFINITION-LOCATION
generic function.  Locations are non-negative integers.  For a given
class, the locations increase consecutively, in the order that the
directly accessible slots appear in the list of effective slots.  (Note
that here, the next paragraph, and the specification of this
around-method are the only places where the value returned by
CLOS:COMPUTE-SLOTS is described as a list rather than a set.)
Given the location of a directly accessible slot, the value of
that slot in an instance can be accessed with the appropriate accessor.
For STANDARD-CLASS, this accessor is the function
CLOS:STANDARD-INSTANCE-ACCESS.  For CLOS:FUNCALLABLE-STANDARD-CLASS, this
accessor is the function CLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESS.
In each case, the arguments to the accessor are the instance and the
slot location, in that order.  See the definition of each accessor for
additional restrictions on the use of these function.
Portable programs are permitted to affect and rely on the
allocation of locations only in the following limited way: By first
defining a portable primary method on CLOS:COMPUTE-SLOTS which orders the
returned value in a predictable way, and then relying on the defined
behavior of the specified around-method to assign locations to all
directly accessible slots.  Portable programs may compile-in calls to
low-level accessors which take advantage of the resulting predictable
allocation of slot locations.
This example shows the use of this mechanism to implement a new
class metaobject class, ordered-class and class
option :SLOT-ORDER.  This option provides control
over the allocation of slot locations.  In this simple example
implementation, the :SLOT-ORDER option is not
inherited by subclasses; it controls only instances of the class
itself.
(defclass ordered-class (standard-class)
  ((slot-order :initform ()
               :initarg :slot-order
               :reader class-slot-order)))
(defmethod compute-slots ((class ordered-class))
  (let ((order (class-slot-order class)))
    (sort (copy-list (call-next-method))
          #'(lambda (a b)
              (< (position (slot-definition-name a) order)
                 (position (slot-definition-name a) order))))))
Following is the source code the user of this extension would write.
Note that because the code above does not implement inheritance of
the :SLOT-ORDER option, the function
distance must not be called on instances of
subclasses of point; it can only be called on
instances of point itself.
(defclass point ()
  ((x :initform 0)
   (y :initform 0))
  (:metaclass ordered-class)
  (:slot-order x y))
(defun distance (point)
  (sqrt (/ (+ (expt (standard-instance-access point 0) 2)
              (expt (standard-instance-access point 1) 2))
           2.0)))
You cannot assume that the slot-location
  values start at 0.  In class point, for
  example, x and y will be at slot locations 1 and 2, not 0 and
  1.
In more realistic uses of this mechanism, the calls to the low-level instance structure accessors would not actually appear textually in the source program, but rather would be generated by a meta-level analysis program run during the process of compiling the source program.
Instances of classes which are themselves instances of
CLOS:FUNCALLABLE-STANDARD-CLASS or one of its subclasses are called
funcallable instances.
Funcallable instances can only be created by
ALLOCATE-INSTANCE
 (CLOS:FUNCALLABLE-STANDARD-CLASS)
Like standard instances, funcallable instances have slots with the
normal behavior.  They differ from standard instances in that they can
be used as functions as well; that is, they can be passed to FUNCALL
and APPLY, and they can be stored as the definition of a function
name.  Associated with each funcallable instance is the function which
it runs when it is called.  This function can be changed with
CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION.
The following simple example shows the use of funcallable
instances to create a simple, DEFSTRUCT-like facility.  (Funcallable
instances are useful when a program needs to construct and maintain a
set of functions and information about those functions.  They make it
possible to maintain both as the same object rather than two separate
objects linked, for example, by hash tables.)
(defclass constructor () ((name :initarg :name :accessor constructor-name) (fields :initarg :fields :accessor constructor-fields)) (:metaclass funcallable-standard-class)) ⇒#>FUNCALLABLE-STANDARD-CLASS CONSTRUCTOR>(defmethod initialize-instance :after ((c constructor)&KEY) (with-slots (name fields) c (set-funcallable-instance-function c #'(lambda () (let ((new (make-array (1+ (length fields))))) (setf (aref new 0) name) new))))) ⇒#<STANDARD-METHOD :AFTER (#<FUNCALLABLE-STANDARD-CLASS CONSTRUCTOR>)>(setq c1 (make-instance 'constructor :name 'position :fields '(x y))) ⇒#<CONSTRUCTOR #<UNBOUND>>(setq p1 (funcall c1)) ⇒#(POSITION NIL NIL)
CLOS:STANDARD-INSTANCE-ACCESSCLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESSCLOS:SET-FUNCALLABLE-INSTANCE-FUNCTIONCLOS:SLOT-VALUE-USING-CLASS(SETF CLOS:SLOT-VALUE-USING-CLASS)CLOS:SLOT-BOUNDP-USING-CLASSCLOS:SLOT-MAKUNBOUND-USING-CLASSCLOS:STANDARD-INSTANCE-ACCESS(CLOS:STANDARD-INSTANCE-ACCESS
    instance location)instancelocationThis function is called to provide direct access to a slot in an instance. By usurping the normal slot lookup protocol, this function is intended to provide highly optimized access to the slots associated with an instance.
The following restrictions apply to the use of this function:
instance argument must be a
      standard instance (it must have been returned by
      ALLOCATE-INSTANCE(STANDARD-CLASS)instance argument cannot be an
      non-updated obsolete instance.location argument must be a location of
      one of the directly accessible slots of the instance's class.
    The results are undefined if any of these restrictions are violated.
CLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESS(CLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESS
    instance location)instancelocationThis function is called to provide direct access to a slot in an instance. By usurping the normal slot lookup protocol, this function is intended to provide highly optimized access to the slots associated with an instance.
The following restrictions apply to the use of this function:
instance argument must be a
      funcallable instance (it must have been returned by
      ALLOCATE-INSTANCE
       (CLOS:FUNCALLABLE-STANDARD-CLASS)instance argument cannot be an
      non-updated obsolete instance.location argument must be a location of
      one of the directly accessible slots of the instance's class.
    The results are undefined if any of these restrictions are violated.
CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION(CLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION
    funcallable-instance function)
funcallable-instanceALLOCATE-INSTANCE
       (CLOS:FUNCALLABLE-STANDARD-CLASS)functionCLOS:SET-FUNCALLABLE-INSTANCE-FUNCTION is called, any subsequent calls
   to funcallable-instance will run the new
   function.CLOS:SLOT-VALUE-USING-CLASS(CLOS:SLOT-VALUE-USING-CLASS class
    object slot)classobject argumentobjectslotThis generic function implements the behavior of the
   SLOT-VALUE function.  It is called by SLOT-VALUE with the class
   of object as its first argument and the pertinent effective slot definition metaobject as its
   third argument.
The generic function CLOS:SLOT-VALUE-USING-CLASS returns the value
   contained in the given slot of the given object.  If the slot is
   unbound, SLOT-UNBOUND is called.
The results are undefined if
 the class argument is not the class of the object argument, or
 if the slot argument does not appear among the set of effective
 slots associated with the class argument.
Methods
(CLOS:SLOT-VALUE-USING-CLASS
   (class STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))(CLOS:SLOT-VALUE-USING-CLASS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))These methods implement
 the full behavior of this generic function for slots with allocation
 :INSTANCE and :CLASS.  If the supplied slot has an allocation
 other than :INSTANCE or :CLASS an ERROR is SIGNALed.
Overriding these methods is permitted, but may require overriding other methods in the standard implementation of the slot access protocol.
(CLOS:SLOT-VALUE-USING-CLASS
   (class BUILT-IN-CLASS) object slot)SIGNALs an ERROR.
(SETF CLOS:SLOT-VALUE-USING-CLASS)((SETF CLOS:SLOT-VALUE-USING-CLASS) new-value class
    object slot)new-valueclassobject argument.objectslotnew-value argument.The generic function (SETF CLOS:SLOT-VALUE-USING-CLASS) implements
   the behavior of the ( function. It is called by
   SETF SLOT-VALUE)( with the class of SETF SLOT-VALUE)object as its second argument
   and the pertinent effective slot definition metaobject as its fourth argument.
The generic function (SETF CLOS:SLOT-VALUE-USING-CLASS) sets the value
   contained in the given slot of the given object to the given new
   value; any previous value is lost.
The results are undefined if
 the class argument is not the class of the object argument, or
 if the slot argument does not appear among the set of effective
 slots associated with the class argument.
Methods
((SETF CLOS:SLOT-VALUE-USING-CLASS)
   new-value (class STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))((SETF CLOS:SLOT-VALUE-USING-CLASS)
   new-value (class CLOS:FUNCALLABLE-STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))These methods implement
 the full behavior of this generic function for slots with allocation
 :INSTANCE and :CLASS.  If the supplied slot has an allocation
 other than :INSTANCE or :CLASS an ERROR is SIGNALed.
Overriding these methods is permitted, but may require overriding other methods in the standard implementation of the slot access protocol.
((SETF CLOS:SLOT-VALUE-USING-CLASS)
   new-value (class BUILT-IN-CLASS) object slot)SIGNALs an ERROR.
CLOS:SLOT-BOUNDP-USING-CLASS(CLOS:SLOT-BOUNDP-USING-CLASS class object
    slot)classobject argument.objectslotBOOLEANThis generic function implements the behavior of the
   SLOT-BOUNDP function.  It is called by SLOT-BOUNDP with the class
   of object as its first argument and the pertinent effective slot definition metaobject as its
   third argument.
The generic function CLOS:SLOT-BOUNDP-USING-CLASS tests whether a
   specific slot in an instance is bound.
The results are undefined if
 the class argument is not the class of the object argument, or
 if the slot argument does not appear among the set of effective
 slots associated with the class argument.
Methods
(CLOS:SLOT-BOUNDP-USING-CLASS
   (class STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))(CLOS:SLOT-BOUNDP-USING-CLASS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))These methods implement
 the full behavior of this generic function for slots with allocation
 :INSTANCE and :CLASS.  If the supplied slot has an allocation
 other than :INSTANCE or :CLASS an ERROR is SIGNALed.
Overriding these methods is permitted, but may require overriding other methods in the standard implementation of the slot access protocol.
(CLOS:SLOT-BOUNDP-USING-CLASS
   (class BUILT-IN-CLASS) object slot)SIGNALs an ERROR.Remarks. In cases where the class metaobject class does not distinguish unbound slots, true should be returned.
CLOS:SLOT-MAKUNBOUND-USING-CLASS(CLOS:SLOT-MAKUNBOUND-USING-CLASS class object
    slot)classobject argument.objectslotobject argument.This generic function implements the behavior of the
   SLOT-MAKUNBOUND function.  It is called by SLOT-MAKUNBOUND with
   the class of object as its first argument and the pertinent
   effective slot definition metaobject as its third argument.
The generic function CLOS:SLOT-MAKUNBOUND-USING-CLASS restores a slot in
   an object to its unbound state.  The interpretation
   of “restoring a slot to its unbound state” depends on
   the class metaobject class.
The results are undefined if
 the class argument is not the class of the object argument, or
 if the slot argument does not appear among the set of effective
 slots associated with the class argument.
Methods
(CLOS:SLOT-MAKUNBOUND-USING-CLASS
   (class STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))(CLOS:SLOT-MAKUNBOUND-USING-CLASS
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) object
   (slot CLOS:STANDARD-EFFECTIVE-SLOT-DEFINITION))These methods implement
 the full behavior of this generic function for slots with allocation
 :INSTANCE and :CLASS.  If the supplied slot has an allocation
 other than :INSTANCE or :CLASS an ERROR is SIGNALed.
Overriding these methods is permitted, but may require overriding other methods in the standard implementation of the slot access protocol.
(CLOS:SLOT-MAKUNBOUND-USING-CLASS
   (class BUILT-IN-CLASS) object slot)SIGNALs an ERROR.
It is convenient for portable metaobjects to be able to memoize information about other metaobjects, portable or otherwise. Because class and generic function metaobjects can be reinitialized, and generic function metaobjects can be modified by adding and removing methods, a means must be provided to update this memoized information.
The dependent maintenance protocol supports this by providing a
way to register an object which should be notified whenever a class or
generic function is modified.  An object which has been registered this
way is called a dependent of the class or generic function metaobject.
The dependents of class and generic function metaobjects are maintained with CLOS:ADD-DEPENDENT
and CLOS:REMOVE-DEPENDENT.  The dependents of a class or generic function metaobject can be
accessed with CLOS:MAP-DEPENDENTS.  Dependents are notified about a
modification by calling CLOS:UPDATE-DEPENDENT.  (See the specification of
CLOS:UPDATE-DEPENDENT for detailed description of the circumstances under
which it is called.)
To prevent conflicts between two portable programs, or between portable programs and the implementation, portable code must not register metaobjects themselves as dependents. Instead, portable programs which need to record a metaobject as a dependent, should encapsulate that metaobject in some other kind of object, and record that object as the dependent. The results are undefined if this restriction is violated.
This example shows a general facility for encapsulating metaobjects before recording them as dependents. The facility defines a basic kind of encapsulating object: an updater. Specializations of the basic class can be defined with appropriate special updating behavior. In this way, information about the updating required is associated with each updater rather than with the metaobject being updated.
Updaters are used to encapsulate any metaobject which requires
updating when a given class or generic function is modified.  The
function record-updater is called to both create an
updater and add it to the dependents of the class or generic function.
Methods on the generic function CLOS:UPDATE-DEPENDENT, specialized to the
specific class of updater do the appropriate update work.
(defclass updater ()
  ((dependent :initarg :dependent :reader dependent)))
(defun record-updater (class dependee dependent &REST initargs)
  (let ((updater (apply #'make-instance class :dependent dependent
                                              initargs)))
    (add-dependent dependee updater)
    updater))
A flush-cache-updater simply flushes the
cache of the dependent when it is updated.
(defclass flush-cache-updater (updater) ())
(defmethod update-dependent (dependee (updater flush-cache-updater)
                             &REST args)
  (declare (ignore args))
  (flush-cache (dependent updater)))
CLOS:UPDATE-DEPENDENT(CLOS:UPDATE-DEPENDENT metaobject
    dependent &REST initargs)
metaobjectdependentinitargsThis generic function is called to update a
   dependent of metaobject.
When a class or a generic function is reinitialized each of
   its dependents is updated.  The initargs argument to
   CLOS:UPDATE-DEPENDENT is the set of initialization arguments received by
   REINITIALIZE-INSTANCE.
When a method is added to a generic function, each of the
   generic function's dependents is updated.  The initargs argument
   is a list of two elements: the symbol ADD-METHOD, and the method
   that was added.
When a method is removed from a generic function, each of the
   generic function's dependents is updated.  The initargs argument
   is a list of two elements: the symbol REMOVE-METHOD, and the method
   that was removed.
In each case, CLOS:MAP-DEPENDENTS is used to call
   CLOS:UPDATE-DEPENDENT on each of the dependents.  So, for example, the
   update of a generic function's dependents when a method is added
   could be performed by the following code:
(CLOS:MAP-DEPENDENTSgeneric-function#'(lambda (dep) (CLOS:UPDATE-DEPENDENTgeneric-functiondep 'add-method new-method)))
Remarks. See Section 29.11, “Dependent Maintenance” for remarks about the use of this facility.
CLOS:ADD-DEPENDENT(CLOS:ADD-DEPENDENT metaobject
    dependent)metaobjectdependentThis generic function adds dependent to the
   dependents of metaobject.  If dependent is already in the set
   of dependents it is not added again (no ERROR is SIGNALed).
The generic function CLOS:MAP-DEPENDENTS can be called to access
   the set of dependents of a class or generic function.  The generic
   function CLOS:REMOVE-DEPENDENT can be called to remove an object from
   the set of dependents of a class or generic function.  The effect of
   calling CLOS:ADD-DEPENDENT or CLOS:REMOVE-DEPENDENT while a call to
   CLOS:MAP-DEPENDENTS on the same class or generic function is in progress
   is unspecified.
The situations in which CLOS:ADD-DEPENDENT is called are not
   specified.
Methods
(CLOS:ADD-DEPENDENT
   (class STANDARD-CLASS) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:ADD-DEPENDENT
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:ADD-DEPENDENT
   (generic-function STANDARD-GENERIC-FUNCTION) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
Remarks. See Section 29.11, “Dependent Maintenance” for remarks about the use of this facility.
CLOS:REMOVE-DEPENDENT(CLOS:REMOVE-DEPENDENT metaobject
     dependent)metaobjectdependentThis generic function removes dependent from the
   dependents of metaobject.  If dependent is not one of the
   dependents of metaobject, no ERROR is SIGNALed.
The generic function CLOS:MAP-DEPENDENTS can be called to access
   the set of dependents of a class or generic function.  The generic
   function CLOS:ADD-DEPENDENT can be called to add an object from the set
   of dependents of a class or generic function.  The effect of calling
   CLOS:ADD-DEPENDENT or CLOS:REMOVE-DEPENDENT while a call to
   CLOS:MAP-DEPENDENTS on the same class or generic function is in progress
   is unspecified.
 The situations in which CLOS:REMOVE-DEPENDENT is called are not
   specified.
Methods
(CLOS:REMOVE-DEPENDENT
   (class STANDARD-CLASS) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:REMOVE-DEPENDENT
   (class CLOS:FUNCALLABLE-STANDARD-CLASS) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:REMOVE-DEPENDENT
   (class STANDARD-GENERIC-FUNCTION) dependent)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
Remarks. See Section 29.11, “Dependent Maintenance” for remarks about the use of this facility.
CLOS:MAP-DEPENDENTS(CLOS:MAP-DEPENDENTS metaobject
    function)metaobjectfunctionfunction to each of
   the dependents of metaobject.  The order in which the dependents
   are processed is not specified, but function is applied to each
   dependent once and only once.  If, during the mapping,
   CLOS:ADD-DEPENDENT or CLOS:REMOVE-DEPENDENT is called to alter the
   dependents of metaobject, it is not specified whether the newly
   added or removed dependent will have function applied to it.
Methods
(CLOS:MAP-DEPENDENTS
   (metaobject STANDARD-CLASS) function)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:MAP-DEPENDENTS
   (metaobject CLOS:FUNCALLABLE-STANDARD-CLASS) function)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
(CLOS:MAP-DEPENDENTS
   (metaobject STANDARD-GENERIC-FUNCTION) function)No behavior is specified for this method beyond that which is specified for the generic function.
This method cannot be overridden unless the following methods are overridden as well:
Remarks. See Section 29.11, “Dependent Maintenance” for remarks about the use of this facility.
This section lists the differences between the [AMOP] and the CLISP implementation thereof.
Not implemented in CLISP
The generic function CLOS:MAKE-METHOD-LAMBDA is not implemented.
  See Section 29.5.3.2, “Generic Function Invocation Protocol”.
Features implemented differently in CLISP
The class precedence list of CLOS:FUNCALLABLE-STANDARD-OBJECT
  is different. See Section 29.2.2, “Inheritance Structure of Metaobject Classes”.
The DEFCLASS macro passes default values to CLOS:ENSURE-CLASS.
  See Section 29.3.1, “Macro DEFCLASS”.
The DEFGENERIC macro passes default values to ENSURE-GENERIC-FUNCTION.
  See Section 29.5.3.1, “Macro DEFGENERIC”.
The class CLOS:FORWARD-REFERENCED-CLASS is implemented differently.
  See Implementation of class CLOS:FORWARD-REFERENCED-CLASS in CLISP.
The function CLOS:GENERIC-FUNCTION-ARGUMENT-PRECEDENCE-ORDER SIGNALs an ERROR
  if the generic function has no lambda list.
Extensions specific to CLISP
The Meta-Object Protocol is applicable to classes of type STRUCTURE-CLASS.
  The default superclass for STRUCTURE-CLASS instances is
  STRUCTURE-OBJECT.
  Structure classes do not support multiple inheritance and reinitialization.
  See Section 29.3.5.1, “Initialization of class metaobjects”.
  See also Section 8.2, “The structure Meta-Object Protocol.”.
The DEFGENERIC macro supports user-defined options.
  See User-defined options.
The class METHOD is subclassable.
  See Section 29.2.2, “Inheritance Structure of Metaobject Classes”.
Slot names like NIL and T are allowed.
  See Section 29.4.2.1.1, “Generic Function CLOS:SLOT-DEFINITION-NAME”.
The CLOS:VALIDATE-SUPERCLASS method is more permissive by
  default and does not need to be overridden in
  some “obvious” cases.
  See Section 29.3.6.7, “Generic Function CLOS:VALIDATE-SUPERCLASS”.
New generic function CLOS:COMPUTE-DIRECT-SLOT-DEFINITION-INITARGS.  It can sometimes
  be used when overriding CLOS:DIRECT-SLOT-DEFINITION-CLASS is cumbersome.
New generic function CLOS:COMPUTE-EFFECTIVE-SLOT-DEFINITION-INITARGS. It can sometimes
  be used when overriding CLOS:EFFECTIVE-SLOT-DEFINITION-CLASS is cumbersome.
New function CLOS:COMPUTE-EFFECTIVE-METHOD-AS-FUNCTION. It
  can be used in overriding methods of CLOS:COMPUTE-DISCRIMINATING-FUNCTION.
The generic function CLOS:ENSURE-GENERIC-FUNCTION-USING-CLASS accepts a
  :DECLARE keyword.
The functions CLOS:FUNCALLABLE-STANDARD-INSTANCE-ACCESS and
  CLOS:STANDARD-INSTANCE-ACCESS support non-updated obsolete instances and
  also support slots with allocation :CLASS.
The existence of the function CLOS:CLASS-DIRECT-SUBCLASSES
  does not prevent otherwise unreferenced classes from being garbage-collected.
When CLISP encounters suspicious CLOS code, it issues a
 WARNING of type CLOS:CLOS-WARNING.
 To suppress the undesired warnings (not recommended!) use
 EXT:SET-GLOBAL-HANDLER with MUFFLE-WARNING on the appropriate
 WARNING type;.
 To find where the warnings come from (recommended), set
 *BREAK-ON-SIGNALS* to the appropriate WARNING type.
This is a hint that the order in which program files are loaded (order of definitions, order of macro expansions, or similar) is wrong. Example:
(defclass ware () ((title :initarg :title :accessor title)))
(defclass book (ware) ())
(defclass compact-disk (ware) ())
(defclass dvd (ware) ())
(defgeneric add-to-inventory (object))
(defmethod add-to-inventory ((object ware)) nil)
(add-to-inventory (make-instance 'book :title "CLtL1"))
(defvar *book-counter* 0)
(defmethod add-to-inventory ((object book)) (incf *book-counter*))
(add-to-inventory (make-instance 'book :title "CLtL2"))
*book-counter*
⇒ 1
 Since [CLtL1] and [CLtL2] were already added to the inventory, the
 programmer might have expected that *book-counter*
 is 2.
A few functions, such as PRINT-OBJECT, are listed in the
  [ANSI CL standard] and the [AMOP] as “standard generic functions”,
  to which users may add methods.
  This warning is not issued for such functions.
A generic function is defined by a contract.
  Whoever puts a method on a generic function, however, is also
  expecting a contract to be fulfilled.
  (In the example above, it is that *book-counter*
  equals the number of invocations
  of add-to-inventory on book instances.)
  If the generic function was already called before the
  method was installed, the method's contract was definitely broken.
  Maybe the programmer has foreseen this case (in this example:
  he could initialize *book-counter* to the number of
  instances of book that exist at this moment, rather than to 0),
  or maybe not. This is what the warning is about.
This is a hint that different parts of the program, possibly developed by independent people, are colliding. Example: in addition to the code above:
(defvar *book-sales-statistics* (make-hash-table :test 'equal)) (defmethod add-to-inventory ((object book)) (setf (gethash (title object) sale-stats) (cons 0 0))) (add-to-inventory (make-instance 'book :title "AMOP")) *book-counter* ⇒1*book-sales-statistics* ⇒#S(HASH-TABLE :TEST FASTHASH-EQUAL ("AMOP" . (0 . 0)))
The programmer who programmed the first
 add-to-inventory@book*book-counter* will be incremented.
 The programmer who programmed the second
 add-to-inventory@book*book-sales-statistics* gets
 augmented.  If the implementation gives no warning, one of the two
 programmers will waste time debugging.
This warning can be warranted for the same reason as above: if the old method and the new method have a different contract, something is fishy and possibly wrong. Additionally, the programmers may not even have intended to replace the method. They may have intended cumulative effects of the two methods.
Table of Contents
This interface permits the definition of new classes of streams, and programming their behavior by defining methods for the elementary stream operations. It is based on the proposal STREAM-DEFINITION-BY-USER:GENERIC-FUNCTIONS of David N. Gray to X3J13 and is supported by most Common Lisp implementations currently in use.
All symbols defined by this interface, starting with the prefix
 FUNDAMENTAL- or STREAM-,
 are exported from the package “GRAY”
 and EXT:RE-EXPORTed from “EXT”.
Defined classes
GRAY:FUNDAMENTAL-STREAMSTREAM and of STANDARD-OBJECT.
   Its metaclass is STANDARD-CLASS.GRAY:FUNDAMENTAL-INPUT-STREAMSTREAMs.
   It is a subclass of GRAY:FUNDAMENTAL-STREAM.  The built-in function INPUT-STREAM-P
   returns true on instances of this class.  This means that when you
   define a new stream class capable of doing input, you have to make it
   a subclass of GRAY:FUNDAMENTAL-INPUT-STREAM.GRAY:FUNDAMENTAL-OUTPUT-STREAMSTREAMs.
   It is a subclass of GRAY:FUNDAMENTAL-STREAM.  The built-in function OUTPUT-STREAM-P
   returns true on instances of this class.  This means that when you
   define a new stream class capable of doing output, you have to make
   it a subclass of GRAY:FUNDAMENTAL-OUTPUT-STREAM.GRAY:FUNDAMENTAL-CHARACTER-STREAMSTREAM-ELEMENT-TYPE is CHARACTER.  It is a subclass of
   GRAY:FUNDAMENTAL-STREAM.  It defines a method on STREAM-ELEMENT-TYPE that returns
   CHARACTER.GRAY:FUNDAMENTAL-BINARY-STREAMSTREAM-ELEMENT-TYPE is a subtype of INTEGER.  It is a
   subclass of GRAY:FUNDAMENTAL-STREAM.  When you define a subclass of GRAY:FUNDAMENTAL-BINARY-STREAM,
   you have to provide a method on STREAM-ELEMENT-TYPE.
  GRAY:FUNDAMENTAL-CHARACTER-INPUT-STREAMGRAY:FUNDAMENTAL-CHARACTER-STREAM and GRAY:FUNDAMENTAL-INPUT-STREAM.GRAY:FUNDAMENTAL-CHARACTER-OUTPUT-STREAMGRAY:FUNDAMENTAL-CHARACTER-STREAM and GRAY:FUNDAMENTAL-OUTPUT-STREAM.GRAY:FUNDAMENTAL-BINARY-INPUT-STREAMGRAY:FUNDAMENTAL-BINARY-STREAM and GRAY:FUNDAMENTAL-INPUT-STREAM.GRAY:FUNDAMENTAL-BINARY-OUTPUT-STREAMGRAY:FUNDAMENTAL-BINARY-STREAM and GRAY:FUNDAMENTAL-OUTPUT-STREAM.General generic functions defined on streams
(STREAM-ELEMENT-TYPE stream)Returns the stream's element type, normally a
   subtype of CHARACTER or INTEGER.
The method for GRAY:FUNDAMENTAL-CHARACTER-STREAM returns CHARACTER.
  
((SETF STREAM-ELEMENT-TYPE)
    new-element-type stream)Changes the stream's element type.
The default method SIGNALs an ERROR.
This function is a CLISP extension (see Section 21.3.1, “Function STREAM-ELEMENT-TYPE”).
(CLOSE stream &KEY
    :ABORT)Closes the stream and flushes any associated buffers.
When you define a primary method on this
    function, do not forget to CALL-NEXT-METHOD.
  
(OPEN-STREAM-P stream)Returns true before the stream has been closed, and
    NIL after the stream has been closed.
You do not need to add methods to this function.
(GRAY:STREAM-POSITION
    stream position)Just like FILE-POSITION, but NIL
    position means inquire.
You must define a method for this function.
generic functions for character input
(GRAY:STREAM-READ-CHAR stream)If a character was pushed back using GRAY:STREAM-UNREAD-CHAR,
   returns and consumes it.  Otherwise returns and consumes the next
   character from the stream. Returns :EOF if the end-of-stream is reached.
   
You must define a method for this function.
(GRAY:STREAM-UNREAD-CHAR stream char)Pushes char, which must be the last character
   read from the stream, back onto the front of the stream.
   
You must define a method for this function.
(GRAY:STREAM-READ-CHAR-NO-HANG stream)Returns a character or :EOF, like GRAY:STREAM-READ-CHAR, if
   that would return immediately.  If GRAY:STREAM-READ-CHAR's value is not available
   immediately, returns NIL instead of waiting.
   The default method simply calls GRAY:STREAM-READ-CHAR; this is sufficient for streams
   whose GRAY:STREAM-READ-CHAR method never blocks.
(GRAY:STREAM-PEEK-CHAR
    stream)If a character was pushed back using GRAY:STREAM-UNREAD-CHAR,
   returns it.  Otherwise returns the next character from the stream,
   avoiding any side effects GRAY:STREAM-READ-CHAR would do.  Returns :EOF if the
   end-of-stream is reached.
The default method calls GRAY:STREAM-READ-CHAR and GRAY:STREAM-UNREAD-CHAR; this is
   sufficient for streams whose GRAY:STREAM-READ-CHAR method has no
   side-effects.
(GRAY:STREAM-LISTEN
    stream)If a character was pushed back using GRAY:STREAM-UNREAD-CHAR,
   returns it.  Otherwise returns the next character from the stream, if
   already available.  If no character is available immediately, or if
   end-of-stream is reached, returns NIL.
The default method calls GRAY:STREAM-READ-CHAR-NO-HANG and GRAY:STREAM-UNREAD-CHAR; this is
   sufficient for streams whose GRAY:STREAM-READ-CHAR method has no
   side-effects.
(GRAY:STREAM-READ-CHAR-WILL-HANG-P
    stream)Returns NIL if GRAY:STREAM-READ-CHAR will return immediately.
   Otherwise it returns true.
The default method calls GRAY:STREAM-READ-CHAR-NO-HANG and GRAY:STREAM-UNREAD-CHAR; this is
   sufficient for streams whose GRAY:STREAM-READ-CHAR method has no side-effects.
This function is a CLISP extension (see EXT:READ-CHAR-WILL-HANG-P).
(GRAY:STREAM-READ-CHAR-SEQUENCE stream
   sequence &OPTIONAL [start [end]])Fills the subsequence of sequence specified by
   :START and :END with characters consecutively read from stream.
   Returns the index of the first element of sequence that was not
   updated (= end, or < end if the stream reached its end).
   
sequence is an ARRAY of CHARACTERs, i.e. a STRING.
   start is a nonnegative INTEGER and defaults to 0.
   end is a nonnegative INTEGER or NIL and defaults to NIL,
   which stands for (.
  LENGTH sequence)
The default method repeatedly calls GRAY:STREAM-READ-CHAR; this
   is always sufficient if speed does not matter.
This function is a CLISP extension (see
   EXT:READ-CHAR-SEQUENCE).
(GRAY:STREAM-READ-LINE
    stream)Reads a line of characters, and return two values:
   the line (a STRING, without the terminating #\Newline character),
   and a BOOLEAN value which is true if the line was terminated by
   end-of-stream instead of #\Newline.
The default method repeatedly calls GRAY:STREAM-READ-CHAR; this
   is always sufficient.
(GRAY:STREAM-CLEAR-INPUT
    stream)Clears all pending interactive input from the
   stream, and returns true if some pending input was removed.
The default method does nothing and returns NIL; this is
   sufficient for non-interactive streams.
generic functions for character output
(GRAY:STREAM-WRITE-CHAR stream char)Writes char.
   
You must define a method for this function.
(GRAY:STREAM-LINE-COLUMN stream)Returns the column number where the next character
   would be written (0 stands for the first column),
    or NIL if that is not meaningful for this stream.
   
You must define a method for this function.
(GRAY:STREAM-START-LINE-P
                 stream)Returns true if the next character would be written at the start of a new line.
The default method calls GRAY:STREAM-LINE-COLUMN and compares its result with
   0; this is sufficient for streams whose GRAY:STREAM-LINE-COLUMN never returns NIL.
  
(GRAY:STREAM-WRITE-CHAR-SEQUENCE
    stream sequence &OPTIONAL [start [end]])Outputs the subsequence of sequence specified
   by :START and :END to stream.
sequence is an ARRAY of CHARACTERs, i.e. a STRING.
   start is a nonnegative INTEGER and defaults to 0.
   end is a nonnegative integer or NIL and defaults to NIL,
   which stands for (.
  LENGTH sequence)
The default method repeatedly calls GRAY:STREAM-WRITE-CHAR; this
   is always sufficient if speed does not matter.
  
This function is a CLISP extension
   (see EXT:WRITE-CHAR-SEQUENCE).
(GRAY:STREAM-WRITE-STRING
    stream string &OPTIONAL [start [end]])Outputs the subsequence of string specified by
   :START and :END to stream.  Returns string.
string is a string.  start is a nonnegative integer
   and default to 0.  end is a nonnegative integer or NIL and
   defaults to NIL, which stands for (.
   LENGTH string)
The default method calls
   GRAY:STREAM-WRITE-CHAR-SEQUENCE;
   this is always sufficient.
(GRAY:STREAM-TERPRI
                 stream)Outputs a #\Newline character.
The default method calls GRAY:STREAM-WRITE-CHAR; this is always
   sufficient.
(GRAY:STREAM-FRESH-LINE
                 stream)Possibly outputs a #\Newline character, so as to ensure that the next character would be written at the start of a new line. Returns true if it did output a #\Newline character.
The default method calls
   GRAY:STREAM-START-LINE-P and then
   GRAY:STREAM-TERPRI if necessary; this is always
   sufficient.
(GRAY:STREAM-FINISH-OUTPUT
                 stream)Ensures that any buffered output has reached its destination, and then returns.
The default method does nothing.
(GRAY:STREAM-FORCE-OUTPUT
                 stream)Brings any buffered output on its way towards its destination, and returns without waiting until it has reached its destination.
The default method does nothing.
(GRAY:STREAM-CLEAR-OUTPUT
                 stream)Attempts to discard any buffered output which has not yet reached its destination.
The default method does nothing.
(GRAY:STREAM-ADVANCE-TO-COLUMN
    stream column)Ensures that the next character will be written at
    least at column.
The default method outputs an appropriate amount of space characters; this is sufficient for non-proportional output.
generic functions for binary input
(GRAY:STREAM-READ-BYTE stream)Returns and consumes the next integer from the
   stream. Returns :EOF if the end-of-stream is reached.
You must define a method for this function.
(GRAY:STREAM-READ-BYTE-LOOKAHEAD stream)To be called only if stream's
   STREAM-ELEMENT-TYPE is ( or UNSIGNED-BYTE 8)(.
   Returns SIGNED-BYTE 8)T if GRAY:STREAM-READ-BYTE would return immediately with an
   INTEGER result.  Returns :EOF if the end-of-stream is already
   known to be reached.  If GRAY:STREAM-READ-BYTE's value is not available
   immediately, returns NIL instead of waiting.
You must define a method for this function.
This function is a CLISP extension (see
   EXT:READ-BYTE-LOOKAHEAD).
(GRAY:STREAM-READ-BYTE-WILL-HANG-P stream)To be called only if stream's
   STREAM-ELEMENT-TYPE is ( or UNSIGNED-BYTE 8)(.
   Returns SIGNED-BYTE 8)NIL if GRAY:STREAM-READ-BYTE will return immediately.
   Otherwise it returns true.
The default method calls GRAY:STREAM-READ-BYTE-LOOKAHEAD; this is always sufficient.
   
This function is a CLISP extension (see EXT:READ-BYTE-WILL-HANG-P).
 
(GRAY:STREAM-READ-BYTE-NO-HANG stream)To be called only if stream's
   STREAM-ELEMENT-TYPE is ( or UNSIGNED-BYTE 8)(.
   Returns an SIGNED-BYTE 8)INTEGER or :EOF, like GRAY:STREAM-READ-BYTE, if that would
   return immediately.  If GRAY:STREAM-READ-BYTE's value is not available immediately,
   returns NIL instead of waiting.
The default method calls GRAY:STREAM-READ-BYTE if GRAY:STREAM-READ-BYTE-LOOKAHEAD returns true;
    this is always sufficient.
This function is a CLISP extension (see EXT:READ-BYTE-NO-HANG).
 
(GRAY:STREAM-READ-BYTE-SEQUENCE
     stream sequence &OPTIONAL
      [start [end [no-hang [interactive]]]])Fills the subsequence of sequence specified by
    :START and :END with integers consecutively read from stream.
    Returns the index of the first element of sequence that was not
    updated (= end, or < end if the stream reached its end).
   
sequence is an ARRAY of INTEGERs.
    start is a nonnegative INTEGER and defaults to 0.
    end is a nonnegative INTEGER or NIL and defaults to NIL,
    which stands for (.
    If LENGTH sequence)no-hang is true, the function should avoid blocking and instead fill
    only as many elements as are immediately available. If no-hang is false
    and interactive is true, the function can block for reading the first
    byte but should avoid blocking for any further bytes.
The default method repeatedly calls GRAY:STREAM-READ-BYTE; this
    is always sufficient if speed does not matter.
This function is a CLISP extension (see
    EXT:READ-BYTE-SEQUENCE).
generic functions for binary output
(GRAY:STREAM-WRITE-BYTE
                 stream integer)Writes integer.
You must define a method for this function.
(GRAY:STREAM-WRITE-BYTE-SEQUENCE
     stream sequence &OPTIONAL
      [start [end [no-hang [interactive]]]])Outputs the subsequence of sequence specified
    by :START and :END to stream
sequence is an ARRAY of INTEGERs.
    start is a nonnegative INTEGER and defaults to 0.
    end is a nonnegative INTEGER or NIL and defaults to NIL,
    which stands for (.
    If LENGTH sequence)no-hang is true, the function should avoid blocking and instead output
    only as many elements as it can immediately proceed. If no-hang is false
    and interactive is true, the function can block for writing the first
    byte but should avoid blocking for any further bytes.
The default method repeatedly calls
    GRAY:STREAM-WRITE-BYTE; this is always
    sufficient if speed does not matter.
This function is a CLISP extension (see
    EXT:WRITE-BYTE-SEQUENCE).
EXT:FILL-STREAMAs an example of the use of “GRAY” STREAMs, CLISP
 offers an additional class, EXT:FILL-STREAM.  An instance of this class
 is a “formatting” STREAM, which makes the final
 output to the underlying stream look neat: indented and filled.
 An instance of EXT:FILL-STREAM is created like this:
(MAKE-INSTANCE'EXT:FILL-STREAM:streamstream[:text-indent symbol-or-number] [:sexp-indent symbol-or-number-or-function])
where
streamSTREAM where the output actually
    goes.symbol-or-numberINTEGER text
    indentation or the indentation itself (defaults to 0).
 symbol-or-number-or-functionWhen FORMAT writes an S-expression to a
    EXT:FILL-STREAM using ~S, and the expression's printed
    representation does not fit on the current line, it is printed on
    separate lines, ignoring the prescribed text indentation and
    preserving spacing.  When this argument is non-NIL, the
    S-expression is indented by:
    Defaults to CUSTOM:*FILL-INDENT-SEXP*, whose initial value is 1+.
Note that, due to buffering, one must call FORCE-OUTPUT
 when done with the EXT:FILL-STREAM (and before changing the indent variable).
 The former is done automatically by the macro
(with-fill-stream (fill target-stream ...) ...).
Example 30.1. Example of EXT:FILL-STREAM usage
(defvar *my-indent-level*)
(with-output-to-string (out)
  (let ((*print-right-margin* 20)
        (*print-pretty* t)
        (*my-indent-level* 2))
    (with-fill-stream (fill out :text-indent '*my-indent-level*)
      (format fill "~%this is some long sentence which will      be broken at spaces")
      (force-output fill)
      (let ((*my-indent-level* 5))
        (format fill "~%and    properly indented to the level specified by the ~S argument which can be a ~S or an ~S - cool!"
                :TEXT-INDENT 'symbol 'integer))
      (format fill "~%Don't forget  to call ~S on it, and/or use ~S   Pretty formatting of the  S-expressions    printed with ~~S is  preserved: ~S"
              'force-output 'with-fill-stream '(defun foo (x y z) (if x (+ y z) (* y z)))))))
⇒ "
  this is some long
  sentence which
  will be broken at
  spaces
     and properly
     indented to
     the level
     specified by
     the :TEXT-INDENT
     argument which
     can be a
SYMBOL
     or an INTEGER
     - cool!
  Don't forget to
  call FORCE-OUTPUT
  on it, and/or use
WITH-FILL-STREAM
  Pretty formatting
  of the
  S-expressions
  printed with ~S
  is preserved:
(DEFUN FOO (X Y Z)
 (IF X (+ Y Z)
  (* Y Z)))
"Table of Contents
EXT:ETHEEXT:LETF & EXT:LETF*EXT:OPEN-HTTP and
  macro EXT:WITH-HTTP-INPUTEXT:BROWSE-URLCUSTOM:*HTTP-PROXY*Table of Contents
EXT:ETHEEXT:LETF & EXT:LETF*EXT:OPEN-HTTP and
  macro EXT:WITH-HTTP-INPUTEXT:BROWSE-URLCUSTOM:*HTTP-PROXY*Initialization
Parse command line arguments until the first
    positional argument (see :SCRIPT in
    Section 31.2, “Saving an Image”).
Load the memory image.
Install internal signal handlers.
Initialize time variables.
Initialize locale-dependent encodings.
Initialize stream variables.
Initialize pathname variables.
Initialize “FFI”.
Run all functions in CUSTOM:*INIT-HOOKS*.
Say “hi”, unless suppressed by -q.
  
The actual work
Handle command line options: file loading and/or compilation, form evaluation, script execution, read-eval-print loop.
Finalization (executed even on abnormal exit due
  to kill)
Unwind the STACK, executing cleanup forms in
    UNWIND-PROTECT.
Run all functions in CUSTOM:*FINI-HOOKS*.
Call FRESH-LINE on the standard streams.
Say “bye” unless suppressed by -q.
  
Wait for a keypress if requested by
    -w.
  
Close all open FILE-STREAMs.
Close all open DLLs.
CUSTOM:*INIT-HOOKS* is run like this:
(MAPC#'FUNCALLCUSTOM:*INIT-HOOKS*)
CUSTOM:*INIT-HOOKS* and init functionCUSTOM:*INIT-HOOKS* are
    always run regardless of the command line
    options before even the banner is printed.CUSTOM:*FINI-HOOKS* is run like this:
(MAPC#'FUNCALLCUSTOM:*FINI-HOOKS*)
The function (
 saves the running CLISP's memory to the file EXT:SAVEINITMEM &OPTIONAL
  (filename "lispinit.mem") &KEY :KEEP-GLOBAL-HANDLERS :QUIET
  :INIT-FUNCTION :LOCKED-PACKAGES :START-PACKAGE :EXECUTABLE :NORC
  :SCRIPT :DOCUMENTATION :VERBOSE)filename;
 extension #P".mem" is recommended (when filename does not have an
 extension, #P".mem" extension is automatically added unless the file
 being created is an executable).
:QUIETIf this argument is not NIL, the startup banner
    and the good-bye message will be suppressed, as if by -q.
This is not recommended for interactive application delivery, please append your banner to ours (using init function) instead of replacing it.
:VERBOSECUSTOM:*SAVEINITMEM-VERBOSE*; initial value is T.
 :NORCNIL, the RC file
    loading will be suppressed, as if by -norc.
 :INIT-FUNCTIONThis argument specifies a function that will be
   executed at startup of the saved image, before entering the standard read-eval-print loop
   (but after all other initialization, see Section 31.1.1, “Cradle to Grave”);
   thus, if you want to avoid the read-eval-print loop, you have to call
   EXT:EXIT at the end
   of the init function yourself
   (this does not prevent CUSTOM:*FINI-HOOKS* from being run).
See the manual for passing command line arguments to this function.
See also CUSTOM:*INIT-HOOKS* and CUSTOM:*FINI-HOOKS*.
:SCRIPTThis options determines the handling of positional arguments when the image is invoked.
T, then the first positional argument
       is the script name and the rest is placed into EXT:*ARGS*, as described
       in Section 32.5.2, “Scripting with CLISP”.NIL, then all positional arguments
       are placed into EXT:*ARGS* to be handled by the init function.
     
    This option defaults to T when init function is NIL and to
    NIL when init function is non-NIL.
 
:DOCUMENTATIONThe description of what this image does, printed
    by the -help-image olption.
Defaults to (DOCUMENTATION init function
     'FUNCTION)
:LOCKED-PACKAGESCUSTOM:*SYSTEM-PACKAGE-LIST*.
 :START-PACKAGE*PACKAGE* in the image being saved, and defaults to the current
   value of *PACKAGE*.:KEEP-GLOBAL-HANDLERSWhen non-NIL, the currently established global
    handlers (either with EXT:SET-GLOBAL-HANDLER or with -on-error)
    are inherited by the image.  Defaults to NIL, so that
    
$clisp -i myfile -x '(EXT:SAVEINITMEM)'
will produce an image without any global handlers inherited from the batch mode of the above command.
:EXECUTABLENIL, the saved file will be an
    standalone executable.
    In this case, the #P".mem" extension is not added.
    On Win32 and Cygwin the extension #P".exe"
    is added instead.
You can use this memory image with the -M option.
On UNIX systems, you may compress it with GNU gzip to save disk
space.
Memory images are not portable across different platforms
  (in contrast with platform-independent #P".fas" files).
  They are not even portable across linking sets: image saved using
  the full linking set cannot be used with the base runtime:
$clisp -K full -x '(EXT:SAVEINITMEM)'$clisp -K base -M lispinit.mem base/lisp.run: initialization file `lispinit.mem' was not created by this version of CLISP runtime
The functions
| ( | 
| ( | 
| ( | 
 - all synonymous - terminate CLISP.  If status is non-NIL,
 CLISP aborts with the supplied numeric error status, i.e.,
 the OS environment is informed that the CLISP session did not
 succeed.
Final delimiters also terminate CLISP.
CLISP is internationalized, and is localized for the languages English, German, French, Spanish, Dutch, Russian, and Danish. CLISP also supports internationalized Lisp programs, through GNU gettext, see Section 33.2, “Internationalization of User Programs”.
User programs can also be internationalized, see Section 33.2, “Internationalization of User Programs”.
The facilities described in this section will work only for the languages for which CLISP itself is already localized.
The language CLISP uses to communicate with the user can be one of
| ENGLISH | 
| DEUTSCH(i.e., German) | 
| FRANÇAIS(i.e., French) | 
| ESPAÑOL(i.e., Spanish) | 
| NEDERLANDS(i.e., Dutch) | 
| РУССКИЙ(i.e. Russian) | 
| DANSK(i.e., Danish) | 
This is controlled by the SYMBOL-MACRO
 CUSTOM:*CURRENT-LANGUAGE*,
 which can be set at run time as well as using the -L start-up option.
 If you wish to change the
 locale directory
 at run time too, you can do that by setting CUSTOM:*CURRENT-LANGUAGE* to a CONS
 cell, whose CAR is the language (a SYMBOL, one of the above),
 and whose CDR is the new locale directory.
More languages can be defined through the macro
 I18N:DEFLANGUAGE:
 (.
 For such an additional language to take effect, you must install the
 corresponding message catalog, or translate the messages yourself,
 using GNU gettext and Emacs (or XEmacs) po-mode.I18N:DEFLANGUAGE language)
This works only for strings.  For arbitrary language-dependent
 Lisp objects, you define one through the macro
 I18N:DEFINTERNATIONAL:
 ( and add
 language-dependent values through the macro
 I18N:DEFINTERNATIONAL symbol &OPTIONAL
 (default-language T))I18N:DEFLOCALIZED:
 (
 (One such form for each language.  Languages without an assigned
 value will be treated like the default-language.)
 You can then access the localized value by calling
 I18N:DEFLOCALIZED symbol language
  value-form)I18N:LOCALIZED:
 (I18N:LOCALIZED symbol &OPTIONAL language)
An “encoding” describes the correspondence
 between CHARACTERs and raw bytes during input/output via
 STREAMs with STREAM-ELEMENT-TYPE CHARACTER.
An EXT:ENCODING is an object composed of the following facets:
CHARACTERs that
    can be represented and passed through the I/O channel, and the way
    these characters translate into raw bytes, i.e., the map between
    sequences of CHARACTER and (UNSIGNED-BYTE 8) in the form of STRINGs
    and (VECTOR (UNSIGNED-BYTE 8)) as well as character and byte STREAMs.
    In this context, for example, CHARSET:UTF-8 and CHARSET:UCS-4
    are considered different, although they can represent the same set
    of characters.EXT:ENCODINGs are also TYPEs.  As such, they represent the set of
 characters encodable in the character set.  In this context, the way
 characters are translated into raw bytes is ignored, and the line
 terminator mode is ignored as well.  TYPEP and SUBTYPEP can be used
 on encodings:
(SUBTYPEPCHARSET:UTF-8CHARSET:UTF-16) ⇒; ⇒T(TSUBTYPEPCHARSET:UTF-16CHARSET:UTF-8) ⇒; ⇒T(TSUBTYPEPCHARSET:ASCII CHARSET:ISO-8859-1) ⇒; ⇒T(TSUBTYPEPCHARSET:ISO-8859-1 CHARSET:ASCII) ⇒; ⇒NILT
The following character sets are supported, as values of the corresponding (constant) symbol in the “CHARSET” package:
Symbols in package “CHARSET”
UCS-2
   ≡ UNICODE-16
   ≡ UNICODE-16-BIG-ENDIAN,
   the 16-bit basic multilingual plane of the UNICODE character set.
   Every character is represented as two bytes.UNICODE-16-LITTLE-ENDIAN
    UCS-4
   ≡ UNICODE-32
   ≡ UNICODE-32-BIG-ENDIAN,
   the 21-bit UNICODE character set. Every character is represented as
   four bytes. This encoding is used by CLISP internally.UNICODE-32-LITTLE-ENDIANUTF-8,
   the 21-bit UNICODE character set.
   Every character is represented as one to four bytes.
   ASCII characters represent themselves and need one byte per character.
   Most Latin/Greek/Cyrillic/Hebrew characters need two bytes per
   character. Most other characters need three bytes per character,
   and the rarely used remaining characters need four bytes per
   character. This is therefore, in general, the most space-efficient
   encoding of all of Unicode.UTF-16,
   the 21-bit UNICODE character set. Every character in the 16-bit
   basic multilingual plane is represented as two bytes, and the
   rarely used remaining characters need four bytes per character.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.UTF-7,
   the 21-bit UNICODE character set. This is a stateful 7-bit encoding.
   Not all ASCII characters represent themselves.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.JAVA,
   the 21-bit UNICODE character set.
   ASCII characters represent themselves and need one byte per character.
   All other characters of the basic multilingual plane are represented
   by \unnnn sequences
   (nnnn a hexadecimal number)
   and need 6 bytes per character. The remaining characters are represented
   by \uxxxx\uyyyy
   and need 12 bytes per character. While this encoding is very comfortable
   for editing Unicode files using only ASCII-aware tools and editors, it
   cannot faithfully represent all UNICODE text. Only text which
   does not contain \u (backslash followed by
   lowercase Latin u) can be faithfully represented by this encoding.
 ASCII,
   the well-known US-centric 7-bit character set (American Standard
   Code for Information Interchange - ASCII).ISO-8859-1,
   an extension of the ASCII character set, suitable for the Afrikaans, Albanian, Basque, Breton, Catalan,
   Cornish, Danish, Dutch, English, Færoese, Finnish, French,
   Frisian, Galician, German, Greenlandic, Icelandic, Irish, Italian,
   Latin, Luxemburgish, Norwegian, Portuguese, Ræto-Romanic,
   Scottish, Spanish, and Swedish languages.
This encoding has the nice property that
(LOOP:for i :from 0 :toCHAR-CODE-LIMIT:for c = (CODE-CHARi) :always (OR(NOT(TYPEPc CHARSET:ISO-8859-1)) (EQUALP(EXT:CONVERT-STRING-TO-BYTES(STRINGc) CHARSET:ISO-8859-1) (VECTORi)))) ⇒T
   i.e., it is compatible with CLISP CODE-CHAR/CHAR-CODE
   in its own domain.
ISO-8859-2,
   an extension of the ASCII character set, suitable for the Croatian, Czech, German, Hungarian, Polish,
   Slovak, Slovenian, and Sorbian languages. ISO-8859-3,
   an extension of the ASCII character set, suitable for the Esperanto and Maltese languages.ISO-8859-4,
   an extension of the ASCII character set, suitable for the Estonian, Latvian, Lithuanian and Sami (Lappish)
   languages.ISO-8859-5,
   an extension of the ASCII character set, suitable for the Bulgarian, Byelorussian, Macedonian, Russian,
   Serbian, and Ukrainian languages.ISO-8859-6,
   suitable for the Arabic language.ISO-8859-7,
   an extension of the ASCII character set, suitable for the Greek language.ISO-8859-8,
      an extension of the ASCII character set, suitable for the Hebrew language (without punctuation).
 ISO-8859-9,
   an extension of the ASCII character set, suitable for the Turkish language.ISO-8859-10,
   an extension of the ASCII character set, suitable for the Estonian, Icelandic, Inuit (Greenlandic), Latvian,
   Lithuanian, and Sami (Lappish) languages.ISO-8859-13,
   an extension of the ASCII character set, suitable for the Estonian, Latvian, Lithuanian, Polish and Sami
   (Lappish) languages.ISO-8859-14,
   an extension of the ASCII character set, suitable for the Irish Gælic, Manx Gælic, Scottish
   Gælic, and Welsh languages.ISO-8859-15,
   an extension of the ASCII character set, suitable for the ISO-8859-1 languages, with improvements for
   French, Finnish and the Euro.ISO-8859-16
   an extension of the ASCII character set, suitable for the Rumanian language.KOI8-R,
   an extension of the ASCII character set, suitable for the Russian language (very popular, especially on the
   internet).KOI8-U,
   an extension of the ASCII character set, suitable for the Ukrainian language (very popular, especially on the
   internet).KOI8-RU,
   an extension of the ASCII character set, suitable for the Russian language. This character set is only available on
                           platforms with GNU libiconv.JIS_X0201,
   a character set for the Japanese language.MAC-ARABIC,
   a platform specific extension of the ASCII character set.MAC-CENTRAL-EUROPE,
   a platform specific extension of the ASCII character set.MAC-CROATIAN,
   a platform specific extension of the ASCII character set.MAC-CYRILLIC,
   a platform specific extension of the ASCII character set.MAC-DINGBAT,
   a platform specific character set.
 MAC-GREEK,
   a platform specific extension of the ASCII character set.MAC-HEBREW,
   a platform specific extension of the ASCII character set.MAC-ICELAND,
   a platform specific extension of the ASCII character set.MAC-ROMAN
   ≡ MACINTOSH,
   a platform specific extension of the ASCII character set.MAC-ROMANIA,
   a platform specific extension of the ASCII character set.MAC-SYMBOL,
   a platform specific character set.MAC-THAI,
   a platform specific extension of the ASCII character set.MAC-TURKISH,
   a platform specific extension of the ASCII character set.MAC-UKRAINE,
   a platform specific extension of the ASCII character set.CP437, a DOS oldie,
   a platform specific extension of the ASCII character set.CP437-IBM,
   an IBM variant of CP437.
 CP737, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Greek language.
 CP775, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for some Baltic languages.
 CP850, a DOS oldie,
   a platform specific extension of the ASCII character set.CP852, a DOS oldie,
   a platform specific extension of the ASCII character set.CP852-IBM,
   an IBM variant of CP852.CP855, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Russian language.
 CP857, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Turkish language.
 CP860, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Portuguese language.
 CP860-IBM,
   an IBM variant of CP860.
 CP861, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Icelandic language.
 CP861-IBM,
   an IBM variant of CP861.
 CP862, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Hebrew language.
 CP862-IBM,
   an IBM variant of CP862.
 CP863, a DOS oldie,
   a platform specific extension of the ASCII character set.CP863-IBM,
   an IBM variant of CP863.
 CP864, a DOS oldie,
   meant to be suitable for the Arabic language.
 CP864-IBM,
   an IBM variant of CP864.
 CP865, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for some Nordic languages.
 CP865-IBM,
   an IBM variant of CP865.
 CP866, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Russian language.
 CP869, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Greek language.
 CP869-IBM,
   an IBM variant of CP869.
 CP874, a DOS oldie,
   a platform specific extension of the ASCII character set, meant to be suitable for the Thai language.
 CP874-IBM,
   an IBM variant of CP874.
 WINDOWS-1250
   ≡ CP1250,
   a platform specific extension of the ASCII character set, heavily incompatible with ISO-8859-2.
 WINDOWS-1251
   ≡ CP1251,
   a platform specific extension of the ASCII character set, heavily incompatible with ISO-8859-5,
   meant to be suitable for the Russian language.
 WINDOWS-1252
   ≡ CP1252,
   a platform specific extension of the ISO-8859-1 character set.
 WINDOWS-1253
   ≡ CP1253,
   a platform specific extension of the ASCII character set, gratuitously incompatible with ISO-8859-7,
   meant to be suitable for the Greek language.
 WINDOWS-1254
   ≡ CP1254,
   a platform specific extension of the ISO-8859-9 character set.
 WINDOWS-1255
   ≡ CP1255,
   a platform specific extension of the ASCII character set, gratuitously incompatible with ISO-8859-8,
   suitable for the Hebrew language.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.WINDOWS-1256
   ≡ CP1256,
   a platform specific extension of the ASCII character set, meant to be suitable for the Arabic language.
 WINDOWS-1257
   ≡ CP1257,
   a platform specific extension of the ASCII character set.WINDOWS-1258
   ≡ CP1258,
   a platform specific extension of the ASCII character set, meant to be suitable for the Vietnamese language.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.HP-ROMAN8,
   a platform specific extension of the ASCII character set.NEXTSTEP,
   a platform specific extension of the ASCII character set.EUC-JP,
   a multibyte character set for the Japanese language.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.SHIFT-JIS,
   a multibyte character set for the Japanese language.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.CP932,
   a Microsoft variant of SHIFT-JIS.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ISO-2022-JP,
   a stateful 7-bit multibyte character set for the Japanese language.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ISO-2022-JP-2,
   a stateful 7-bit multibyte character set for the Japanese language.
   This character set is only available on platforms with GNU libc 2.3
   or newer or GNU libiconv.ISO-2022-JP-1,
   a stateful 7-bit multibyte character set for the Japanese language.
   This character set is only available on
                           platforms with GNU libiconv.EUC-CN,
   a multibyte character set for simplified Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.HZ,
   a stateful 7-bit multibyte character set for simplified Chinese.
   This character set is only available on
                           platforms with GNU libiconv.GBK,
   a multibyte character set for Chinese,
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.CP936,
   a Microsoft variant of GBK.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.GB18030,
   a multibyte character set for Chinese,
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.EUC-TW,
   a multibyte character set for traditional Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.BIG5,
   a multibyte character set for traditional Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.CP950,
   a Microsoft variant of BIG5.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.BIG5-HKSCS,
   a multibyte character set for traditional Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ISO-2022-CN,
   a stateful 7-bit multibyte character set for Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ISO-2022-CN-EXT,
   a stateful 7-bit multibyte character set for Chinese.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.EUC-KR,
   a multibyte character set for Korean.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.CP949,
   a Microsoft variant of EUC-KR.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ISO-2022-KR,
   a stateful 7-bit multibyte character set for Korean.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.JOHAB,
   a multibyte character set for Korean used mostly on DOS.
   This character set is only available on
                                 platforms with GNU libc or GNU libiconv.ARMSCII-8,
   an extension of the ASCII character set, suitable for the Armenian. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.GEORGIAN-ACADEMY,
   an extension of the ASCII character set, suitable for the Georgian. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.GEORGIAN-PS,
   an extension of the ASCII character set, suitable for the Georgian. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.TIS-620,
   an extension of the ASCII character set, suitable for the Thai. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.MULELAO-1,
   an extension of the ASCII character set, suitable for the Laotian. This character set is only available on
                           platforms with GNU libiconv.CP1133,
   an extension of the ASCII character set, suitable for the Laotian. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.VISCII,
   an extension of the ASCII character set, suitable for the Vietnamese. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.TCVN,
   an extension of the ASCII character set, suitable for the Vietnamese. This character set is only available on
                                 platforms with GNU libc or GNU libiconv.BASE64, encodes
  arbitrary byte sequences with 64 ASCII characters 
   ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
  
 as specifined by MIME; 3 bytes are encoded with 4
  characters, line breaks are inserted after every 76 characters.
While this is not a traditional character set (i.e., it does
  not map a set of characters in a natural language into bytes), it
  does define a map between arbitrary byte sequences and certain
  character sequences, so it falls naturally into the EXT:ENCODING class.
The character sets provided by the library function
 iconv can also be used as encodings.  To create such an encoding,
 call EXT:MAKE-ENCODING with the character set name (a string) as the
 :CHARSET argument.
When an EXT:ENCODING is available both as a built-in and
 through iconv, the built-in is used, because it is more
 efficient and available across all platforms.
These encodings are not assigned to global variables, since
 there is no portable way to get the list of all character sets
 supported by iconv.
On standard-compliant UNIX systems (e.g., GNU systems, such as GNU/Linux and GNU/Hurd) and on systems with GNU libiconv you get this list by calling the program: iconv -l.
The reason we use only GNU libc 2.2 or GNU libiconv is
 that the other iconv implementations are broken in various ways and
 we do not want to deal with random CLISP crashes caused by those bugs.
 If your system supplies an iconv implementation which passes the
 GNU libiconv's test suite, please report that to <clisp-list@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-list) and a
 future CLISP version will use iconv on your system.
The line terminator mode can be one of the following three keywords:
Windows programs typically use the :DOS line terminator,
 sometimes they also accept :UNIX line terminators or produce
 :MAC line terminators.
The HTTP protocol also requires :DOS line terminators.
The line terminator mode is relevant only for output (writing to a
 file/pipe/socket STREAM).  During input, all three kinds of line terminators
 are recognized.  See also Section 13.8, “Treatment of Newline during Input and Output
   [CLHS-13.1.8]”.
EXT:MAKE-ENCODINGThe function (
 returns an EXT:MAKE-ENCODING &KEY :CHARSET
     :LINE-TERMINATOR :INPUT-ERROR-ACTION :OUTPUT-ERROR-ACTION)EXT:ENCODING. The :CHARSET argument may be
 an encoding, a string, or :DEFAULT.
 The possible values for the line terminator argument are the
 keywords :UNIX, :MAC, :DOS.
The :INPUT-ERROR-ACTION argument specifies
 what happens when an invalid byte sequence is encountered while
 converting bytes to characters.  Its value can be :ERROR, :IGNORE
 or a character to be used instead.  The UNICODE character
 #\uFFFD is typically used to indicate an error in the
 input sequence.
The :OUTPUT-ERROR-ACTION argument specifies
 what happens when an invalid character is encountered while converting
 characters to bytes.  Its value can be :ERROR, :IGNORE, a byte to
 be used instead, or a character to be used instead.  The UNICODE
 character #\uFFFD can be used here only if it is
 encodable in the character set.
EXT:ENCODING-CHARSETThe function ( returns the
 charset of the EXT:ENCODING-CHARSET encoding)encoding, as a SYMBOL or a STRING.
( is
  not necessarily a valid STRING (EXT:ENCODING-CHARSET encoding))MIME name.
Besides every file/pipe/socket STREAM containing an encoding,
 the following SYMBOL-MACRO places contain global EXT:ENCODINGs:
SYMBOL-MACRO CUSTOM:*DEFAULT-FILE-ENCODING*. The SYMBOL-MACRO place CUSTOM:*DEFAULT-FILE-ENCODING* is the encoding used for
 new file/pipe/socket STREAM, when no :EXTERNAL-FORMAT argument was specified.
The following are SYMBOL-MACRO places.
CUSTOM:*PATHNAME-ENCODING*
   CUSTOM:*TERMINAL-ENCODING*
   *TERMINAL-IO*.
 CUSTOM:*MISC-ENCODING*
   CUSTOM:*FOREIGN-ENCODING*
   The default encoding objects are initialized according to -Edomain encoding
You have to use EXT:LETF/EXT:LETF*
  for SYMBOL-MACROs; LET/LET* will not work!
The line terminator facet of the above EXT:ENCODINGs is determined by
 the following logic: since CLISP understands all possible
 line terminators on input (see
 Section 13.8, “Treatment of Newline during Input and Output
   [CLHS-13.1.8]”), all that matters is what line terminator
 do most other programs expect?
O_BINARY cpp
   constant is defined, we assume that the OS distinguishes between text
   and binary files, and, since the encodings are relevant only for text
   files, we thus use :DOS; otherwise the default is :UNIX.
:DOS.This boils down to the following code
 in src/encoding.d:
#if defined(WIN32) || (defined(UNIX) && (O_BINARY != 0))
Both of the above tests
  pass on Cygwin, so the default line terminator is :DOS.
  If you so desire, you can change it in your RC file.
Encodings can also be used to convert directly between strings and their corresponding byte vector representation according to that encoding.
(EXT:CONVERT-STRING-FROM-BYTES
      vector encoding &KEY :START :END)vector (a (VECTOR (UNSIGNED-BYTE 8)))
   from start to end to a STRING, according to the given
   encoding, and returns the resulting string.
(EXT:CONVERT-STRING-TO-BYTES
      string encoding &KEY :START :END)string from
   start to end to a (VECTOR (UNSIGNED-BYTE 8)), according to the given
   encoding, and returns the resulting byte vector.
This interface is CLISP-specific and now obsolete. Please use the Gray streams interface instead.
Generic streams are user programmable streams. The programmer interface:
(gstream:make-generic-stream
                 controller)(gstream:generic-stream-controller
                 stream)gstream:make-generic-stream.
  (gstream:generic-stream-p
                 stream)T if it is, NIL otherwise.
  In order to specify the behavior of a generic stream, the user
 must define CLOS methods on the following CLOS generic
 functions.  The function
 gstream:generic-stream-
 corresponds to the Common Lisp function
 xyzxyz
(gstream:generic-stream-read-char
                 controller)NIL at
    end of file.  Takes one argument, the controller object.
  (gstream:generic-stream-peek-char
                 controller)NIL at end of file.  A
   second value indicates whether the side effects associated with
   consuming the character were executed: T means that a full
   READ-CHAR was done, NIL means that no side effects were done.
   Takes one argument, the controller object.
  (gstream:generic-stream-read-byte
                 controller)NIL at end
   of file.  Takes one argument, the controller object.
  (gstream:generic-stream-read-char-will-hang-p
     controller)NIL if
   gstream:generic-stream-read-char and
   gstream:generic-stream-peek-char will certainly
   return immediately.  Otherwise it returns true.
  (gstream:generic-stream-write-char
                 controller char)(gstream:generic-stream-write-byte
                 controller
                 by)(gstream:generic-stream-write-string
                 controller
                 string start length)string starting from
   start of length length.
   The first argument is the controller object.
  (gstream:generic-stream-clear-input
                 controller)(gstream:generic-stream-clear-output
     controller)(gstream:generic-stream-finish-output
     controller)(gstream:generic-stream-force-output
     controller)(gstream:generic-stream-close
     controller)Recall two terms: An object is called “"alive"” as
 long as it can be retrieved by the user or program, through any kind of
 references, starting from global and local variables. (Objects that
 consume no heap storage, also known as “"immediate
 objects"”, such as CHARACTERs, FIXNUMs, and
 SHORT-FLOATs, are alive indefinitely.) An object is said to be
 garbage-collected when its storage is reclaimed, at some moment after it becomes
 “"dead"”.
A EXT:WEAK-POINTER is an object holding a reference to a given object,
 without keeping the latter from being garbage-collected.
Weak Pointer API
(EXT:MAKE-WEAK-POINTER
   value)EXT:WEAK-POINTER referring to
   value.(EXT:WEAK-POINTER-P object)object is of type
   EXT:WEAK-POINTER.(EXT:WEAK-POINTER-VALUE
   weak-pointer)T,
   if the value has not yet been garbage-collected, else NIL and NIL.
   It is SETF-able: you can change the value that the weak pointer
   points to.Weak pointers are useful for notification-based communication
 protocols between software modules, e.g. when a change to an object
 x requires a notification to an object y, as long as y is
 alive.
A EXT:WEAK-LIST is an ordered collection of references to objects
 that does not keep the objects from being garbage-collected. It is
 semantically equivalent to a list of EXT:WEAK-POINTERs, however with a
 more efficient in-memory representation than a plain list of
 EXT:WEAK-POINTERs would be.
Weak List API
(EXT:MAKE-WEAK-LIST list)EXT:WEAK-LIST pointing to each of the
   elements in the given list.(EXT:WEAK-LIST-P object)object is of type
   EXT:WEAK-LIST.(EXT:WEAK-LIST-LIST
   weak-list)LIST of those objects from the
   weak-list that are still
   alive.(SETF (EXT:WEAK-LIST-LIST
   weak-list) list)weak-list.Weak lists are useful for notification based communication
 protocols between software modules, e.g. when a change to an object
 x requires a notification to objects k1, k2, ..., as long
 as such a particular kn is alive.
A EXT:WEAK-LIST with a single element is semantically equivalent to a
 single EXT:WEAK-POINTER.
A weak “and” relation is an ordered collection of references to objects, that does not keep the objects from being garbage-collected, and which allows access to all the objects as long as all of them are still alive. As soon as one of them is garbage-collected, the entire collection of objects becomes empty.
Weak “And” Relation API
(EXT:MAKE-WEAK-AND-RELATION
   list)EXT:WEAK-AND-RELATION between the objects in
   the given list.(EXT:WEAK-AND-RELATION-P
   object)object is of type
   EXT:WEAK-AND-RELATION.(EXT:WEAK-AND-RELATION-LIST
   weak-and-relation)weak-and-relation. The returned list must not
   be destructively modified.EXT:WEAK-AND-RELATIONs are useful to model relations between objects
 that become worthless when one of the objects dies.
A EXT:WEAK-AND-RELATION with a single element is semantically
 equivalent to a EXT:WEAK-POINTER.
A weak “or” relation is an ordered collection of references to objects, that keeps all objects from being garbage-collected as long as one of them is still alive. In other words, each of them keeps all others among them from being garbage-collected. When all of them are unreferenced, the collection of objects becomes empty.
Weak “Or” Relation API
(EXT:MAKE-WEAK-OR-RELATION
   list)EXT:WEAK-OR-RELATION between the objects in
   the given list.(EXT:WEAK-OR-RELATION-P
   object)object is of type
   EXT:WEAK-OR-RELATION.(EXT:WEAK-OR-RELATION-LIST
   weak-or-relation)weak-or-relation. The returned list must not
   be destructively modified.EXT:WEAK-OR-RELATIONs are useful to model relations between objects
 that do not become worthless when one of the objects dies.
A EXT:WEAK-OR-RELATION with a single element is semantically
 equivalent to a EXT:WEAK-POINTER.
A weak association is a mapping from an object called key to
 an object called value, that exists as long as the key is alive. In
 other words, as long as the key is alive, it keeps the value from being
 garbage-collected.
Weak Association API
(EXT:MAKE-WEAK-MAPPING
   key value)EXT:WEAK-MAPPING.
(EXT:WEAK-MAPPING-P
   object)EXT:WEAK-MAPPING.(EXT:WEAK-MAPPING-PAIR
   weak-mapping)T, if the key has not yet been garbage-collected, else NIL, NIL,
   NIL.(EXT:WEAK-MAPPING-VALUE
   weak-mapping)NIL.(SETF (EXT:WEAK-MAPPING-VALUE
   weak-mapping) value)weak-mapping. It has no effect when the
   key has already been garbage-collected.Weak associations are useful to supplement objects with additional information that is stored outside of the object.
A weak “and” mapping is a mapping from a tuple of
 objects called keys to an object called value, that does
 not keep the keys from being garbage-collected and that exists as long as all
 keys are alive. As soon as one of the keys is garbage-collected, the entire
 mapping goes away.
Weak “And” Mapping API
(EXT:MAKE-WEAK-AND-MAPPING
   keys value)EXT:WEAK-AND-MAPPING between the keys
   objects in the given list and the given value.
   The keys list must be non-empty.(EXT:WEAK-AND-MAPPING-P
   object)object is of type
   EXT:WEAK-AND-MAPPING.(EXT:WEAK-AND-MAPPING-PAIR
   weak-and-mapping)T, if none of the keys have been garbage-collected, else NIL, NIL, NIL.
   The returned keys list must not be destructively modified.
(EXT:WEAK-AND-MAPPING-VALUE
   weak-and-mapping)NIL.(SETF
   (EXT:WEAK-AND-MAPPING-VALUE
   weak-and-mapping) value)weak-and-mapping. It has no effect when
   some key has already been garbage-collected.EXT:WEAK-AND-MAPPINGs are useful to model properties of sets of
 objects that become worthless when one of the objects dies.
A EXT:WEAK-AND-MAPPING with a single key is semantically equivalent
 to a weak association.
A weak “or” mapping is a mapping from a tuple of
 objects called keys to an object called value, that keeps all
 keys and the value from being garbage-collected as long as one of the keys is
 still alive. In other words, each of the keys keeps all others among
 them and the value from being garbage-collected.  When all of them are
 unreferenced, the entire mapping goes away.
Weak “Or” Mapping API
(EXT:MAKE-WEAK-OR-MAPPING
   keys value)EXT:WEAK-OR-MAPPING between the
   keys objects in the given list and the given
   value. The keys list must be
   non-empty.(EXT:WEAK-OR-MAPPING-P
   object)object is of type
   EXT:WEAK-OR-MAPPING.(EXT:WEAK-OR-MAPPING-PAIR
   weak-or-mapping)T, if the keys have not yet been garbage-collected, else NIL, NIL, NIL.
   The returned keys list must not be destructively modified.
(EXT:WEAK-OR-MAPPING-VALUE
   weak-or-mapping)NIL.(SETF (EXT:WEAK-OR-MAPPING-VALUE
   weak-or-mapping) value)weak-or-mapping. It has no effect when the
   keys have already been garbage-collected.EXT:WEAK-OR-MAPPINGs are useful to model properties of sets of
 objects that do not become worthless when one of the objects dies.
A EXT:WEAK-OR-MAPPING with a single key is semantically equivalent
 to a weak association.
A weak association list is an ordered collection of pairs, each
 pair being built from an object called key and an object called
 value.  The lifetime of each pair depends on the type of the weak
 association list:
:KEYkey is not garbage-collected.
    As long as the key is alive, it prevents the value from
    being garbage-collected.:VALUEvalue is not garbage-collected.
   As long as the value is alive, it prevents the key from
   being garbage-collected.:KEY-AND-VALUEkey and the value
   are alive.
 :KEY-OR-VALUEkey or the value
   are alive.  As long as the key is alive, it prevents the value
   from being garbage-collected, and as long as the value is alive, it prevents the
   key from being garbage-collected.In other words, each pair is:
:KEYEXT:WEAK-MAPPING from the key to the value,
 :VALUEEXT:WEAK-MAPPING from the value to the key,
 :KEY-AND-VALUEEXT:WEAK-AND-RELATION of the key and the value,
 :KEY-OR-VALUEEXT:WEAK-OR-RELATION of the key and the value.
 Weak Association List API
(EXT:MAKE-WEAK-ALIST
   :type :initial-contents)EXT:WEAK-ALIST. The type argument
   must be one of the four aforementioned types; the default is :KEY.
   The initial-contents argument must be an
   association list.(EXT:WEAK-ALIST-P object)object is of type
   EXT:WEAK-ALIST.(EXT:WEAK-ALIST-TYPE
   weak-alist)weak-alist.(EXT:WEAK-ALIST-CONTENTS
   weak-alist)weak-alist.
(SETF (EXT:WEAK-ALIST-CONTENTS
   weak-alist)
   contents)weak-alist. The
   contents argument must be an
   association list.(EXT:WEAK-ALIST-ASSOC item
   weak-alist
   [:test] [:test-not] [:key])(ASSOC item (EXT:WEAK-ALIST-CONTENTS
    weak-alist)
    [:test] [:test-not] [:key]).
(EXT:WEAK-ALIST-RASSOC item
   weak-alist
   [:test] [:test-not] [:key])(RASSOC item (EXT:WEAK-ALIST-CONTENTS
    weak-alist)
    [:test] [:test-not] [:key]).
(EXT:WEAK-ALIST-VALUE item
   weak-alist [:test] [:test-not])(CDR (EXT:WEAK-LIST-ASSOC
    item weak-alist
    [:test] [:test-not])).
(SETF (EXT:WEAK-ALIST-VALUE
   item weak-alist [:test] [:test-not])
   value)item in
   a weak-alist.  When a pair with the given
   item as key does not exist or has already been garbage-collected, a new pair
   is added to the association list.Weak associations lists are useful to supplement objects with additional information that is stored outside of the object, when the number of such objects is known to be small.
A weak HASH-TABLE is an unordered collection of pairs, each
 pair being built from an object called key and an object called
 value. There can be only one pair with a given key in a weak
 HASH-TABLE. The lifetime of each pair depends on the type of the
 weak HASH-TABLE
:KEYkey is not garbage-collected.
    As long as the key is alive, it prevents the value from
    being garbage-collected.:VALUEvalue is not garbage-collected.
     As long as the value is alive, it prevents the key from
     being garbage-collected.:KEY-AND-VALUEkey and the
     value are alive.:KEY-OR-VALUEkey or the
     value are alive.  As long as the key is alive, it prevents
     the key from being garbage-collected, and as long as the value is
     alive, it prevents the key from being garbage-collected.
  In other words, each pair is:
:KEYEXT:WEAK-MAPPING from the key to the value,
 :VALUEEXT:WEAK-MAPPING from the value to the key,
 :KEY-AND-VALUEEXT:WEAK-AND-RELATION of the key and the value,
 :KEY-OR-VALUEEXT:WEAK-OR-RELATION of the key and the value.
See also Section 18.1.1, “Function MAKE-HASH-TABLE”.
Weak HASH-TABLEs are useful to supplement objects with
 additional information that is stored outside of the object. This data
 structure scales up without performance degradation when the number of
 pairs is big.
Weak HASH-TABLEs are also useful to implement canonicalization
 tables.
Calling (
 has the effect that when the specified object is being garbage-collected,
 EXT:FINALIZE object function)( will be executed.FUNCALL function object)
Calling (
 has a similar effect, but only as long as the
 EXT:FINALIZE object function
  guardian)guardian has not been garbage-collected:
 when object is being garbage-collected, ( will be executed.
 If the FUNCALL function
 object guardian)guardian is garbage-collected before object
 is, nothing happens.
The time when “the object is being garbage-collected” is
  not defined deterministically.  (Actually, it might possibly never
  occur.)  It denotes a moment at which no references to object
  exist from other Lisp objects.  When the function is called,
  object (and possibly guardian) enter
  the “arena of live Lisp objects” again.
No finalization request will be executed more than once.
CLISP prompt consists of 3 mandatory parts: “start”,
 “body”, and “finish”; and 2 optional parts:
 “break”, which appears only during
 debugging (after BREAK or ERROR),
 and “step”, which appears only during STEPping.
 Each part is controlled by a custom variable, which can be either a
 STRING or a FUNCTION of no arguments returning a STRING
 (if it is something else - or if the return value was not a STRING
 - it is printed with PRINC).  In the order of invocation:
 
CUSTOM:*PROMPT-START*CUSTOM:*PROMPT-STEP*STEPping.
     Defaults to “Step n ”,
     where n is the stepping level as returned by EXT:STEP-LEVEL.
  CUSTOM:*PROMPT-BREAK*Break n ”,
     where n is the break level as returned by EXT:BREAK-LEVEL.
  CUSTOM:*PROMPT-BODY*package[n]”
     where package is the shortest (nick)name (as returned by
     EXT:PACKAGE-SHORTEST-NAME) of the current package *PACKAGE*
     if it is not the same as it was in the beginning
     (determined by EXT:PROMPT-NEW-PACKAGE)
     or if it does not contain symbol T,
     (it is assumed that in the latter case you would want to keep in
     mind that your current package is something weird);
     and n is the index of the current prompt, kept in EXT:*COMMAND-INDEX*;
  CUSTOM:*PROMPT-FINISH*> ”.
To facilitate your own custom prompt creation, the following functions and variables are available:
EXT:BREAK-LEVELFUNCTION returns current BREAK/ERROR level.
  EXT:STEP-LEVELFUNCTION returns current STEP level.
  EXT:PROMPT-NEW-PACKAGEFUNCTION returns *PACKAGE* or NIL
     if the current package is the same as it was initially.
  EXT:PACKAGE-SHORTEST-NAMEFUNCTION takes one argument, a
     PACKAGE, and returns its shortest name or nickname.
  EXT:*COMMAND-INDEX*Some [ANSI CL standard] features are turned off by default for convenience and
 for backwards compatibility.
 They can be switched on, all at once, by setting the SYMBOL-MACRO
 CUSTOM:*ANSI* to T, or they can be switched on individually.
 Setting CUSTOM:*ANSI* to T implies the following:
CUSTOM:*PRINT-PATHNAMES-ANSI* to T.CUSTOM:*PRINT-SPACE-CHAR-ANSI* to T.CUSTOM:*COERCE-FIXNUM-CHAR-ANSI* to T.CUSTOM:*SEQUENCE-COUNT-ANSI* to T.CUSTOM:*MERGE-PATHNAMES-ANSI* to T.CUSTOM:*PARSE-NAMESTRING-ANSI* to T.CUSTOM:*FLOATING-POINT-CONTAGION-ANSI* to T.CUSTOM:*FLOATING-POINT-RATIONAL-CONTAGION-ANSI* to T.CUSTOM:*PHASE-ANSI* to T.CUSTOM:*LOOP-ANSI* to T.CUSTOM:*PRINT-EMPTY-ARRAYS-ANSI* to T.CUSTOM:*PRINT-UNREADABLE-ANSI* to T.CUSTOM:*DEFUN-ACCEPT-SPECIALIZED-LAMBDA-LIST* to NILIf you run CLISP with the -ansi switch or set
 the SYMBOL-MACRO CUSTOM:*ANSI* to T and then save memory image,
 then all subsequent invocations of CLISP with this image
 will be as if with -ansi
 (regardless whether you actually supply the -ansi switch).
 You can always set the SYMBOL-MACRO CUSTOM:*ANSI* to NIL, or invoke
 CLISP with the -traditional switch, reversing the above
 settings, i.e.,
CUSTOM:*PRINT-PATHNAMES-ANSI* to NIL.CUSTOM:*PRINT-SPACE-CHAR-ANSI* to NIL.CUSTOM:*COERCE-FIXNUM-CHAR-ANSI* to NIL.CUSTOM:*SEQUENCE-COUNT-ANSI* to NIL.CUSTOM:*MERGE-PATHNAMES-ANSI* to NIL.CUSTOM:*PARSE-NAMESTRING-ANSI* to NIL.CUSTOM:*FLOATING-POINT-CONTAGION-ANSI* to NIL.CUSTOM:*FLOATING-POINT-RATIONAL-CONTAGION-ANSI* to NIL.CUSTOM:*PHASE-ANSI* to NIL.CUSTOM:*LOOP-ANSI* to NIL.CUSTOM:*PRINT-EMPTY-ARRAYS-ANSI* to NIL.CUSTOM:*PRINT-UNREADABLE-ANSI* to NIL.CUSTOM:*DEFUN-ACCEPT-SPECIALIZED-LAMBDA-LIST* to TEXT:ETHEEXT:LETF & EXT:LETF*EXT:OPEN-HTTP and
  macro EXT:WITH-HTTP-INPUTEXT:BROWSE-URLCUSTOM:*HTTP-PROXY*CLISP comes with some extension macros, mostly defined in the
 file macros3.lisp and loaded from the file init.lisp during
 make:
EXT:ETHE(
 enforces a type check in both interpreted and compiled code.
EXT:ETHE value-type form)
These macros are similar to LET and LET*, respectively,
 except that they can bind places, even places with multiple values.
 Example:
(letf (((values a b) form)) ...)
is equivalent to
(multiple-value-bind (a b) form ...)
while
(letf (((first l) 7)) ...)
is approximately equivalent to
(LET*((#:g1 l) (#:g2 (first #:g1))) (UNWIND-PROTECT(PROGN(SETF(first #:g1) 7) ...) (SETF(first #:g1) #:g2)))
(
 memoizes the primary value of EXT:MEMOIZED form)form from its first evaluation.
Similar to the LOOP's
 collect
 construct, except that it is looks more "Lispy" and can appear
 arbitrarily deep.  It defines local macros (with MACROLET) which
 collect objects given to it into lists, which are then returned as
 multiple values.  E.g., 
(ext:with-collect (c0 c1) (dotimes (i 10) (if (oddp i) (c0 i) (c1 i)))) ⇒(1 3 5 7 9); ⇒(0 2 4 6 8)
 returns two LISTs (1 3 5 7 9)
and (0 2 4 6 8) as multiple values.
Similar to its namesake from Paul Graham's book “On Lisp”, this macro is useful for writing other macros:
(with-gensyms ("FOO-" bar baz zot) ...)
expands to
(let ((bar (gensym "FOO-BAR-"))
      (baz (gensym "FOO-BAZ-"))
      (zot (gensym "FOO-ZOT-")))
  ...)
Similar to REMOVE and REMF, this function removes some
 properties from a property list.  It is non-destructive and thus can be
 used on &REST arguments to remove some keyword parameters, e.g.,
(defmacro with-foo ((&KEYfoo1 foo2)&BODYbody) `(... ,foo1 ... ,foo2 ... ,@body)) (defmacro with-foo-bar ((&RESTopts&KEYbar1 bar2&ALLOW-OTHER-KEYS)&BODYbody) `(with-foo (,@(remove-plist opts :bar1 :bar2) ... ,bar1 ... ,bar2 ... ,@body))) (defun foo-bar () (with-foo-bar (:bar1 1 :foo2 2) ...))
here WITH-FOO does not receive the
:BAR1 1 argument from FOO-BAR.
Defined in inspect.lisp, these macros are useful
 for the rudimentary HTTP server defined there.
EXT:OPEN-HTTP and
  macro EXT:WITH-HTTP-INPUTDefined in
 clhs.lisp,
 they allow downloading data over the Internet using the HTTP protocol.
 ( opens
 a socket connection to the EXT:OPEN-HTTP url &KEY :IF-DOES-NOT-EXIST)url host,
 sends the GET request,
 and returns two values: the SOCKET:SOCKET-STREAM and content length.
(EXT:WITH-HTTP-INPUT ( binds variable url) &BODY body)variable
to the SOCKET:SOCKET-STREAM returned by EXT:OPEN-HTTP and executes the body.
(EXT:WITH-HTTP-INPUT ((
additionally binds variable contents) url) &BODY body)contents to the content length.
EXT:OPEN-HTTP will check CUSTOM:*HTTP-PROXY* on startup and parse the environment variable
 HTTP_PROXY if CUSTOM:*HTTP-PROXY* is NIL.
EXT:BROWSE-URLFunction (
  calls a browser on the URL. EXT:BROWSE-URL url &KEY :BROWSER :OUT)browser
  (defaults to CUSTOM:*BROWSER*) should be a valid keyword in the CUSTOM:*BROWSERS* association list.
  :OUT specifies the stream where the progress messages are printed
  (defaults to *STANDARD-OUTPUT*).
CUSTOM:*HTTP-PROXY*If you are behind a proxy server, you will need to set CUSTOM:*HTTP-PROXY* to
 a LIST (name:password host port).
 By default, the environment variable http_proxy is used, the
 expected format is "name:password@host:port".
 If no #\@ is present,
 name and password are NIL.
 If no #\: is present,
 password (or port) are NIL.
Use function (EXT:HTTP-PROXY  to reset &OPTIONAL (STRING
  (EXT:GETENV "http_proxy")))CUSTOM:*HTTP-PROXY*.
The user-customizable variables and functions are located in the
 package “CUSTOM” and thus can be listed using
 (:
 APROPOS "" "CUSTOM")
Some of these variables are platform-specific.
You should set these variables (and do whatever other
 customization you see fit) in the file config.lisp in the build
 directory before building CLISP.
 Alternatively, after building CLISP, or if you are using a binary
 distribution of CLISP, you can modify config.lisp, compile and load
 it, and then save the memory image.
 Finally, you can create an RC file which is loaded whenever CLISP
 is started.
You can use function EXT:EXPAND-FORM to expand all the macros,
 SYMBOL-MACROs, etc, in a single form:
(EXT:EXPAND-FORM'(macrolet ((bar (x) `(print ,x))) (macrolet ((baz (x) `(bar ,x))) (symbol-macrolet ((z 3)) (baz z))))) ⇒(locally (print 3)); the expansion ⇒; indicator: some expansion has actually been doneT
This is sometimes called a “code walker”,
 except that a code walker would probably leave the MACROLET and
 SYMBOL-MACROLET forms intact and just do the expansion.
Function EXT:EXPAND-FORM is the exported part of the
  CLISP interpreter (AKA EVAL), so it expands forms by assuming the
  EVAL-WHEN situation :EXECUTE and is therefore
  unsuitable for forms that may later be passed to the compiler:
(EXT:EXPAND-FORM'(EVAL-WHEN(:COMPILE-TOPLEVEL) (foo))) ⇒; ⇒NIL(TEXT:EXPAND-FORM'(EVAL-WHEN(:LOAD-TOPLEVEL) (foo))) ⇒; ⇒NILT
Table of Contents
(SCREEN:MAKE-WINDOW)*TERMINAL-IO* should not be used for input or output during this
    time.  (Use EXT:WITH-KEYBOARD and EXT:*KEYBOARD-INPUT* instead.)
  (SCREEN:WITH-WINDOW .
    body)SCREEN:*WINDOW*
    to a WINDOW-STREAM and executes body.
    The stream is guaranteed to be closed when the body is left.
    During its execution, *TERMINAL-IO* should not be used, as above.
  (SCREEN:WINDOW-SIZE
    window-stream)(SCREEN:WINDOW-CURSOR-POSITION
    window-stream)(SCREEN:SET-WINDOW-CURSOR-POSITION
    window-stream line column)(SCREEN:CLEAR-WINDOW
    window-stream)(SCREEN:CLEAR-WINDOW-TO-EOT
    window-stream)(SCREEN:CLEAR-WINDOW-TO-EOL
    window-stream)(SCREEN:DELETE-WINDOW-LINE
    window-stream)(SCREEN:INSERT-WINDOW-LINE
    window-stream)(SCREEN:HIGHLIGHT-ON
    window-stream)(SCREEN:HIGHLIGHT-OFF
    window-stream)(SCREEN:WINDOW-CURSOR-ON
    window-stream)(SCREEN:WINDOW-CURSOR-OFF
    window-stream)Everything described in the section will work verbatim on Win32
  when using Cygwin or MinGW, except for one
  thing - you will need to replace the run
  extension in lisp.run with the Win32 executable
  extension exe.
For historical reasons, all examples appear to assume UNIX and
  use the run file type (“extension”)
  for the CLISP run-time.
  This does not mean that they will not work on Win32.
CLISP has a facility for adding external modules (written in C, for example). It is invoked through clisp-link.
A module is a
 piece of external code which defines extra Lisp objects, symbols and
 functions.  A module name must consist of the
 characters A-Z,
 a-z, _,
 0-9.
 The module name “clisp” is reserved.
 Normally a module name is derived from the corresponding file name.
clisp-link needs a directory containing:
"modules.c""clisp.h"
clisp-link expects to find these files in a
subdirectory linkkit/ of the current directory.
This can be overridden by the environment variable CLISP_LINKKIT.
clisp-link operates on CLISP linking sets and on module sets.
A linking set is a directory containing:
makevarssome /bin/sh commands, setting the variables
| 
 | the C compiler | 
| 
 | flags for the C compiler, when preprocessing or compiling | 
| 
 | flags for the C compiler, when compiling or linking | 
| 
 | flags for the C compiler, when linking | 
| 
 | libraries to use when linking (either present in the linking set directory, or system-wide) | 
| 
 | additional X Window System libraries to use | 
| 
 | the ranlib command | 
| 
 | the list of files needed when linking | 
modules.hmodules.oFILESmakevars
lisp.runlispinit.memTo run a CLISP contained in some linking set directory, call
$directory/lisp.run-Mdirectory/lispinit.mem
or
$clisp-Kdirectory
 (recommended, since it also passes
 -B
 to the run-time).
A module set is a directory containing:
NEW_FILES,
  NEW_LIBS, NEW_MODULES, TO_LOAD
  and optionally TO_PRELOADIn link.sh the module set directory is referred to
 as $modulename/.
The following variables should be defined in link.sh.
NEW_FILESNEW_LIBSlisp.run belonging to a new linking set.
 NEW_MODULES#P".c" file in the
  module set defines a module of its own.  The module name is derived
  from the file name.TO_LOADlispinit.mem belonging to a new linking set.
 TO_PRELOAD (optional)the space-separated list of Lisp files to load
   into an intermediate lispinit.mem file, before building the lispinit.mem
   belonging to a new linking set.
   This variable is usually used to create
   (or unlock) the Lisp PACKAGEs which
   must be present when the new #P".c" files are initialized.
   E.g., the FFI:DEF-CALL-IN functions must reside in already defined packages;
   see Example 32.6, “Calling Lisp from C”.  You can find a live example in
   modules/syscalls/preload.lisp
   and modules/syscalls/link.sh.in.
  
If you are unlocking a package, you must also
    DELETE it from CUSTOM:*SYSTEM-PACKAGE-LIST* (see Section 31.2, “Saving an Image”) here
    and re-add it to CUSTOM:*SYSTEM-PACKAGE-LIST* in one of the TO_LOAD files.
    See, e.g., modules/i18n/preload.lisp
    and modules/i18n/link.sh.in.
The command
$clisp-link create-module-setmodulefile1.c...
 creates a module set in module directory which refers
 (via symbolic links) to file1.c etc.
 The files are expected to be modules of their own.
The command
$clisp-link add-module-setmodulesourcedestination
 combines a linking set in directory source and a
 module in directory module to a new linking set, in the directory
 destination which is newly created.
The command
$clisp-link runsourcemodule...
 runs the linking set in directory source, with the module
 in directory module loaded. More than one module can be specified.
 If CLISP has been built with the configuration option --with-dynamic-modules,
 the loading will be performed dynamically.
 Otherwise - this is much slower - a temporary linking set will be created
 and deleted afterwards.
Each module has two initialization functions:
module__name__init_function_1
    (struct module_t* module)called only once when CLISP
  discovers while loading a memory image that there is a module present
  in the executable (lisp.run) which was not present at the time the
  image was saved.  It can be used to create Lisp objects,
  e.g. functions or keywords, and is indeed used for that purpose by
  modprep.
You do not have to define this function yourself; modprep and “FFI” will do that for you.
If you use “FFI”, (
  will add code to this function.FFI:C-LINES :init-once ...)
The PACKAGEs must already exist and be unlocked,
   cf. TO_PRELOAD.
If you are using modprep and defining your
   own “init-once” function, it must call the
   module__
   function!name__init_function_1__modprep
module__name__init_function_2
  (struct module_t* module)called every time CLISP starts.
  It can be used to bind names to foreign addresses, since the address
  will be different in each invocation of CLISP, and is indeed used
  for that purpose by “FFI” (e.g., by FFI:DEF-CALL-OUT).
  It can also be used to set parameters of the libraries to which the
  module interfaces, e.g., the pcre module
  sets pcre_malloc and pcre_free.
 
You do not have to define this function yourself; modprep and “FFI” will do that for you.
If you use “FFI”, (
  will add code to this function.FFI:C-LINES :init-always ...)
name is the module name.
See also Section 31.1, “Customizing CLISP Process Initialization and Termination”.
Each module has a finalization function
module__name__fini_function
   (struct module_t* module)called before exiting CLISP.
You do not have to define this function yourself; modprep and “FFI” will do that for you.
If you use “FFI”, ( will
  add code to this function.FFI:C-LINES :fini ...)
name is the module name.
See also Section 31.1, “Customizing CLISP Process Initialization and Termination”.
EXT:MODULE-INFOFunction ( allows one to inquire
 about what modules are available in the currently running image.
 When called without arguments, it returns the list of module names,
 starting with “clisp”.  When EXT:MODULE-INFO &OPTIONAL name
  verbose)name is supplied and
 names a module, 3 values are returned - name,
 subr-count,
 object-count.
 When verbose is non-NIL, the full list of
 module lisp function names written in C (Subrs) and
 the full list of internal lisp objects available in C code
 are additionally returned for the total of 5 values.
When name is :FFI, returns the list of
 shared libraries opened using :LIBRARY.
 When verbose is non-NIL, return the
 association list of DLL names and all foreign objects associated with it.
SYS::DYNLOAD-MODULES--with-dynamic-modules.Dynamic loading does not work on all operating systems
  (dlopen or equivalent is required).
--with-dynamic-modules precludes some optimizations which
  are enabled by default.
Function (
 loads a shared object file or library containing a number of named
 external CLISP modules.
 SYS::DYNLOAD-MODULES filename ({name}+))
This facility cannot be used to
   access arbitrary shared libraries.  To do that, use the :LIBRARY
   argument to FFI:DEF-CALL-OUT and FFI:DEF-C-VAR instead.
External modules for CLISP are shared objects
 (dynamic libraries) that contain the
 module__ variable, among others.
 This serves to register external functions which operate on Lisp-level
 structures with CLISP.name__subr_tab
To use dlopen with modules,
 you should add -fPIC to the module's compilation options.
 Something like cc -shared -o name.so name.o
 may be needed to produce the shared object file.
To link in the “FFI” bindings for the GNU/Linux operating system, the following steps are needed. (Step 1 and step 2 need not be executed in this order.)
Create a new module set
$clisp-link create-module-set linux /somewhere/bindings/linux.c
Modify the newly created
  linux/link.sh
add -lm to the libraries
replace
NEW_LIBS="$file_list"
with
NEW_LIBS="$file_list -lm"
load linux.fas before saving the
    memory image
replace
TO_LOAD=''
with
TO_LOAD='/somewhere/bindings/linux.fas'Compile linux.lisp, creating
  linux.c
$clisp -c /somewhere/bindings/linux.lisp
Create a new linking set
$ clisp-link add-module-set linux base base+linuxRun and try it
$ base+linux/lisp.run -M base+linux/lispinit.mem -x '(linux:stat "/tmp")'There are some tools to facilitate easy module writing.
If your module is written in C, you can pre-process your
 sources with modprep in the CLISP distribution and define lisp
 functions with the DEFUN macro:
 
DEFUN(MY-PACKAGE:MY-FUNCTION-NAME, arg1 arg2 &KEY FOO BAR) {
  if (!boundp(STACK_0)) STACK_0 = fixnum(0); /* BAR */
  if (!boundp(STACK_1)) STACK_1 = fixnum(1); /* FOO */
  pushSTACK(`MY-PACKAGE::SOME-SYMBOL`); /* create a symbol in the package */
  pushSTACK(`#(:THIS :IS :A :VECTOR)`); /* some vector, created once */
  pushSTACK(``MY-PACKAGE::MY-FUNCTION-NAME``); /* double `` means FUNCTION */
  VALUES1(listof(7)); /* cons up a new list and clean up the STACK */
}
Then (MY-PACKAGE:MY-FUNCTION-NAME 'A 12 :FOO T) will
 return (A 12 T 0 MY-PACKAGE::SOME-SYMBOL #(:THIS
  :IS :A :VECTOR) #<ADD-ON-SYSTEM-FUNCTION
  MY-PACKAGE:MY-FUNCTION-NAME>)
(assuming you EXPORTed MY-FUNCTION-NAME from
 “MY-PACKAGE”).
Another useful macros are:
See modules/syscalls/calls.c
 and other included modules for more examples and file modprep for full
 documentation.
If you manipulate Lisp objects, you need to watch out for GC-safety.
If your module is written in C, you will probably want
 to #include "clisp.h" to access CLISP objects.
 You will certainly need to read "clisp.h" and some code in
 included modules, but here are
 some important hints that you will need to keep in mind:
allocate_*() functions) - but not C
   allocations (malloc et al) -
   and must be saved on the STACK using cpp macros
   pushSTACK(), popSTACK()
   and skipSTACK().TheFoo() macro, e.g.,
   TheCons(my_cons)->Car, but first check the
   type with consp().STACK, as illustrated
   in the above example.begin_system_call()/end_system_call()
   pairs.  These macros, defined in "clisp.h", save and restore
   registers used by CLISP which could be clobbered by a system call.
 
If your module uses “FFI” to interface to a C library,
 you might want to make your module package
 case-sensitive and use
 exporting.lisp in the CLISP distribution to make “FFI” forms
 and DEFUN, DEFMACRO at al export the symbols they define.
 See modules/netica/,
 modules/matlab/ and
 modules/bindings/ for examples.
When deciding how to write a module: whether to use “FFI” or to stick with C and modprep, one has to take into account several issues:
“FFI” has a noticeable overhead:
   compare RAWSOCK:HTONS (defined
   in modules/rawsock/rawsock.c)
   with 
(FFI:DEF-CALL-OUT htons (:name "htons") (:library :default)
  (:arguments (s ffi:short)) (:return-type ffi:short) (:language :stdc))
 and observe that RAWSOCK:HTONS is
   almost 3 times as fast (this really does compare the “FFI”
   overhead to the normal lisp function call because
   htons is computationally trivial).
   This difference will matter only if you call a simple function very
   many times, in which case it would make sense to put the loop itself
   into C.
First of all, “FFI” is not as widely ported as CLISP, so it is possible that you will face a platform where CLISP runs but “FFI” is not present.
Second, it is much easier to handle portability in C:
   observe the alternative implementations
   of htonl et al in
   modules/rawsock/rawsock.c.
Third, certain C structures have different layout on different platforms, and functions may take 64-bit arguments on some platforms and 32-bit arguments on others; so the “FFI” code has to track those differences, while C will mostly take care of these things for you.
:LIBRARY argument to FFI:DEF-CALL-OUT and
   FFI:DEF-C-VAR, you do not need to leave your CLISP session to try
   out your code.  This is a huge advantage for rapid prototyping.
&OPTIONAL and
   &KEYword arguments etc), you will need to write wrappers to your
   FFI:FOREIGN-FUNCTIONs, while in C you can do that directly.
   The same goes for “polymorphism”: accepting different
   argument types (like, e.g., POSIX:RESOLVE-HOST-IPADDR does) would require a lisp
   wrapper for FFI:FOREIGN-FUNCTIONs.
If you are comfortable with C, you might find the CLISP C module facilities (e.g., modprep) very easy to use.
CLISP “FFI”, on the other hand, is quite high-level, so, if you are more comfortable with high-level languages, you might find it easier to write “FFI” forms than C code.
FFI:DEF-CALL-OUT form does not describe the function's expectations
   with respect to the arguments and return values (including
   ALLOCATION), you will probably learn that the hard way.
   If the module is written in C, all the opportunities to shoot
   oneself in the foot (and other body parts) are wide open
   (although well known to most C users).
   However, with C, one has to watch
   for GC-safety too.
It is not a good idea to have
  both foo.lisp and foo.c
  files in a module, because if you ever add an “FFI” form to the
  former, COMPILE-FILE will
  overwrite the latter.
A few modules come with the source distribution of CLISP (but are not necessarily built in a particular binary distribution).
To use modules, read unix/INSTALL
 and build CLISP in directory build-dir with,
 e.g.,
$ ./configure --with-module=pcre --with-module=clx/new-clx --build build-dir
then run it with
$./build-dir/clisp-Kfull
This will create a base linking set with modules
i18n, regexp and syscalls (and maybe readline);
and a full linking set with modules clx/new-clx and pcre in addition
to the 3 (or 4) base modules.
Here we list the included modules by their general theme. See Chapter 33, Extensions Implemented as Modules for individual module documentation.
The default build process includes the following modules in both base and full linking sets:
i18nregexpsyscallsreadline (only when both GNU readline and
    “FFI” are available)The composition of the full linking set depends on the platform and on the vendor preferences.
gdbmberkeley-dbdirkeypostgresqloraclelibsvmparimatlabneticapcrewildcardzlibVECTORs using
    ZLIB.
 Call Xlib functions from CLISP. Two implementations are supplied:
clx/mit-clx, from MIT
   ftp://ftp.x.org/R5contrib/CLX.R5.02.tar.Zclx/new-clx, by faster, with additional features, but not quite complete yet.
    Please try it first and use clx/mit-clx only
    if clx/new-clx does not work for you.
    clx/new-clx comes with several demos, please try them using
    
$clisp-Kfull-imodules/clx/new-clx/demos/clx-demos.lisp-x'(clx-demos:run-all-demos)'
and follow the intructions.
This functionality is documented in the manual
  http://www.stud.uni-karlsruhe.de/~unk6/clxman/, also
  available in the CLISP source distribution as
  modules/clx/clx-manual.tar.gz.
 
gtk2Call the operating system functions from CLISP. The following platforms are supported:
queensn-queens
    problem on a n×n chessboard (a toy
    example for the users to explore the CLISP module system).
 modules/clx/new-clx/demos/sokoban.lispclx/new-clx.
This facility, also known as “Foreign Language Interface”, allows one to call a function implemented in C from inside CLISP and to do many related things, like inspect and modify foreign memory, define a “callback” (i.e., make a lisp function available to the C world), etc. To use this facility, one writes a foreign function description into an ordinary Lisp file, which is then compiled and loaded as usual.
There are two basic ways to do define a foreign function:
dlopen and
  dlsym to get to the location of the
  function code in a dynamic library.
  To access this facility, pass the :LIBRARY option to FFI:DEF-CALL-OUT
  and FFI:DEF-C-VAR.
  Unfortunately, this functionality is not available on some operating
  systems, and, also, it offers only a part of the foreign functionality:
  cpp macros and inline functions cannot be
  accessed this way.:LIBRARY argument, COMPILE-FILE produces a #P".c" file (in
  addition to a #P".fas" and a #P".lib").
  Then you compile (with a C compiler) and link it into CLISP
  (statically, linking it into lisp.a, or
  dynamically, loading it into a running CLISP using
  dlopen and
  dlsym).
  This way you can use any functionality your foreign library exports,
  whether using ordinary functions, inline functions,
  or cpp macros (see Example 32.5, “Accessing cpp macros”).
 
All symbols relating to the foreign function interface are
 exported from the package “FFI”.  To use them,
 (.USE-PACKAGE “FFI”)
Special “FFI” forms may appear anywhere in the Lisp file.
These are the special “FFI” forms. We have taken a pragmatic approach: the only foreign languages we support for now are C and ANSI C.
Unless specifically noted otherwise, type specification
  parameters are not evaluated, so that they can be compiled by
  FFI:PARSE-C-TYPE into the internal format at macroexpansion time.
High-level “FFI” forms; name is any Lisp
   SYMBOL; c-name is a STRING
(FFI:DEF-C-TYPE name &OPTIONAL c-type)This form makes name a shortcut for c-type.
   Note that c-type may already refer to name.
   Forward declarations of types are not possible, however.
When c-type is omitted, the type is assumed to be an
   integer, and its size and signedness are determined at link time,
   e.g., (.FFI:DEF-C-TYPE size_t)
(FFI:DEF-C-VAR name
   {option}*)This form defines a FFI:FOREIGN-VARIABLE.
  name is the Lisp name, a regular Lisp SYMBOL.
Options for FFI:DEF-C-VAR
(:NAME c-name)STRING.  If not specified, it is derived from the print name of
   the Lisp name.(:TYPE c-type)(:READ-ONLY BOOLEAN)NIL,
   it will be impossible to change the variable's value from within
   Lisp (using SETQ or similar).(:ALLOC ALLOCATION):NONE or
   :MALLOC-FREE and defaults to :NONE.  If it is
   :MALLOC-FREE, any values of type FFI:C-STRING, FFI:C-PTR,
   FFI:C-PTR-NULL, FFI:C-ARRAY-PTR within the foreign value are assumed
   to be pointers to malloc-allocated storage, and when SETQ
   replaces an old value by a new one, the old storage is freed using
   free and the new storage allocated using malloc.  If it is
   :NONE, SETQ assumes that the pointers point to good storage
   (not NULL!) and overwrites the old values by the new ones.
   This is dangerous (just think of overwriting a string with a
   longer one or storing some data in a NULL pointer...)  and
   deprecated.(:LIBRARY name)FFI:DEFAULT-FOREIGN-LIBRARY.(:DOCUMENTATION string)VARIABLE documentation.
(FFI:DEF-C-CONST name
   {option}*)This form defines a Lisp constant variable name whose value is
   determined at build time using an internal FFI:FOREIGN-FUNCTION.
Options for FFI:DEF-C-CONST
(:NAME c-name)STRING.  If not specified, it is derived from the print name
      of the Lisp name.(:TYPE c-type)specifies the constant's foreign type, one of
| FFI:INT | 
| FFI:C-STRING | 
| FFI:C-POINTER | 
(:GUARD
      string)specifies the cpp check to wrap around c-name,
      defaults to "defined(;
      can be c-name)"NIL to omit the test. When the test fails, name is
      unbound.
(:DOCUMENTATION string)VARIABLE documentation.
  See also Example 32.5, “Accessing cpp macros”.
(FFI:DEF-CALL-OUT
              name {option}*)This form defines a named call-out function (a foreign function called from Lisp: control flow temporarily leaves Lisp).
Options for FFI:DEF-CALL-OUT
(:NAME c-name)#'name
  is redirected to call the C function c-name.
(:ARGUMENTS
   {(argument c-type [PARAM-MODE [ALLOCATION]])}*)(:RETURN-TYPE c-type [ALLOCATION])(:LANGUAGE language)(:BUILT-IN BOOLEAN)FFI:*OUTPUT-C-FUNCTIONS*).
(:LIBRARY name)FFI:DEFAULT-FOREIGN-LIBRARY(:DOCUMENTATION string)FUNCTION documentation.
(FFI:DEF-CALL-IN
              name {option}*)This form defines a named call-in function (i.e., a Lisp function called from the foreign language: control flow temporary enters Lisp)
Options for FFI:DEF-CALL-IN
(:NAME c-name)c-name is redirected to call the Common Lisp function
   #'name.(:ARGUMENTS
   {(argument c-type [PARAM-MODE [ALLOCATION]])}*)(:RETURN-TYPE c-type [ALLOCATION])(:LANGUAGE language)(FFI:CLOSE-FOREIGN-LIBRARY
   name)Close (unload) a shared foreign library (opened by the
   :LIBRARY argument to FFI:DEF-CALL-OUT or FFI:DEF-C-VAR).
If you modify your shared library, you need to use close it
   using FFI:CLOSE-FOREIGN-LIBRARY first.  When you try to use the
   FFI:FOREIGN-VARIABLE or the FFI:FOREIGN-FUNCTION which resides in the
   library name, it will be re-opened automatically.
(FFI:DEFAULT-FOREIGN-LIBRARY
   library-name)This macro sets the default :LIBRARY argument for
   FFI:DEF-CALL-OUT and FFI:DEF-C-VAR.  library-name should be NIL
   (meaning use the C file produced by COMPILE-FILE), a
   STRING, or, depending on the
   underlying dlsym implementation,
   :DEFAULT or :NEXT.
The default is set separately in each compilation unit, so, if you
   are interfacing to a single library, you can set this variable in the
   beginning of your lisp file and omit the :LIBRARY argument
   throughout the file.
(FFI:DEF-C-STRUCT
   name (symbol c-type)*)This form defines name to be both a
  STRUCTURE-CLASS and a foreign C type with the given slots.
  If this class representation overhead is not needed one should consider
  writing ( instead.
  FFI:DEF-C-TYPE name (FFI:C-STRUCT
  {LIST | VECTOR} (symbol c-type)*))name is a SYMBOL (structure name) or a LIST whose FIRST
  element is the structure name and the REST is options.
  Two options are supported at this time:
  
Options for FFI:DEF-C-STRUCT
:TYPEDEFtypedef
      elsewhere.:EXTERNAL#P".c" file that you include with, e.g.,
      (FFI:C-LINES "#include <filename.h>~%").
  
  These options determine how the struct is written to the #P".c".
(FFI:DEF-C-ENUM
   name {symbol | (symbol [value])}*)This form defines symbols
  as constants, similarly to the C declaration enum {
  symbol [= value], ... };
You can use ( and
 FFI:ENUM-FROM-VALUE
  name value)( to convert between the numeric and symbolic
 representations (of course, the latter function boils down to
 FFI:ENUM-TO-VALUE name
  symbol)SYMBOL-VALUE plus a check that the symbol is indeed a constant
 defined in the FFI:DEF-C-ENUM name).
(FFI:C-LINES format-string
   {argument}*)This form outputs the string
   (
   to the C output file's top level.
   This is usually used to include the relevant header files,
   see FORMAT NIL format-string {argument}*):EXTERNAL
   and FFI:*OUTPUT-C-FUNCTIONS*.
When format-string is not a STRING, is should be a SYMBOL,
   and then the STRING (
   is added to the appropriate C function:FORMAT NIL {argument}*)
:INIT-ALWAYS:INIT-ONCE:FINI(FFI:ELEMENT
     c-place index1 ...
     indexn)c-place is of foreign type
  (FFI:C-ARRAY c-type
  (dim1
  ... dimn))
  and 0 ≤ index1
  < dim1, ..., 0
  ≤ indexn <
  dimn, this will be
  the place corresponding to (AREF
  c-place index1
  ... indexn) or
  c-place[index1]...[indexn]c-type.
  If c-place is of foreign type (FFI:C-ARRAY-MAX
  c-type dim) and 0 ≤ index < dim,
  this will be the place corresponding to (AREF c-place
  index) or c-place[index]c-type.
(FFI:DEREF c-place)c-place is of foreign type
  (FFI:C-PTR c-type),
  (FFI:C-PTR-NULL c-type) or
  (FFI:C-POINTER c-type),
  this will be the place the pointer points to.
  It is a place of type c-type.
  For (FFI:C-PTR-NULL c-type),
  the c-place may not be NULL.
(FFI:SLOT c-place
   slot-name)c-place is of
   foreign type (FFI:C-STRUCT class ...
    (slot-name c-type) ...) or of
   type (FFI:C-UNION
    ... (slot-name c-type) ...),
   this will be of type c-type.(FFI:CAST
           c-place c-type)c-place, but of type c-type.
 (FFI:OFFSET
           c-place offset c-type)c-place by an
  offset counted in bytes, with type c-type.
  This can be used to resize an array, e.g. of c-type
  (FFI:C-ARRAY uint16 n)
  via (FFI:OFFSET c-place 0 '(FFI:C-ARRAY uint16
   k)).
 (FFI:C-VAR-ADDRESS
           c-place)c-place as a Lisp object of
  type FFI:FOREIGN-ADDRESS.  This is useful as an argument
  to foreign functions expecting a parameter of C type FFI:C-POINTER.
 (FFI:C-VAR-OBJECT
   c-place)FFI:FOREIGN-VARIABLE object underlying the
   c-place.  This is also an acceptable argument type to a FFI:C-POINTER
   declaration.(FFI:TYPEOF c-place)c-type corresponding to the c-place.
(FFI:SIZEOF c-type)(FFI:SIZEOF c-place)The first form returns the size and alignment of the
   C type c-type, measured in bytes.
The second form returns the size and alignment of the
   C type of c-place, measured in bytes.
(FFI:BITSIZEOF c-type)(FFI:BITSIZEOF c-place)The first form returns the size and alignment of the
   C type c-type, measured in bits.
The second form returns the size and alignment of the
   C type of c-place, measured in bits.
(FFI:FOREIGN-ADDRESS-NULL foreign-entity)T if the
  foreign-entity refers to the NULL address (and thus foreign-entity should
  probably not be passed to most foreign functions).
(FFI:FOREIGN-ADDRESS-UNSIGNED foreign-entity)(FFI:UNSIGNED-FOREIGN-ADDRESS number)FFI:FOREIGN-ADDRESS-UNSIGNED returns the INTEGER
   address embodied in the Lisp object of type FFI:FOREIGN-ADDRESS,
   FFI:FOREIGN-POINTER, FFI:FOREIGN-VARIABLE or FFI:FOREIGN-FUNCTION.
FFI:UNSIGNED-FOREIGN-ADDRESS returns a FFI:FOREIGN-ADDRESS
   object pointing to the given INTEGER address.
(FFI:FOREIGN-ADDRESS foreign-entity)FFI:FOREIGN-ADDRESS is both a type name and a
   selector/constructor function. It is the Lisp object type
   corresponding to a FFI:C-POINTER external type declaration, e.g. a
   call-out function with ( yields
   a Lisp object of type :RETURN-TYPE FFI:C-POINTER)FFI:FOREIGN-ADDRESS.
The function extracts the object of type FFI:FOREIGN-ADDRESS
   living within any FFI:FOREIGN-VARIABLE or FFI:FOREIGN-FUNCTION object.
   If the foreign-entity already is a FFI:FOREIGN-ADDRESS, it returns it.
   If it is a FFI:FOREIGN-POINTER (e.g. a base foreign library address),
   it encapsulates it into a FFI:FOREIGN-ADDRESS object, as suitable
   for use with a FFI:C-POINTER external type declaration.
   It does not construct addresses out of NUMBERs,
   FFI:UNSIGNED-FOREIGN-ADDRESS must be used for that purpose.
(FFI:FOREIGN-VARIABLE foreign-entity
   c-type-internal &KEY name)FFI:FOREIGN-VARIABLE
   from the given FFI:FOREIGN-ADDRESS or FFI:FOREIGN-VARIABLE and the
   internal C type descriptor (as obtained from FFI:PARSE-C-TYPE).
   name, a STRING, is mostly useful for documentation and
   interactive debugging since it appears in the printed representation
   of the FFI:FOREIGN-VARIABLE object, as in
   #<FFI:FOREIGN-VARIABLE "foo"
    #x0ADD4E55>.
   In effect, this is similar to FFI:CAST (or rather
   (FFI:OFFSET ... 0 ...) for places),
   except that it works with FFI:FOREIGN-ADDRESS objects and allows
   caching of the internal C types.(FFI:FOREIGN-FUNCTION
   foreign-entity c-type-internal &KEY name)FFI:FOREIGN-FUNCTION
   from the given FFI:FOREIGN-ADDRESS or FFI:FOREIGN-FUNCTION and the
   internal C type descriptor (as obtained from
   (FFI:PARSE-C-TYPE '(FFI:C-FUNCTION ...)),
   in which case it is important to specify the :LANGUAGE because the
   expressions are likely to be evaluated at run time, outside the compilation unit).
   name, a STRING, is mostly useful for documentation and
   interactive debugging since it appears in the printed representation
   of the FFI:FOREIGN-FUNCTION object, as in
   #<FFI:FOREIGN-FUNCTION "foo"
    #x0052B060>.
   It is inherited from the given FFI:FOREIGN-FUNCTION object when
   available.(FFI:VALIDP foreign-entity)(SETF (FFI:VALIDP foreign-entity) value)This predicate returns NIL if the foreign-entity
  (e.g. the Lisp equivalent of a FFI:C-POINTER) refers to a pointer
  which is invalid (e.g., because it comes from a previous Lisp session).
  It returns T if foreign-entity can be used within the current Lisp process
  (thus it returns T for all non-foreign arguments).
You can invalidate a foreign object using
  (.
  You cannot resurrect a zombie, nor can you kill a non-foreign object.
SETF FFI:VALIDP)
(FFI:FOREIGN-POINTER foreign-entity)FFI:FOREIGN-POINTER returns the FFI:FOREIGN-POINTER
   associated with the Lisp object of type FFI:FOREIGN-ADDRESS,
   FFI:FOREIGN-POINTER, FFI:FOREIGN-VARIABLE or FFI:FOREIGN-FUNCTION.
(FFI:SET-FOREIGN-POINTER foreign-entity {foreign-entity |
   :COPY})FFI:SET-FOREIGN-POINTER changes the
   FFI:FOREIGN-POINTER associated with the Lisp object of type
   FFI:FOREIGN-ADDRESS, FFI:FOREIGN-VARIABLE or FFI:FOREIGN-FUNCTION to
   that of the other entity.
   With :COPY, a fresh FFI:FOREIGN-POINTER is allocated.
   The original foreign-entity still points to the same object and is returned.
   This is particularly useful with (SETF FFI:VALIDP),
   see Example 32.10, “Controlling validity of resources”.(FFI:WITH-FOREIGN-OBJECT (variable c-type
      [initarg]) body)(FFI:WITH-C-VAR (variable c-type
      [initarg]) body)These forms allocate space on the C execution
  stack, bind respectively a FFI:FOREIGN-VARIABLE object or
  a local SYMBOL-MACRO to variable and execute body.
When initarg is not supplied,
  they allocate space only for ( bytes.  This space is filled with zeroes.  E.g.,
  using a FFI:SIZEOF
  c-type)c-type of FFI:C-STRING or even (FFI:C-PTR
  (FFI:C-ARRAY uint8 32)) (!) both allocate space
  for a single pointer, initialized to NULL.
When initarg is supplied, they
  allocate space for an arbitrarily complex set of structures rooted in
  c-type.  Therefore, FFI:C-ARRAY-MAX, #()
  and "" are your friends for creating a
  pointer to the empty arrays:
(with-c-var (v '(c-ptr (c-array-max uint8 32)) #()) (setf (element (deref v) 0) 127) v)
  c-type is evaluated, making creation of variable sized buffers easy:
(with-c-var (fv `(c-array uint8 ,(length my-vector)) my-vector) (print fv))
(FFI:FOREIGN-VALUE FFI:FOREIGN-VARIABLE)(SETF (FFI:FOREIGN-VALUE FFI:FOREIGN-VARIABLE) ...)This functions converts the reference to a C
  data structure which the FFI:FOREIGN-VARIABLE describes, to Lisp. Such a
  reference is typically obtained from FFI:ALLOCATE-SHALLOW,
  FFI:ALLOCATE-DEEP, FFI:FOREIGN-ALLOCATE or via a (FFI:C-POINTER
   C type description.
  Alternatively, macros like c-type)FFI:WITH-C-PLACE or FFI:WITH-C-VAR and the
  concept of foreign place hide many uses of this function.
The SETF form performs conversion from Lisp to C,
  following to the FFI:FOREIGN-VARIABLE's type description.
(FFI:WITH-FOREIGN-STRING
   (foreign-address char-count
    byte-count string
    &KEY encoding null-terminated-p
    start end) &BODY body)This forms converts a Lisp string according to
   the encoding, allocating space on the C execution stack.
   encoding can be any EXT:ENCODING, e.g. CHARSET:UTF-16 or CHARSET:UTF-8,
   whereas CUSTOM:*FOREIGN-ENCODING* must be an ASCII-compatible encoding.
   
body is then executed with the three variables foreign-address,
   char-count and
   byte-count respectively bound to an
   untyped FFI:FOREIGN-ADDRESS (as known from the FFI:C-POINTER foreign
   type specification) pointing to the stack location, the number of
   CHARACTERs of the Lisp string that were considered and the
   number of ( bytes that were allocated for it on the C
   stack.UNSIGNED-BYTE 8)
When null-terminated-p is true,
   which is the default, a variable number of zero bytes is appended,
   depending on the encoding, e.g. 2 for CHARSET:UTF-16,
   and accounted for in byte-count,
   and char-count is incremented by one.
The FFI:FOREIGN-ADDRESS object bound to foreign-address is
   invalidated upon the exit from the form.
A stupid example (a quite costly interface
   to mblen):
(with-foreign-string (fv elems bytes string
                      :encoding charset:jis... :null-terminated-p nil
                      :end 5)
 (declare (ignore fv elems))
 (format t "This string would take ~D bytes." bytes))
(FFI:PARSE-C-TYPE c-type)(FFI:DEPARSE-C-TYPE c-type-internal)Convert between the external (LIST) and internal
   (VECTOR) C type representations (used by DESCRIBE).
  
Although you can memoize a c-type-internal (see
    Section 31.11.3, “Macro EXT:MEMOIZED” - but do not expect type redefinitions to
    work across memoization!), you cannot serialize it (write to
    disk) because deserialization loses object identity.
(FFI:ALLOCATE-SHALLOW
   c-type &KEY :COUNT :READ-ONLY)(FFI:ALLOCATE-DEEP c-type contents
   &KEY :COUNT :READ-ONLY)(FFI:FOREIGN-FREE foreign-entity &KEY :FULL)(FFI:FOREIGN-ALLOCATE c-type-internal
   &KEY :INITIAL-CONTENTS :COUNT :READ-ONLY)Macro FFI:ALLOCATE-SHALLOW allocates
   (
   bytes on the C heap and zeroes them out
   (like FFI:SIZEOF c-type)calloc).
   When :COUNT is supplied, c-type is substituted with
   (FFI:C-ARRAY ,
   except when c-type count)c-type is CHARACTER, in which case
   (FFI:C-ARRAY-MAX 
   is used instead.
   When CHARACTER count):READ-ONLY is supplied, the Lisp side is prevented from modifying the
   memory contents.  This can be used as an indication that some foreign
   side is going to fill this memory
   (e.g. via read).
Returns a FFI:FOREIGN-VARIABLE object of the actual c-type,
   whose address part points to the newly allocated memory.
FFI:ALLOCATE-DEEP will call C malloc as many times
   as necessary to build a structure on the C heap of the given
   c-type, initialized from the given contents.
E.g., (
    performs 2 allocations: one for a C pointer to a string,
    another for the contents of that string.  This would be useful in
    conjunction with a char** C type
    declaration.  FFI:ALLOCATE-DEEP 'FFI:C-STRING "ABCDE")(
    allocates room for a single pointer (probably 4 bytes).FFI:ALLOCATE-SHALLOW 'FFI:C-STRING)
( allocates and initializes room for the type FFI:ALLOCATE-DEEP 'CHARACTER "ABCDEF" :count
    10)(FFI:C-ARRAY-MAX ,
    corresponding to char* or, more specifically,
   char[10] in C.CHARACTER 10)
Function FFI:FOREIGN-FREE deallocates memory at the address
   held by the given foreign-entity. If :FULL is supplied
   and the argument is of type FFI:FOREIGN-VARIABLE, recursively frees
   the whole complex structure pointed to by this variable.
If given a FFI:FOREIGN-FUNCTION object that corresponds to a
   CLISP callback, deallocates it.  Callbacks are automatically
   created each time you pass a Lisp function via the “FFI”.
Use ( to disable further
   references to this address from Lisp.  This is currently not done
   automatically.  If the given pointer is already invalid,
   SETF FFI:VALIDP)FFI:FOREIGN-FREE (currently) SIGNALs an ERROR. This may change to
   make it easier to integrate with EXT:FINALIZE.
Function FFI:FOREIGN-ALLOCATE is a lower-level interface as it
   requires an internal C type descriptor as returned by
   FFI:PARSE-C-TYPE.
(FFI:WITH-C-PLACE (variable foreign-entity)
   body)Create a place out of the given FFI:FOREIGN-VARIABLE
  object so operations on places (e.g. FFI:CAST, FFI:DEREF, FFI:SLOT etc.) can
  be used within body.  FFI:WITH-C-VAR appears as a composition of
  FFI:WITH-FOREIGN-OBJECT and FFI:WITH-C-PLACE.
Such a place can be used to access memory referenced by a foreign-entity
  object:
  
(setq foo (allocate-deep '(c-array uint8 3) rgb)) (with-c-place (place foo) (element place 0))
FFI:*OUTPUT-C-FUNCTIONS*FFI:*OUTPUT-C-VARIABLES*FFI:DEF-CALL-OUT) and
   foreign variables (defined with FFI:DEF-C-VAR) into the output #P".c"
   (when the Lisp file is compiled with COMPILE-FILE)
   unless these variables are NIL.
   They are NIL by default, so the extern
   declarations are not written; you are encouraged to use
   FFI:C-LINES to include the appropriate C headers.
   Set these variables to non-NIL if the headers are not available or
   not usable.FFI:*FOREIGN-GUARD*When this variable is non-NIL at compile time,
  CLISP will guard the C statements in the output file with
  cpp conditionals to take advantage of GNU autoconf feature detection.
  E.g., 
(eval-when (compile) (setq *foreign-guard* t)) (def-call-out some-function (:name "function_name") ...)
will produce
# if defined(HAVE_FUNCTION_NAME) register_foreign_function((void*)&function_name,"function_name",1024); # endif
and will compile and link on any system.
This is mostly useful for product delivery when you want your module to build on any system even if some features will not be available.
FFI:*FOREIGN-GUARD* is initialized to NIL for backwards compatibility.
Low-level “FFI” forms
(FFI:MEMORY-AS foreign-address c-type-internal &OPTIONAL
   offset)(SETF (FFI:MEMORY-AS foreign-address c-type-internal &OPTIONAL
   offset) value)This accessor is useful when operating with untyped
   foreign pointers (FFI:FOREIGN-ADDRESS) as opposed to typed ones
   (represented by FFI:FOREIGN-VARIABLE).  It allows to type and
   dereference the given pointer without the need to create an object of
   type FFI:FOREIGN-VARIABLE.
Alternatively, one could use (
   (also FFI:FOREIGN-VALUE
    (FFI:FOREIGN-VARIABLE foreign-entity c-type-internal))SETFable).
Note that c-type-internal is the internal
   representation of a foreign type, thus FFI:PARSE-C-TYPE is required
   with literal names or types, e.g. ( or FFI:MEMORY-AS foreign-address
    (FFI:PARSE-C-TYPE '(FFI:C-ARRAY uint8 3)))(.SETF
    (FFI:MEMORY-AS foreign-address (FFI:PARSE-C-TYPE 'uint32)) 0)
Foreign C types are used in the “FFI”. They are not regular Common Lisp types or CLOS classes.
A c-type is either a predefined C type or the name of a
 type defined by FFI:DEF-C-TYPE.
the predefined C types (c-type)
simple-c-typethe simple C types
| Lisp name | Lisp equivalent | C equivalent | ILU equivalent | Comment | 
|---|---|---|---|---|
| NIL | NIL | void | as a result type only | |
| BOOLEAN | BOOLEAN | int | BOOLEAN | |
| CHARACTER | CHARACTER | char | SHORT CHARACTER | |
| char | INTEGER | signed char | ||
| uchar | INTEGER | unsigned char | ||
| short | INTEGER | short | ||
| ushort | INTEGER | unsigned short | ||
| int | INTEGER | int | ||
| uint | INTEGER | unsigned int | ||
| long | INTEGER | long | ||
| ulong | INTEGER | unsigned long | ||
| uint8 | ( | uint8 | BYTE | |
| sint8 | ( | sint8 | ||
| uint16 | ( | uint16 | SHORT CARDINAL | |
| sint16 | ( | sint16 | SHORT INTEGER | |
| uint32 | ( | uint32 | CARDINAL | |
| sint32 | ( | sint32 | INTEGER | |
| uint64 | ( | uint64 | LONG CARDINAL | does not work on all platforms | 
| sint64 | ( | sint64 | LONG INTEGER | does not work on all platforms | 
| SINGLE-FLOAT | SINGLE-FLOAT | float | ||
| DOUBLE-FLOAT | DOUBLE-FLOAT | double | 
NIL is accepted as a FFI:C-POINTER and
   treated as NULL; when a function wants to return a NULL
   FFI:C-POINTER, it actually returns NIL.
(FFI:C-POINTER
  c-type)c-type *: a pointer to a single item of the given
  c-type. It differs from (FFI:C-PTR-NULL
  c-type) (see below) in that no conversion to and from
  Lisp will occur (beyond the usual one of the C NULL pointer
  to or from Lisp NIL). Instead, an object of type FFI:FOREIGN-VARIABLE
  is used to represent the foreign place. It is assimilable to a typed
  pointer.(FFI:C-STRUCT
  class (ident1
   c-type1) ...
  (identn
   c-typen))This type is equivalent to what C calls
 struct { c-type1
 ident1; ...;
 c-typen
 identn; }.
 Its Lisp equivalent is: if class is VECTOR, a
 SIMPLE-VECTOR; if class is LIST, a proper list;
 if class is a symbol naming a structure or CLOS class, an
 instance of this class, with slots of names
 ident1, ...,
 identn.
 class may also be a CONS of a SYMBOL (as above) and
 a LIST of FFI:DEF-C-STRUCT options.
 
(FFI:C-UNION
  (ident1
   c-type1) ...
  (identn
   c-typen))c-type1
  ident1; ...;
  c-typen
  identn;
  }.
  Conversion to and from Lisp assumes that a value is to be viewed as
  being of c-type1.
 (FFI:C-ARRAY
   c-type dim1)(FFI:C-ARRAY
   c-type (dim1 ...
   dimn))c-type [dim1]
  ... [dimn].
  Note that when an array is passed as an argument to a function in
  C, it is actually passed as a pointer; you therefore have to
  write (FFI:C-PTR (FFI:C-ARRAY ...)) for this
  argument's type.(FFI:C-ARRAY-MAX
  c-type maxdimension)c-type [maxdimension], an array containing up to
  maxdimension elements.
  The array is zero-terminated if it contains less than maxdimension elements.
  Conversion from Lisp of an array with more than maxdimension elements
  silently ignores the superfluous elements.
  (FFI:C-FUNCTION (:ARGUMENTS
      {(argument a-c-type
        [PARAM-MODE [ALLOCATION]])}*)
    (:RETURN-TYPE r-c-type [ALLOCATION])
    (:LANGUAGE language))(r-c-type (*)
    (a-c-type1, ...)).
  Conversion between C functions and Lisp functions
  is transparent, and NULL/NIL is recognized and
  accepted.(FFI:C-PTR
              c-type)c-type *: a pointer to a single item of the given
  c-type.(FFI:C-PTR-NULL c-type)c-type *: a pointer to a single item of the given
  c-type, with the exception that C NULL corresponds to
  Lisp NIL.(FFI:C-ARRAY-PTR c-type)c-type (*)[]: a pointer to a zero-terminated array of
  items of the given c-type.The conversion of FFI:C-STRING,
 (FFI:C-ARRAY ,
 CHARACTER dim1)(FFI:C-ARRAY-MAX ,
 CHARACTER maxdimension)(FFI:C-ARRAY-PTR 
 is governed by CHARACTER)CUSTOM:*FOREIGN-ENCODING* and dimensions are given
 in bytes.
 The conversion of CHARACTER, and as such of
 (FFI:C-PTR , or
 CHARACTER)(FFI:C-PTR-NULL , as well as
 that of multi-dimensional arrays CHARACTER)(FFI:C-ARRAY ,
 are governed by CHARACTER
 (dim1 ... dimn))CUSTOM:*FOREIGN-ENCODING* if the latter is a 1:1 encoding, or by the
 ASCII encoding otherwise.
Remember that the C type char is
  a numeric type and does not use CHARACTER
  EXT:ENCODINGs.
FFI:C-FUNCTION, FFI:DEF-CALL-IN, FFI:DEF-CALL-OUT take a :LANGUAGE argument.
The language is either :C (denotes K&R C) or :STDC
(denotes ANSI C) or :STDC-STDCALL (denotes ANSI C
with the “stdcall” calling convention).
It specifies whether the C function (caller or callee) has been
compiled by a K&R C compiler or by an ANSI C compiler,
and possibly the calling convention.
The default language is set using the macro
 FFI:DEFAULT-FOREIGN-LANGUAGE
  .
 If this macro has not been called in the current compilation unit
 (usually a file), a warning is issued and
:STDC is used for the rest of the unit.
Foreign variables are variables whose storage is allocated in the
 foreign language module.
 They can nevertheless be evaluated and modified through SETQ,
 just as normal variables can, except that the range of allowed values
 is limited according to the variable's foreign type.
For a foreign variable x the form ( is not necessarily true, since every time EQL x
   x)x is
  evaluated its foreign value is converted to a fresh Lisp value.
  Ergo, ( modifies this
  fresh Lisp value (immediately discarded), not the foreign data.
  Use SETF (AREF x n) y)FFI:ELEMENT et al instead, see Section 32.3.6, “Operations on foreign places”.
Foreign variables are defined using FFI:DEF-C-VAR and FFI:WITH-C-VAR.
A FFI:FOREIGN-VARIABLE name defined by FFI:DEF-C-VAR, FFI:WITH-C-VAR
 or FFI:WITH-C-PLACE defines a place,
 i.e., a form which can also be used as argument to SETF.
 (An “lvalue” in C terminology.)
 The following operations are available on foreign places:
 
| FFI:ELEMENT | FFI:C-VAR-ADDRESS | 
| FFI:DEREF | FFI:C-VAR-OBJECT | 
| FFI:SLOT | FFI:TYPEOF | 
| FFI:CAST | FFI:SIZEOF | 
| FFI:OFFSET | FFI:BITSIZEOF | 
Foreign functions are functions which are defined in the foreign
 language.  There are named foreign functions
 (imported via FFI:DEF-CALL-OUT or created via FFI:DEF-CALL-IN) and
 anonymous foreign functions; they arise through
 conversion of function pointers.
A call-out function is a foreign function called from Lisp: control flow temporarily leaves Lisp. A call-in function is a Lisp function called from the foreign language: control flow temporary enters Lisp.
The following operators define foreign functions:
| FFI:DEF-CALL-IN | FFI:FOREIGN-FUNCTION | 
| FFI:DEF-CALL-OUT | 
When passed to and from functions, allocation of arguments and results is handled as follows:
Values of SIMPLE-C-TYPE, FFI:C-POINTER are passed on the stack,
 with dynamic extent. The ALLOCATION is effectively ignored.
Values of type FFI:C-STRING, FFI:C-PTR, FFI:C-PTR-NULL, FFI:C-ARRAY-PTR
 need storage.  The ALLOCATION specifies the allocation policy:
If no ALLOCATION is specified, the default ALLOCATION is
 :NONE for most types, but :ALLOCA for FFI:C-STRING and FFI:C-PTR and
 FFI:C-PTR-NULL and FFI:C-ARRAY-PTR and for :OUT arguments.
 The :MALLOC-FREE policy provides the ability to pass
 arbitrarily nested structures within a single conversion.
:MALLOC-FREEmalloc and
     never deallocates it.  The C function is supposed to call
     free when done with it.:ALLOCA:NONELisp assumes that the pointer already points to a valid area of the proper size and puts the result value there.
This is dangerous and deprecated.
:MALLOC-FREEfree on it when done.
    :NONEPassing FFI:C-STRUCT, FFI:C-UNION,
  FFI:C-ARRAY, FFI:C-ARRAY-MAX values as arguments (not via pointers) is
  only possible to the extent the C compiler supports it.
  Most C compilers do it right, but some C compilers
  (such as gcc on hppa,
  x86_64 and Win32)
  have problems with this.
  The recommended workaround is to pass pointers; this is fully supported.
  See also the <clisp-list@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-list) (SFmail/5513622,
  Gmane/devel/10089).
A function parameter's PARAM-MODE may be
:IN (means: read-only)::OUT (means: write-only):ALLOCATION = :ALLOCA.:IN-OUT (means: read-write)::OUT value is returned as an additional multiple value.
  The default is :IN.
Example 32.1. Simple declarations and access
The C declaration
struct foo {
    int a;
    struct foo * b[100];
};
corresponds to
(def-c-struct foo (a int) (b (c-array (c-ptr foo) 100)))
The element access
struct foo f; f.b[7].a
corresponds to
(declare (type foo f)) (foo-a (aref (foo-b f) 7)) or (slot-value (aref (slot-value f 'b) 7) 'a)
Example 32.2. external C variable and some accesses
struct bar {
    short x, y;
    char a, b;
    int z;
    struct bar * n;
};
extern struct bar * my_struct;
my_struct->x++;
my_struct->a = 5;
my_struct = my_struct->n;
corresponds to
(def-c-struct bar (x short) (y short) (a char) (b char) ; or (b character) if it represents a character, not a number (z int) (n (c-ptr bar))) (def-c-var my_struct (:type (c-ptr bar))) (setq my_struct (let ((s my_struct)) (incf (slot-value s 'x)) s)) or (incf (slot my_struct 'x)) (setq my_struct (let ((s my_struct)) (setf (slot-value s 'a) 5) s)) or (setf (slot my_struct 'a) 5) (setq my_struct (slot-value my_struct 'n)) or (setq my_struct (deref (slot my_struct 'n)))
Example 32.3. Calling an external function
On ANSI C systems, <stdlib.h>
 contains the declarations:
typedef struct {
  int quot;   /* Quotient */
  int rem;    /* Remainder */
} div_t;
extern div_t div (int numer, int denom);
This translates to
(def-c-struct (div_t :typedef) (quot int) (rem int)) (default-foreign-language :stdc) (def-call-out div (:arguments (numer int) (denom int)) (:return-type div_t))
Sample call from within Lisp (after running clisp-link):
(div 20 3)
⇒ #S(DIV_T :QUOT 6 :REM 2)
Example 32.4. Another example for calling an external function
Suppose the following is defined in a file
 cfun.c:
struct cfunr { int x; char *s; };
struct cfunr * cfun (int i,char *s,struct cfunr * r,int a[10]) {
  int j;
  struct cfunr * r2;
  printf("i = %d\n", i);
  printf("s = %s\n", s);
  printf("r->x = %d\n", r->x);
  printf("r->s = %s\n", r->s);
  for (j = 0; j < 10; j++) printf("a[%d] = %d.\n", j, a[j]);
  r2 = (struct cfunr *) malloc (sizeof (struct cfunr));
  r2->x = i+5;
  r2->s = "A C string";
  return r2;
}
It is possible to call this function from Lisp using the file
callcfun.lisp (do not call it
cfun.lisp - COMPILE-FILE will
overwrite
cfun.c) whose contents is:
(DEFPACKAGE"TEST-C-CALL" (:use “COMMON-LISP” “FFI”)) (IN-PACKAGE"TEST-C-CALL") (eval-when (compile) (setqFFI:*OUTPUT-C-FUNCTIONS*t)) (def-c-struct cfunr (x int) (s c-string)) (default-foreign-language :stdc) (def-call-out cfun (:arguments (i int) (s c-string) (r (c-ptr cfunr) :in :alloca) (a (c-ptr (c-array int 10)) :in :alloca)) (:return-type (c-ptr cfunr))) (defun call-cfun () (cfun 5 "A Lisp string" (make-cfunr :x 10 :s "Another Lisp string") '#(0 1 2 3 4 5 6 7 8 9)))
Use the module facility:
$clisp-link create-module-set cfun callcfun.c$cc -O -c cfun.c$cd cfun$ln -s ../cfun.o cfun.o Add cfun.o to NEW_LIBS and NEW_FILES in link.sh.$cd ..$base/lisp.run -M base/lispinit.mem -c callcfun.lisp$clisp-link add-module-set cfun base base+cfun$base+cfun/lisp.run -M base+cfun/lispinit.mem -i callcfun > (test-c-call::call-cfun) i = 5 s = A Lisp string r->x = 10 r->s = Another Lisp string a[0] = 0. a[1] = 1. a[2] = 2. a[3] = 3. a[4] = 4. a[5] = 5. a[6] = 6. a[7] = 7. a[8] = 8. a[9] = 9. #S(TEST-C-CALL::CFUNR :X 10 :S "A C string") >$rm -r base+cfun
Note that there is a memory leak here: The return value
r2 of cfun() is
malloced but never freed. Specifying
(:return-type (c-ptr cfunr) :malloc-free)
is not an alternative because this would also
free(r2->x) but r2->x is a
pointer to static data.
The memory leak can be avoided using
(:return-type (c-pointer cfunr))
instead, in conjunction with
(defun call-cfun ()
  (let ((data (cfun ...)))
    (prog1 (FFI:FOREIGN-VALUE data)
      (FFI:FOREIGN-FREE data :FULL nil))))
Example 32.5. Accessing cpp macros
Suppose you are interfacing to a library mylib.so
 which defines types, macros and inline functions
 in mylib.h:
#define FOO(x)  .....
#define BAR ...
struct zot { ... }
inline int bar (int x) { ... }
 To make them available from CLISP, write these forms into the lisp
 file my.lisp:
(FFI:C-LINES"#include <mylib.h> int my_foo (int x) { return FOO(x); } int my_bar (int x) { return bar(x); }~%") (FFI:DEF-C-CONSTbar) (FFI:DEF-C-CONSTzot-size (:name "sizeof(struct zot)") (:guard nil)) (FFI:DEF-CALL-OUTmy-foo (:name "my_foo") (:arguments (x int)) (:return-type int)) (FFI:DEF-CALL-OUTmy-bar (:name "my_bar") (:arguments (x int)) (:return-type int))
Compiling this file will produce my.c
 and my.fas and you have two options:
 
Compile my.c
    into my.o with 
$ gcc -c my.c -lmylib
and use clisp-link to create a new CLISP linking set.
Add (:library "my.dll") to the
    FFI:DEF-CALL-OUT forms, compile my.c
    into my.so (or my.dll on
    Win32) with 
$ gcc -shared -o my.so my.c -lmylib
 and load my.fas.
Of course, you could have created my1.c
 containing
#include <mylib.h>
int my_foo (int x) { return FOO(x); }
int my_bar (int x) { return bar(x); }
manually, but FFI:C-LINES allows you to keep the
 definitions of my_foo and my-foo
 close together for easier maintenance.
Example 32.6. Calling Lisp from C
To sort an array of double-floats using the Lisp function SORT
 instead of the C library function
 qsort, one can use the
 following interface code sort1.c.
 The main problem is to pass a variable-sized array.
extern void lispsort_begin (int);
void* lispsort_function;
void lispsort_double (int n, double * array) {
    double * sorted_array;
    int i;
    lispsort_begin(n); /* store #'sort2 in lispsort_function */
    sorted_array = ((double * (*) (double *)) lispsort_function) (array);
    for (i = 0; i < n; i++) array[i] = sorted_array[i];
    free(sorted_array);
}
This is accompanied by sort2.lisp:
(DEFPACKAGE"FFI-TEST" (:use “COMMON-LISP” “FFI”)) (IN-PACKAGE"FFI-TEST") (eval-when (compile) (setqFFI:*OUTPUT-C-FUNCTIONS*t)) (def-call-in lispsort_begin (:arguments (n int)) (:return-type nil) (:language :stdc)) (def-c-var lispsort_function (:type c-pointer)) (defun lispsort_begin (n) (setf (cast lispsort_function `(c-function (:arguments (v (c-ptr (c-array double-float ,n)))) (:return-type (c-ptr (c-array double-float ,n)) :malloc-free))) #'sort2)) (defun sort2 (v) (declare (type vector v)) (sort v #'<))
To test this, use the following test file sorttest.lisp:
(eval-when (compile) (setq FFI:*OUTPUT-C-FUNCTIONS* t))
(def-call-out sort10
  (:name "lispsort_double")
  (:language :stdc)
  (:arguments (n int)
              (array (c-ptr (c-array double-float 10)) :in-out)))
Now try
$clisp-link create-module-set sort sort2.c sorttest.c$cc -O -c sort1.c$cd sort$ln -s ../sort1.o sort1.o
Add sort1.o to NEW_LIBS
and NEW_FILES in link.sh.
Create a file package.lisp containing the form
(MAKE-PACKAGE "FFI-TEST" :use '(“COMMON-LISP” “FFI”))
and add package.lisp to TO_PRELOAD in link.sh.
Proceed:
$cd ..$base/lisp.run -M base/lispinit.mem -c sort2.lisp sorttest.lisp$clisp-link add-module-set sort base base+sort$base+sort/lisp.run -M base+sort/lispinit.mem -i sort2 sorttest > (sort10 10 '#(0.501d0 0.528d0 0.615d0 0.550d0 0.711d0 0.523d0 0.585d0 0.670d0 0.271d0 0.063d0)) #(0.063d0 0.271d0 0.501d0 0.523d0 0.528d0 0.55d0 0.585d0 0.615d0 0.67d0 0.711d0)$rm -r base+sort
Example 32.7. Calling Lisp from C dynamically
Create a dynamic library lispdll
 (#P".dll" on Win32,
  #P".so" on UNIX)
  with the following function:
typedef int (*LispFunc)(int parameter);
int CallInFunc(LispFunc f) {
  return f(5)+11;
}
and call it from Lisp:
(ffi:def-call-out callout
  (:name "CallInFunc")
  (:library "lispdll.dll")
  (:arguments (function-arg
               (ffi:c-function (:arguments (number ffi:int))
                               (:return-type ffi:int) (:language :stdc))))
  (:return-type ffi:int)
  (:language :stdc))
(defun f (x) (* x 2))
⇒ F
(callout #'f)
⇒ 21
Example 32.8. Variable size arguments:
  calling gethostname from CLISP
 follows a typical pattern of C "out"-parameter convention - it
 expects a pointer to a buffer it is going to fill.
 So you must view this parameter as either :OUT or :IN-OUT.
 Additionally, one must tell the function the size of the buffer.
 Here namelen is just an :IN parameter.
 Sometimes this will be an :IN-OUT parameter, returning the
 number of bytes actually filled in.
So name is actually a pointer to an array of up to
 namelen characters, regardless of what the
 poor char* C prototype says, to be used like a
 C string (NULL-termination).  UNIX specifies
 that “host names are limited to
  HOST_NAME_MAX bytes”, which is, of course,
 system dependent, but it appears that 256 is sufficient.
In the present example, you can use allocation :ALLOCA, like
 you would do in C: stack-allocate a temporary.
(FFI:DEF-CALL-OUTgethostname (:arguments (name (FFI:C-PTR (FFI:C-ARRAY-MAX ffi:char 256)):OUT:ALLOCA) (len ffi:int)) (:language :stdc) (:return-type ffi:int)) (defun myhostname () (multiple-value-bind (success name) ;;:OUTand:IN-OUTparameters are returned as multiple values (gethostname 256) (if (zerop success) name (error ...)))) ;;strerror(errno) (defvar hostname (myhostname))
Example 32.9. Accessing variables in shared libraries
Suppose one wants to access and modify variables that reside in shared libraries:
struct bar {
  double x, y;
  double out;
};
struct bar my_struct = {10.0, 20.5, 0.0};
double test_dll(struct bar *ptr)
{
  return ptr->out = ptr->out + ptr->x + ptr->y;
}
This is compiled to libtest.so (or
 libtest.dll, depending on your platform).
Use the following lisp code:
(USE-PACKAGE“FFI”) (FFI:DEF-C-STRUCTbar (x double-float) (y double-float) (out double-float)) (FFI:DEF-CALL-OUTget-own-c-float (:library "libtest.so") (:language :stdc) (:name "test_dll") (:arguments (ptr c-pointer :in :alloca)) (:return-type double-float)) (FFI:DEF-C-VARmy-c-var (:name "my_struct") (:library "libtest.so") (:type (c-ptr bar)))
Note that get-own-c-float takes a
 FFI:C-POINTER, not a (FFI:C-PTR bar) as the
 argument.
Now you can access call get-own-c-float on
my-c-var:
(FFI:C-VAR-ADDRESSmy-c-var) ⇒#<FOREIGN-ADDRESS #x282935D8>(get-own-c-float (FFI:C-VAR-ADDRESSmy-c-var)) ⇒30.5d0(get-own-c-float (FFI:C-VAR-ADDRESSmy-c-var)) ⇒61.0d0(get-own-c-float (FFI:C-VAR-ADDRESSmy-c-var)) ⇒91.5d0(get-own-c-float (FFI:C-VAR-ADDRESSmy-c-var)) ⇒122.0d0
Example 32.10. Controlling validity of resources
FFI:SET-FOREIGN-POINTER is useful in conjunction with ( to limit the extent of external resources.
 Closing twice can be avoided by checking SETF
  FFI:VALIDP)FFI:VALIDP.
 All pointers depending on this resource can be disabled at once upon
 close by sharing their FFI:FOREIGN-POINTER using FFI:SET-FOREIGN-POINTER.
(def-c-type PGconn c-pointer) ; opaque pointer
(def-call-out PQconnectdb (:return-type PGconn)
  (:arguments (conninfo c-string)))
(defun sql-connect (conninfo)
  (let ((conn (PQconnectdb conninfo)))
    (unless conn (error "NULL pointer"))
    ;; may wish to use EXT:FINALIZE as well
    (FFI:SET-FOREIGN-POINTER conn :COPY)))
(defun sql-dependent-resource (conn arg1)
  (let ((res (PQxxx conn arg1)))
    (FFI:SET-FOREIGN-POINTER res conn)))
(defun sql-close (connection)
  (when (FFI:VALIDP connection)
    (PQfinish connection)
    (setf (FFI:VALIDP connection) nil)
    T))
Sharing FFI:FOREIGN-POINTER goes both ways: invalidating
  the dependent resource will invalidate the primary one.
An alternative approach to resource management, more suitable to non-“FFI” modules, is implemented in the berkeley-db module, see Section 33.6.2, “Closing handles”.
Example 32.11. Float point array computations
Save this code into sum.c:
double sum (int len, double *vec) {
  int i;
  double s=0;
  for (i=0; i<len; i++) s+= vec[i];
  return s;
}
and compile it with
$ gcc -shared -o libsum.so sum.cNow you can sum doubles:
(FFI:DEF-CALL-OUTsum (:name "sum") (:library "libsum.so") (:language :stdc) (:return-type double-float) (:arguments (len int) (vec (FFI:C-ARRAY-PTR double-float)))) (sum 3 #(1d0 2d0 3d0)) ⇒6d0
You can find more information and examples of the CLISP
 “FFI” in the following <clisp-list@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-list) messages:
 
SFmail/5736140,
     Gmane/general/7278SFmail/4062459,
     Gmane/general/6626Even more examples can be found in the file
 tests/ffi.tst
 in the CLISP source distribution.
Sockets are used for interprocess communications by processes running on the same host as well as by processes running on different hosts over a computer network. The most common kind of sockets is Internet stream sockets, and a high-level interface to them is described here. A more low level interface that closely follows the C system calls is also available, see Section 33.17, “Raw Socket Access”.
Two main varieties of sockets are interfaced to:
SOCKET:SOCKET-STREAMs which are bidirectional STREAMs
  SOCKET:SOCKET-SERVERs which are a special kind of objects that are used
    to allow the other side to initiate interaction with lisp.
Example 32.12. Lisp read-eval-print loop server
Here is a simple lisp read-eval-print loop server that waits for a remote connection and evaluates forms read from it:
(LET((server (SOCKET:SOCKET-SERVER))) (FORMATt "~&Waiting for a connection on ~S:~D~%" (SOCKET:SOCKET-SERVER-HOSTserver) (SOCKET:SOCKET-SERVER-PORTserver)) (UNWIND-PROTECT;; infinite loop, terminate with Control+C (LOOP(WITH-OPEN-STREAM(socket (SOCKET:SOCKET-ACCEPTserver)) (MULTIPLE-VALUE-BIND(local-host local-port) (SOCKET:SOCKET-STREAM-LOCALsocket) (MULTIPLE-VALUE-BIND(remote-host remote-port) (SOCKET:SOCKET-STREAM-PEERsocket) (FORMATT"~&Connection: ~S:~D -- ~S:~D~%" remote-host remote-port local-host local-port))) ;; loop is terminated when the remote host closes the connection or onEXT:EXIT(LOOP(WHEN(EQ:eof (SOCKET:SOCKET-STATUS(cons socket :input))) (RETURN)) (EVAL(READsocket)) socket) ;; flush everything left in socket (LOOP:for c = (READ-CHAR-NO-HANGsocket nil nil) :while c) (TERPRIsocket)))) ;; make sure server is closed (SOCKET:SOCKET-SERVER-CLOSEserver)))
Functions like EXT:SHELL, EXT:EXECUTE, EXT:RUN-SHELL-COMMAND will allow the
  remote host to execute arbitrary code with your permissions.
  While functions defined in lisp (like EXT:RUN-SHELL-COMMAND) can be removed
  (using FMAKUNBOUND), the built-in functions (like EXT:SHELL and EXT:EXECUTE)
  cannot be permanently removed from the run-time, and an experienced
  hacker will be able to invoke them even if you FMAKUNBOUND their names.
 
You should limit the socket server to local
  connections by passing string "127.0.0.1"
  as the :INTERFACE argument.
Example 32.13. Lisp HTTP client
Here are a couple of simple lisp HTTP clients that fetch a web page and a binary file, and upload a file:
(DEFUNwget-text (host page file&OPTIONAL(port 80)) ;; HTTP requires the:DOSline terminator (WITH-OPEN-STREAM(socket (SOCKET:SOCKET-CONNECTport host:EXTERNAL-FORMAT:DOS)) (FORMATsocket "GET ~A HTTP/1.0~2%" page) ;; dump the whole thing - header+data - into the output file (WITH-OPEN-FILE(out file :direction :output) (LOOP:for line = (READ-LINEsocket nil nil) :while line :do (WRITE-LINEline out))))) (DEFUNwget-binary (host page file&OPTIONAL(port 80)) (WITH-OPEN-STREAM(socket (SOCKET:SOCKET-CONNECTport host:EXTERNAL-FORMAT:DOS)) (FORMATsocket "GET ~A HTTP/1.0~2%" page) (LOOP:with content-length :for line = (READ-LINEsocket nil nil) ;; header is separated from the data with a blank line :until (ZEROP(LENGTHline)) :do (WHEN(STRING=line #1="Content-length: " :end1 #2=#.(LENGTH#1#)) (SETQcontent-length (PARSE-INTEGERline :start #2#)) ;; this will not work if the server does not supply the content-length header :finally (RETURN(LET((data (MAKE-ARRAYcontent-length :element-type '())) ;; switch to binary i/o on socket (UNSIGNED-BYTE8)SETF(STREAM-ELEMENT-TYPEsocket) '() ;; read the whole file in one system call (UNSIGNED-BYTE8)EXT:READ-BYTE-SEQUENCEdata socket) (WITH-OPEN-FILE(out file :direction :output:ELEMENT-TYPE'() ;; write the whole file in one system call (UNSIGNED-BYTE8)EXT:WRITE-BYTE-SEQUENCEdata out)) data)))))) (DEFUNwput (host page file&OPTIONAL(port 80)) (WITH-OPEN-STREAM(socket (SOCKET:SOCKET-CONNECTport host:EXTERNAL-FORMAT:DOS)) (WITH-OPEN-FILE(in file :direction :inptut:ELEMENT-TYPE'() (UNSIGNED-BYTE8)LET*((length (FILE-LENGTHin)) (data (MAKE-ARRAYlength :element-type '())) ;; some servers may not understand the "Content-length" header (UNSIGNED-BYTE8)FORMATsocket "PUT ~A HTTP/1.0~%Content-length: ~D~2%" page length) (SETF(STREAM-ELEMENT-TYPEsocket) '() (UNSIGNED-BYTE8)EXT:READ-BYTE-SEQUENCEdata in) (EXT:WRITE-BYTE-SEQUENCEdata socket))) ;; not necessary if the server understands the "Content-length" header (SOCKET:SOCKET-STREAM-SHUTDOWNsocket :output) ;; get the server response (LOOP:for line = (READ-LINEsocket nil nil) :while line :collect line)))
(SOCKET:SOCKET-SERVER &OPTIONAL port
     &KEY :INTERFACE
     :BACKLOG)FIXNUM).
    The :BACKLOG parameter defines maximum length
    of queue of pending connections (see
    listen) and defaults to 1.
    The :INTERFACE is either a STRING,
    interpreted as the IP address that will be bound, or a socket, from
    whose peer the connections will be made.
    Default is (for backward compatibility) to bind to all local
    interfaces, but for security reasons it is advisable to bind to
    loopback "127.0.0.1" if you need only
    local connections.(SOCKET:SOCKET-SERVER-CLOSE socket-server)SOCKET:SOCKET-SERVERs are closed at garbage-collection.  You should not rely on
    this however, because garbage-collection times are not deterministic.
 (SOCKET:SOCKET-SERVER-HOST socket-server)(SOCKET:SOCKET-SERVER-PORT socket-server)SOCKET:SOCKET-SERVER.
 (SOCKET:SOCKET-WAIT
    socket-server &OPTIONAL [seconds [microseconds]])socket-server (a SOCKET:SOCKET-SERVER).
    Without a timeout argument, SOCKET:SOCKET-WAIT blocks indefinitely.
    When timeout is zero, poll.
    Returns T when a connection is available (i.e., SOCKET:SOCKET-ACCEPT will
    not block) and NIL on timeout.(SOCKET:SOCKET-ACCEPT socket-server
    &KEY :ELEMENT-TYPE :EXTERNAL-FORMAT :BUFFERED :TIMEOUT)SOCKET:SOCKET-STREAM for the connection.
   Waits for an attempt to connect to the server for no more than
   :TIMEOUT seconds (which may be a non-negative REAL or a
   list (sec usec) or a pair
   (sec . usec)).
   SIGNALs an ERROR if no connection is made in that time.
  (SOCKET:SOCKET-CONNECT
    port &OPTIONAL [host] &KEY
    :ELEMENT-TYPE :EXTERNAL-FORMAT :BUFFERED :TIMEOUT)SOCKET:SOCKET-STREAM.  Blocks until the server accepts the connection, for
   no more than :TIMEOUT seconds.  If it is 0, returns immediately
   and (probably) blocks on the next i/o operation (you can use
   SOCKET:SOCKET-STATUS to check whether it will actually block).
 (SOCKET:SOCKET-STATUS
                 socket-stream-or-list
                 &OPTIONAL [seconds [microseconds]])Checks whether it is possible to read from or write
    to a SOCKET:SOCKET-STREAM or whether a connection is available on a
    SOCKET:SOCKET-SERVER without blocking.
This is similar to LISTEN, which checks only one
    STREAM and only for input, and SOCKET:SOCKET-WAIT, which works only with
    SOCKET:SOCKET-SERVERs.
We define status for a SOCKET:SOCKET-SERVER or a SOCKET:SOCKET-STREAM
    to be :ERROR if any i/o operation will cause an ERROR.
Additionally, for a SOCKET:SOCKET-SERVER, we define
    status to be T if a connection is available, i.e.,
    is SOCKET:SOCKET-ACCEPT will not block, and NIL otherwise.
Additionally, for a SOCKET:SOCKET-STREAM, we define status in the
    given direction (one of :INPUT, :OUTPUT, and :IO) to be
    
Possible status values for various directions:
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| 
 | 
Possible values of
     socket-stream-or-list:
SOCKET:SOCKET-STREAM or SOCKET:SOCKET-SERVER:IO status for SOCKET:SOCKET-STREAM)
    (SOCKET:SOCKET-STREAM . direction)MAPCAR)If you want to avoid consing[3] up a fresh list, you can
    make the elements of socket-stream-or-list
    to be ( or socket-stream direction .
     x)(.
    Then socket-server . x)SOCKET:SOCKET-STATUS will destructively modify its argument and replace
    x or NIL with the status and return the modified list.
    You can pass this modified list to SOCKET:SOCKET-STATUS again.
The optional arguments specify the timeout. NIL means
    wait forever, 0 means poll.
The second value returned is the number of objects with
    non-NIL status, i.e., “actionable” objects.
    SOCKET:SOCKET-STATUS returns either due to a timeout or when this number is
    positive, i.e., if the timeout was NIL and SOCKET:SOCKET-STATUS did
    return, then the second value is positive (this is the reason NIL
    is not treated as an empty LIST, but as an invalid
    argument).
This is the interface to select
    (on some platforms, poll),
    so it will work on any CLISP STREAM which is based on a
    file descriptor, e.g., EXT:*KEYBOARD-INPUT* and file/pipe/socket STREAMs, as well as
    on raw sockets.
(SOCKET:SOCKET-STREAM-HOST socket-stream)(SOCKET:SOCKET-STREAM-PORT socket-stream)SOCKET:SOCKET-STREAM.(SOCKET:SOCKET-STREAM-PEER
    socket-stream [do-not-resolve-p])Given a SOCKET:SOCKET-STREAM, this function returns the
    name of the host on the opposite side of the connection and its port
    number; the server-side can use this to see who connected.
When the optional second argument is non-NIL, the hostname
    resolution is disabled and just the IP address is returned, without
    the FQDN.
 
The socket-stream argument can also be a
                       raw socket.
(SOCKET:SOCKET-STREAM-LOCAL
    socket-stream [do-not-resolve-p])The dual to SOCKET:SOCKET-STREAM-PEER - same information,
   host name and port number, but for the local host.
   The difference from SOCKET:SOCKET-STREAM-HOST and SOCKET:SOCKET-STREAM-PORT is that this function
   asks the OS (and thus returns the correct trusted values) while the
   other two are just accessors to the internal data structure, and
   basically return the arguments given to the function which created
   the socket-stream.
The socket-stream argument can also be a
                       raw socket.
(SOCKET:SOCKET-STREAM-SHUTDOWN socket-stream
    direction)Some protocols provide for closing the connection
   in one direction using shutdown.
   This function provides an interface to this UNIX system call.
   direction should be :INPUT or :OUTPUT.  Note that you
   should still call CLOSE after you are done with your socket-stream; this
   is best accomplished by using WITH-OPEN-STREAM.
All SOCKET:SOCKET-STREAMs are bidirectional STREAMs (i.e., both INPUT-STREAM-P
   and OUTPUT-STREAM-P return T for them).
   SOCKET:SOCKET-STREAM-SHUTDOWN breaks this and turns its argument
   stream into an input STREAM (if direction is :OUTPUT) or output STREAM (if
   direction is :INPUT).
    Thus, the following important invariant is preserved: whenever
   
STREAM is open
    (i.e., OPEN-STREAM-P returns T) andSTREAM is an input STREAM (i.e., INPUT-STREAM-P
     returns T)
   the STREAM can be read from (e.g., with READ-CHAR or READ-BYTE).
   
The socket-stream argument can also be a
                       raw socket.
(SOCKET:SOCKET-OPTIONS socket-server &REST
    {option}*)Query and, optionally, set socket options using
   getsockopt
   and setsockopt.
   An option is a keyword, optionally followed by the new value.
   When the new value is not supplied,
   setsockopt is not called.
   For each option the old (or current, if new value was not supplied)
   value is returned.  E.g., ( returns 2 values: SOCKET:SOCKET-OPTIONS socket-server
   :SO-LINGER 1 :SO-RCVLOWAT)NIL, the old
   value of the :SO-LINGER option, and 1, the
   current value of the :SO-RCVLOWAT option.
  
The socket-stream argument can also be a
                       raw socket.
(SOCKET:STREAM-HANDLES
    stream)stream as multiple values.  See Section 33.17, “Raw Socket Access”.
 This section describes three ways to turn CLISP programs into executable programs, which can be started as quickly as executables written in other languages.
CONFIG_BINFMT_MISC=y#P".fas"
    and #P".lisp" with CLISP; then you can make the
    files executable and run them from the command line.
 These three techniques apply to a single #P".lisp" or
  #P".fas" file.  If your application is made up of several
  #P".lisp" or #P".fas" files, you can simply concatenate them
  (using cat) into one file; the
  techniques then apply to that concatenated file.
These three techniques assume that the target machine has CLISP pre-installed and thus you can deliver just your own application, not CLISP itself. If you want to deliver applications without assuming anything about your target box, you have to resort to creating executable memory images.
On UNIX, a text file (#P".fas" or #P".lisp") can
 be made executable by adding a first line of the form
 
#!interpreter[interpreter-arguments]
and using chmod to make the file executable.
OS Requirements. CLISP can be used as a script interpreter under the following conditions:
interpreter must be the full pathname of CLISP.
 The recommended path is /usr/local/bin/clisp,
 and if CLISP is actually installed elsewhere, making
 /usr/local/bin/clisp be a symbolic link to the
 real CLISP.interpreter must be a real executable, not a script.
 Unfortunately, in the binary distributions of CLISP on Solaris,
 clisp is a shell script because a C compiler cannot be
 assumed to be installed on this platform.  If you do have a C
 compiler installed, build CLISP from the source yourself;
 make install will install clisp as
 a real executable.On some platforms, the first line which specifies the interpreter is limited in length:
Characters exceeding this limit are simply cut off by the system. At least 128 characters are accepted on Solaris, IRIX, AIX, OSF/1. There is no workaround: You have to keep the interpreter pathname and arguments short.
interpreter-arg is passed to the interpreter.
 In order to pass more than one option (for example, -M and
 -C) to CLISP, separate them with
 no-break
 spaces instead of normal spaces.  (But the separator between
 interpreter and interpreter-arguments must still be a normal space!) CLISP
 will split the interpreter-arguments both at no-break spaces and at normal spaces.
#! line.LOAD (in particular, the name of the script file, which
   is $0 in /bin/sh, can be found in *LOAD-TRUENAME* and
   *LOAD-PATHNAME*).EXT:*ARGS* is bound
   to a LIST of STRINGs, representing the arguments given to the
   Lisp script (i.e., $1 in /bin/sh becomes (FIRST
     EXT:*ARGS*) etc).stdio.h>) are used:
    *STANDARD-INPUT* is bound to stdin,
    *STANDARD-OUTPUT* to stdout, and
    *ERROR-OUTPUT* to stderr.
    Note Section 25.2.13.1, “Scripting and DRIBBLE”.ERRORs will be turned into WARNINGs
   (using EXT:APPEASE-CERRORS).ERRORs and
   Control+C interrupts will
   terminate the execution of the Lisp script with an error status
   (using EXT:EXIT-ON-ERROR).-C to the interpreter-arguments.
 See also the manual.
If nothing works. Another, quite inferior, alternative is to put the following into a file:
#!/bin/sh exec clisp <<EOF (lisp-form) (another-lisp-form) (yet-another-lisp-form) EOF
The problem with this approach is that the return values of each form
will be printed to *STANDARD-OUTPUT*.
Another problem is that no user input will be available.
Although we use Win32-specific notation, these techniques work on other desktop environments as well.
There are two different ways to make CLISP “executables” on desktop platforms.
Then clicking on the compiled lisp file (with #P".fas"
 extension) will load the file (thus executing all the code in the
 file), while the clicking on a CLISP memory image (with #P".mem"
 extension) will start CLISP with the given memory image.
On Win32, CLISP is distributed with a file
 src/install.bat, which
 runs src/install.lisp to create a
 file clisp.lnk on your desktop and also associates
 #P".fas", #P".lisp", and #P".mem" files with CLISP.
You have to build your kernel with
 CONFIG_BINFMT_MISC=y and
 CONFIG_PROC_FS=y.  Then you will have a
 /proc/sys/fs/binfmt_misc/ directory and you will
 be able to do (as root; you might want to put
 these lines into /etc/rc.d/rc.local):
#echo ":CLISP:E::fas::/usr/local/bin/clisp:" >> /proc/sys/fs/binfmt_misc/register#echo ":CLISP:E::lisp::/usr/local/bin/clisp:" >> /proc/sys/fs/binfmt_misc/register
Then you can do the following:
$cat << EOF > hello.lisp (print "hello, world!") EOF$clisp -c hello.lisp ;; Compiling file hello.lisp ... ;; Wrote file hello.lisp 0 errors, 0 warnings$chmod +x hello.fas$hello.fas "hello, world!"$
Please read
 
  /usr/src/linux/Documentation/binfmt_misc.txt
 for details.
This section describes how CLISP can invoke external executables and communicate with the resulting processes.
(EXT:EXECUTE program
       arg1
       arg2 ...)
   executes an external program.
   Its name is program (a full pathname).
   It is given the STRINGs arg1,
   arg2, ... as arguments.
 (EXT:SHELL [command])
   calls the operating system's shell, the value of the environment variable
   SHELL on UNIX and COMSPEC on Win32.
   (EXT:SHELL) calls the shell for interactive use.
   (EXT:SHELL command) calls the shell
   only for execution of the one given command.
 The functions EXT:RUN-SHELL-COMMAND and EXT:RUN-PROGRAM are the
   general interface to EXT:SHELL and the above:
(
   runs a shell command (including shell built-in commands,
   like DIR on Win32
   and for/do/done on UNIX).EXT:RUN-SHELL-COMMAND command &KEY
    :MAY-EXEC :INDIRECTP
    :INPUT :OUTPUT :IF-OUTPUT-EXISTS :WAIT)
(
   runs an external program.EXT:RUN-PROGRAM program &KEY
    :MAY-EXEC :INDIRECTP
    :ARGUMENTS :INPUT :OUTPUT :IF-OUTPUT-EXISTS :WAIT)
commandthe shell command.
SHELL, which normally is /bin/sh.
       The command should be a “simple command”;
       a “command list” should be enclosed in "{
       ... ; }" (for /bin/sh) or "( ... )" (for /bin/csh).
     programPATH will be searched for it.
    :ARGUMENTSSTRINGs) that are given
      to the program.:INPUT:TERMINAL (stdin, the default) or
     :STREAM (a Lisp STREAM to be created) or
     a pathname designator (an input file) or NIL (no input at all).
   :OUTPUT:TERMINAL (stdout, the default) or
     :STREAM (a Lisp STREAM to be created) or
     a pathname designator (an output file) or NIL (ignore the output).
   :IF-OUTPUT-EXISTS:OUTPUT file already exists.
     The possible values are :OVERWRITE, :APPEND, :ERROR,
     with the same meaning as for OPEN. The default is :OVERWRITE.
    :WAITT, i.e., synchronous execution.
    :MAY-EXEC:INDIRECTP(EXT:RUN-PROGRAM "dir" :indirectp T)
    will run the shell built-in command DIR.
    This argument defaults to T for EXT:RUN-SHELL-COMMAND and to NIL for EXT:RUN-PROGRAM.
    (Win32 only).If :STREAM was specified for :INPUT or :OUTPUT, a Lisp
 STREAM is returned.
 If :STREAM was specified for both :INPUT and :OUTPUT, three
 Lisp STREAMs are returned, as for the function EXT:MAKE-PIPE-IO-STREAM.
 Otherwise, the return value depends on the process termination
 status: if it ended normally (without signal, core-dump etc), its exit
 status is returned as an INTEGER, otherwise NIL is returned.
This use of EXT:RUN-PROGRAM can cause
 deadlocks, see EXT:MAKE-PIPE-IO-STREAM.
(EXT:MAKE-PIPE-INPUT-STREAM command &KEY :ELEMENT-TYPE
    :EXTERNAL-FORMAT :BUFFERED)STREAM that will supply the output
   from the execution of the given operating system command.
(EXT:MAKE-PIPE-OUTPUT-STREAM command &KEY :ELEMENT-TYPE
   :EXTERNAL-FORMAT :BUFFERED)STREAM that will pass its output as
   input to the execution of the given operating system command.
(EXT:MAKE-PIPE-IO-STREAM command &KEY :ELEMENT-TYPE
   :EXTERNAL-FORMAT :BUFFERED)returns three values.
  The primary value is a bidirectional STREAM that will simultaneously pass its output
  as input to the execution of the given operating system command and
  supply the output from this command as input.
  The second and third value are the input STREAM and the output STREAM that
  make up the bidirectional STREAM, respectively.
These three streams must be closed individually, see CLOSE-CONSTRUCTED-STREAM:ARGUMENT-STREAM-ONLY.
Improper use of this function can lead to deadlocks. Use it at your own risk!
A deadlock occurs if the command and your Lisp program either both try to read from each other at the same time or both try to write to each other at the same time.
To avoid deadlocks, it is recommended that you fix a
   protocol between the command and your program and avoid any hidden
   buffering: use READ-CHAR, READ-CHAR-NO-HANG, LISTEN,
   SOCKET:SOCKET-STATUS instead of READ-LINE and READ on the input side, and
   complete every output operation by a FINISH-OUTPUT.
   The same precautions must apply to the called command as well.
The macro
 EXT:WITH-OUTPUT-TO-PRINTER:
(EXT:WITH-OUTPUT-TO-PRINTER(variable[:EXTERNAL-FORMAT]) {declaration}* {form}*)
 binds the variable variable to an output STREAM
 that sends its output to the printer.
Most modern operating systems support environment variables that associate
 strings (“variables”) with other strings
 (“values”).  These variables are somewhat similar to the
 SPECIAL variables in Common Lisp: their values are inherited by the
 processes from their parent process.
You can access your OS environment variables using the function
(,
where EXT:GETENV &OPTIONAL string)string is the name of the environment variable.
When string is omitted or NIL, all the environment variables and their values
are returned in an association list.
You can change the value of existing environment variables or create new ones
 using (.
SETF (EXT:GETENV string) new-value)
Table of Contents
The “POSIX” module makes some system calls available from lisp. Not all of these system calls are actually POSIX, so this package has a nickname “OS”.
This module is present in the base linking set by default.
When this module is present, *FEATURES*
 contains the symbol :SYSCALLS.
(POSIX:RESOLVE-HOST-IPADDR
    &OPTIONAL host)Returns the HOSTENT structure:
   When host is omitted or :DEFAULT, return the data for the
   current host. When host is NIL, all the
   host database is returned as a list (this would be the contents of the
   /etc/hosts file on a UNIX system or
   ${windir}/system32/etc/hosts on a Win32 system).
  
This is an interface
   to gethostent,
   gethostbyname,
   and gethostbyaddr.
 
(OS:SERVICE
    &OPTIONAL service-name
    protocol)service-name and protocol,
   or all services as a LIST if service-name
   is missing or NIL.(POSIX:FILE-STAT
    pathname &OPTIONAL link-p)Return the FILE-STAT structure.
   pathname can be a STREAM, a PATHNAME, a STRING or a
   NUMBER (on a UNIX system, meaning file descriptor).
   The first slot of the structure returned is the string or the
   number on which stat,
   fstat,
   or lstat was called.
   The other slots are numbers, members of the struct stat:
    
devinomodenlinkuidgidrdevsizeatimemtimectimeblksizeblocksAll slots are read-only.
If the system does not support a particular field (e.g.,
    Win32 prior to 2000 does not have hard links), NIL (or the
    default, like 1 for the number of hard links for old Win32) is
    returned.
Normally, one would expect (POSIX:FILE-STAT
      "foo") and (POSIX:FILE-STAT ( to
     return “similar” objects (OPEN "foo"))OPENing a file changes its
     access time though).  This is not the case on Win32,
     where stat
     works but fstat does not.
     Specifically, fstat requires
     an int argument of an unknown nature,
     and it is not clear how do deduce it from the Win32 file handle.
     Therefore, instead of always failing on open FILE-STREAM arguments,
     this function calls
     GetFileInformationByHandle and
     fills the FILE-STAT return value based on that.
 
(POSIX:SET-FILE-STAT pathname
    &KEY :ATIME :MTIME :MODE :UID :GID)chmod,
    chown,
    and utime.
 (POSIX:STAT-VFS
    pathname)Return a STAT-VFS structure.
   pathname can be a STREAM, a PATHNAME, a STRING or a
   NUMBER (on a UNIX system, meaning file descriptor).
   The first slot of the structure returned is the string
   or the number on which statvfs or
   fstatvfs was called.
   The other slots are members of the struct statvfs:
   
bsizefrsizeblocksfrsize.bfreebavailfilesffreefavailfsidflag:READ-ONLY.
    namemaxvol-namefs-typeAll slots are read-only.
(OS:FILE-INFO
    pathname &OPTIONAL all)Return the FILE-INFO structure.
    pathname should be a pathname designator. The 7 slots are
| attributes | 
| ctime | 
| atime | 
| wtime | 
| size | 
| name | 
| name-short | 
When pathname is wild, returns just the first match,
    unless the second (optional) argument is non-NIL, in which case a
    LIST of objects is returned, one for each match.
 
(POSIX:USER-INFO
    &OPTIONAL user)Return the USER-INFO structure (name,
   encoded password, UID, GID, full name, home directory, shell).
   user should be a STRING
   (getpwnam is used) or an INTEGER
   (getpwuid is used).
   When user is missing or NIL, return all
   users (using getpwent).
   When user is :DEFAULT, return the information about the current user
   (using getlogin
   or getuid).
Platform Dependent: UNIX platform only.
(POSIX:GROUP-INFO
    &OPTIONAL group)Return the GROUP-INFO structure (name,
   GID, member LIST). group should be a
   STRING (getgrnam is used) or an
   INTEGER (getgrgid is used).
   When group is missing or NIL, return all
   groups (using getgrent).
Platform Dependent: UNIX platform only.
(POSIX:UNAME)uname.(POSIX:SYSCONF
    &OPTIONAL what)(POSIX:CONFSTR
    &OPTIONAL what)what is missing or
    NIL), by calling sysconf
    and confstr respectively.
 (POSIX:PATHCONF
    pathname &OPTIONAL what)what is missing or
    NIL), by calling fpathconf on
    open file streams and pathconf on
    all other pathname designators.(POSIX:RLIMIT
    &OPTIONAL what)what is specified or the association list of all available
    limits (as an RLIMIT structure) when what is
    missing or NIL, by calling getrlimit.
 (SETF (POSIX:RLIMIT what)
    (VALUES cur max))(SETF (POSIX:RLIMIT what) rlimit)(SETF (POSIX:RLIMIT) rlimit-alist)Set the limits using
    setrlimit.
cur
       and max are numbers
       (or NIL for RLIM_INFINITY).rlimit
       is an RLIMIT structure.rlimit-alist is an association list, as returned by
       (POSIX:RLIMIT).(POSIX:USAGE)getrusage.
 (POSIX:ERF real)(POSIX:ERFC real)(POSIX:J0 real)(POSIX:J1 real)(POSIX:JN integer real)(POSIX:Y0 real)(POSIX:Y1 real)(POSIX:YN integer real)(POSIX:GAMMA real)(POSIX:LGAMMA real)Compute the error functions, Bessel functions and
   Gamma.  These functions are required by the POSIX standard and should
   be available in libm.so.
Please note that these functions do not provide
    lisp-style error handling and precision, and do all the computations
    at the DOUBLE-FLOAT level.
(POSIX:BOGOMIPS)(POSIX:LOADAVG &OPTIONAL
    percentp)getloadavg.
    If the argument is specified and non-NIL, the values are returned
    as integer percentiles.(POSIX:STREAM-LOCK stream
    lock-p &KEY
    (:BLOCK T) (:SHARED NIL) (:START 0) (:END NIL))Set or remove a file lock for the (portion of the)
    file associated with stream,
    depending on lock-p.
    When block is NIL, the call is non-blocking,
    and when locking fails, it returns NIL.
    When shared is non-NIL,
    then lock can be shared between several callers.
    Several processes can set a shared
    (i.e., read) lock, but only one can set
    an exclusive (i.e., write,
    or non-shared) lock.
    Uses fcntl
    or LockFileEx.
(POSIX:WITH-STREAM-LOCK (stream
    &REST options) &BODY body)stream, execute the body, unlock
    the stream.  Pass options to POSIX:STREAM-LOCK.
 (POSIX:STREAM-OPTIONS
    stream command &OPTIONAL value)fcntl,
    command can be :FD or :FL.
 (POSIX:MKNOD
    pathname type mode)mknod.
   Use :FIFO to create pipes
   and :SOCK to create sockets.
 (POSIX:CONVERT-MODE mode)0644)
    and symbolic (e.g., (:RUSR :WUSR :RGRP
     :ROTH)) file modes.(UMASK
    mode)umask.
 (POSIX:COPY-FILE source destination
    &KEY :METHOD :PRESERVE :IF-EXISTS :IF-DOES-NOT-EXIST)This is an interface to
    symlink
    (when method is :SYMLINK),
    link
    (when it is :HARDLINK),
    and rename
    (when it is :RENAME) system calls, as well as,
    you guessed it, a generic file copy utility (when method is :COPY).
   
Both source and destination may be wild, in which
    case TRANSLATE-PATHNAME is used.
(POSIX:DUPLICATE-HANDLE
    fd1 &OPTIONAL
    fd2)dup system calls on
    UNIX systems and to DuplicateHandle
    system call on Win32.(OS:SHORTCUT-INFO pathname)#P".lnk") file contents in a
    SHORTCUT-INFO structure.(OS:MAKE-SHORTCUT pathname &KEY
    :WORKING-DIRECTORY :ARGUMENTS :SHOW-COMMAND :ICON :DESCRIPTION
    :HOT-KEY :PATH)#P".lnk") file.
 (OS:SYSTEM-INFO)(OS:VERSION)(OS:MEMORY-STATUS)(OS:FILE-PROPERTIES filename set
    &KEY :INITID &ALLOW-OTHER-KEYS)Wrapper for the Win32
    IPropertyStorage functionality.
    
filenameset:BUILT-IN
        or :USER-DEFINED
     :INITID
       init-idinit-id
     specifier valuespecifierthe property specifier: an INTEGER,
            KEYWORD, STRING or a LIST of an INTEGER or a
            KEYWORD and a STRING.
            
INTEGERKEYWORDPredefined KEYWORD IDs are
                
| :APPNAME | :CREATE-DTM | :LASTPRINTED | :SUBJECT | 
| :AUTHOR | :DOC-SECURITY | :LASTSAVE-DTM | :TEMPLATE | 
| :CHARCOUNT | :EDITTIME | :LOCALE | :THUMBNAIL | 
| :CODEPAGE | :KEYWORDS | :PAGECOUNT | :TITLE | 
| :COMMENTS | :LASTAUTHOR | :REVNUMBER | :WORDCOUNT | 
STRINGINTEGER|KEYWORD
               STRING)
valuethe new value of the property, a suitable Lisp
            object, NIL or a LIST of a KEYWORD and the value
            itself.  If value is NIL, no assignment is done.
            :EMPTY and :NULL
            correspond to the VT_EMPTY
            and VT_NULL data types.
            KEYWORD in the LIST specifies the desired type of
            the property being set.
            Supported types are
| :BOOL | :I1 | :LPWSTR | :UI4 | 
| :BSTR | :I2 | :R4 | :UI8 | 
| :DATE | :I4 | :R8 | :UINT | 
| :ERROR | :I8 | :UI1 | |
| :FILETIME | :LPSTR | :UI2 | 
FILETIMEs are converted to/from the universal time format, while DATEs are not.
Returns the property contents before assignment as multiple values.
(POSIX:CRYPT key
    salt)crypt,
    arguments are STRINGs.(POSIX:ENCRYPT block
    decrypt-p)(POSIX:SETKEY key)encrypt
    and setkey, respectively.
    block and key are of type
    (VECTOR (UNSIGNED-BYTE 8) 8).
    decrypt-p is BOOLEAN.
 (OS:PHYSICAL-MEMORY)Return 2 values: total and available physical memory.
(OS:FILE-OWNER
    filename)Return the owner of the file.
(OS:PRIORITY pid
    &OPTIONAL what)Return the process priority, platform-dependent
    INTEGER or platform-independent SYMBOL, one of
    
| :REALTIME | :NORMAL | :IDLE | 
| :HIGH | :BELOW-NORMAL | |
| :ABOVE-NORMAL | :LOW | 
    On UNIX calls getpriority, on
    Win32 calls GetPriorityClass.
SETFable using setpriority and
    SetPriorityClass.
 
(OS:PROCESS-ID)getpid,
    on Win32 calls GetCurrentProcessId)
 (POSIX:OPENLOG ident &KEY
    :PID :CONS :NDELAY :ODELAY :NOWAIT :FACILITY)openlog
 (POSIX:SETLOGMASK
    maskpri)setlogmask
 (POSIX:SYSLOG severity facility
    format-string &REST arguments)calls syslog on
    (APPLY FORMAT NIL format-string arguments)
No % conversion is performed,
    you must do all formatting in Lisp.
(POSIX:CLOSELOG)closelog
 (POSIX:KILL pid signal)kill
 (POSIX:GETPGRP pid)getpgrp
 (POSIX:SETPGRP)setpgrp;
    on non-POSIX systems where it requires 2 arguments (legacy
    BSD-style), it is called as setpgrp(0,0)
 (POSIX:GETSID pid)getsid
 (POSIX:SETSID)setsid
 (POSIX:SETPGID
    pid pgid)setpgid
 (POSIX:ENDUTXENT)endutxent
 (POSIX:GETUTXENT
    &OPTIONAL utmpx)getutxent,
    returns a STRUCTURE-OBJECT of
    type POSIX:UTMPX, which can be passed to subsequent calls to
    this function and re-used.(POSIX:GETUTXID id)getutxid,
    the argument is filled and returned(POSIX:GETUTXLINE line)getutxline,
    the argument is filled and returned(POSIX:PUTUTXLINE
    utmpx)pututxline,
    the argument is filled and returned(POSIX:SETUTXENT)setutxent
 (POSIX:GETUID)(SETF (POSIX:GETUID) uid)getuid and
   setuid.(POSIX:GETGID)(SETF (POSIX:GETGID) gid)getgid and
   setgid.(POSIX:GETEUID)(SETF (POSIX:GETEUID) uid)geteuid and
   seteuid.(POSIX:GETEGID)(SETF (POSIX:GETEGID) gid)getegid and
   setegid.(OS:STRING-TIME format-string
    &OPTIONAL object timezone)object is a STRING, is is parsed
    according to format-string by strptime.
    When it is an INTEGER, it is formatted according to format-string
    by strftime.
    object defaults to (GET-UNIVERSAL-TIME).
 (POSIX:MKSTEMP filename
    &KEY :DIRECTION :ELEMENT-TYPE :EXTERNAL-FORMAT :BUFFERED)calls mkstemp,
    returns a FILE-STREAM.
:DIRECTION should allow output.
When mkstemp is missing,
    use tempnam.
    On Win32 use GetTempFileName.
 
(POSIX:MKDTEMP
    filename)mkdtemp
    (similar to mkstemp but not in POSIX),
    returns the namestring of a new empty temporary directory.
 (POSIX:SYNC &OPTIONAL
    stream)fsync
    (FlushFileBuffers on Win32)
    on the file descriptor associated with stream,
    or sync
    when stream is not suppliedPOSIX:MAKE-XTERM-IO-STREAM &KEY title)When running under the X Window System, you can create a bidirectional STREAM,
    which uses a new dedicated xterm, using the function POSIX:MAKE-XTERM-IO-STREAM:
(SETQ*ERROR-OUTPUT*(SETQ*DEBUG-IO*(POSIX:MAKE-XTERM-IO-STREAM:title "clisp errors and debug")))
Platform Dependent: UNIX platform only.
POSIX:FFS n)ffs, but implemented in Lisp and
    supports BIGNUMs.GNU gettext is a set of functions, included in CLISP or the C library, which permit looking up translations of strings through message catalogs. It is also a set of tools which makes the translation maintenance easy for the translator and the program maintainer.
The GNU gettext functions are available in CLISP in the
“I18N” package, which is EXT:RE-EXPORTed from the “EXT”
package.
This module is present in the base linking set by default.
When this module is present, *FEATURES*
 contains the symbol :I18N.
(I18N:GETTEXT
    MSGID &OPTIONAL DOMAIN CATEGORY)MSGID,
    in the given DOMAIN, depending on the given CATEGORY.
    MSGID should be an ASCII string, and is normally the English message.
 (I18N:NGETTEXT
    MSGID msgid_plural
    n &OPTIONAL DOMAIN CATEGORY)MSGID and n in the given DOMAIN, depending on the given
    CATEGORY.  MSGID and msgid_plural
    should be ASCII strings, and are normally the English singular and
    English plural variant of the message, respectively.
 The DOMAIN is a string identifier denoting the program that
is requesting the translation.  The pathname of the message catalog
depends on the DOMAIN: usually it is located at
TEXTDOMAINDIR/l/LC_MESSAGES/domain.mo, where
l is the ISO
 639-2 code of the language.
The notion of DOMAIN allows several Lisp programs running in the same
image to request translations independently of each other.
Function I18N:TEXTDOMAIN. ( is a place that returns the default
 I18N:TEXTDOMAIN)DOMAIN, used when no DOMAIN argument is passed to the I18N:GETTEXT and
 I18N:NGETTEXT functions.  It is SETFable.
( is usually used
during the startup phase of a program.
Note that the default SETF I18N:TEXTDOMAIN)DOMAIN is not saved in a memory image.
The use of ( is
recommended only for programs that are so simple that they will never
need more than one SETF I18N:TEXTDOMAIN)DOMAIN.
Function I18N:TEXTDOMAINDIR. (
is a place that returns the base directory, called
I18N:TEXTDOMAINDIR DOMAIN)TEXTDOMAINDIR above, where the message
catalogs for the given DOMAIN are assumed to be installed.
It is SETFable.
( is usually used
during the startup phase of a program, and should be used because only
the program knows where its message catalogs are installed.
Note that the SETF I18N:TEXTDOMAINDIR)TEXTDOMAINDIRs
are not saved in a memory image.
The CATEGORY argument of the I18N:GETTEXT and I18N:NGETTEXT
functions denotes which LOCALE facet the result should depend on.
The possible values are a platform-dependent subset of
:LC_ADDRESS, :LC_ALL, :LC_COLLATE, :LC_CTYPE, :LC_IDENTIFICATION, :LC_MEASUREMENT, :LC_MESSAGES, :LC_MONETARY, :LC_NAME, :LC_NUMERIC, :LC_PAPER, :LC_TELEPHONE, :LC_TIME
The use of these values is useful for users who have a
character/time/collation/money handling set differently from the usual
message handling.
Note that when a CATEGORY argument is used, the message catalog
location depends on the CATEGORY: it will be expected at
TEXTDOMAINDIR/ll/category/domain.mo.
A non-internationalized program simulating a restaurant dialogue might look as follows.
(setq n (parse-integer (first EXT:*ARGS*)))
(format t "~A~%" "'Your command, please?', asked the waiter.")
(format t "~@?~%"
          (if (= n 1) "a piece of cake" "~D pieces of cake")
          n)
After being internationalized, all strings are wrapped in
I18N:GETTEXT calls, and I18N:NGETTEXT is used for plurals.
Also, I18N:TEXTDOMAINDIR is assigned a value; in our case, for simplicity,
the current directory.
(setf (textdomain) "prog")
(setf (textdomaindir "prog") "./")
(setq n (parse-integer (first EXT:*ARGS*)))
(format t "~A~%"
          (gettext "'Your command, please?', asked the waiter."))
(format t "~@?~%"
          (ngettext "a piece of cake" "~D pieces of cake" n)
          n)
For ease of reading, it is customary to define an abbreviation
for the I18N:GETTEXT function.  An underscore is customary.
(setf (textdomaindir "prog") "./")
(defun _ (msgid) (gettext msgid "prog"))
(setq n (parse-integer (first EXT:*ARGS*)))
(format t "~A~%"
          (_"'Your command, please?', asked the waiter."))
(format t "~@?~%"
          (ngettext "a piece of cake" "~D pieces of cake" n "prog")
          n)
Now the program's maintainer creates a message catalog template through the command
bash$ xgettext -o prog.pot prog.lisp
xgettext version 0.11 or higher is required here.
The message catalog template looks roughly like this.
msgid "'Your command, please?', asked the waiter." msgstr "" msgid "a piece of cake" msgid_plural "%d pieces of cake" msgstr[0] "" msgstr[1] ""
Then a French translator creates a French message catalog
msgid "" msgstr "" "Content-Type: text/plain; charset=ISO-8859-1\n" "Plural-Forms: nplurals=2; plural=(n > 1);\n" msgid "'Your command, please?', asked the waiter." msgstr "«Votre commande, s'il vous plait», dit le garçon." # Les gateaux allemands sont les meilleurs du monde. msgid "a piece of cake" msgid_plural "%d pieces of cake" msgstr[0] "un morceau de gateau" msgstr[1] "%d morceaux de gateau"
and sends it to the program's maintainer.
The program's maintainer compiles the catalog as follows:
bash$ mkdir -p ./fr/LC_MESSAGES bash$ msgfmt -o ./fr/LC_MESSAGES/prog.mo prog.fr.po
When a user in a french LOCALE then runs the program
bash$ clisp prog.lisp 2
she will get the output
    «Votre commande, s'il vous plait», dit le garçon.
    2 morceaux de gateau
(I18N:SET-LOCALE
   &OPTIONAL CATEGORY LOCALE)This is an interface to
   setlocale.
When LOCALE is missing or NIL, return the current one.
When CATEGORY is missing or NIL, return all categories
   as a LIST.
(I18N:LOCALE-CONV)This is an interface to
   localeconv.
Returns a I18N:LOCALE-CONV structure.
(I18N:LANGUAGE-INFORMATION
   &OPTIONAL item)This is an interface to
   nl_langinfo (UNIX)
   and GetLocaleInfo (Win32).
When item is missing or NIL,
   return all available information as a LIST.
The “REGEXP” module implements the
 POSIX regular expressions
by calling the standard C system facilities.
The syntax of these regular expressions is described in many places,
such as your local <regex.h> manual
and Emacs info pages.
This module is present in the base linking set by default.
When this module is present, *FEATURES*
 contains the symbol :REGEXP.
(REGEXP:MATCH pattern
   string &KEY (:START 0) :END :EXTENDED :IGNORE-CASE :NEWLINE :NOSUB
   :NOTBOL :NOTEOL)This macro returns as first value a REGEXP:MATCH structure
  containing the indices of the start and end of the first match for the
  regular expression pattern in string; or NIL if there is no match.
  Additionally, a REGEXP:MATCH structure is returned for every matched
  "\(...\)" group in pattern, in the
  order that the open parentheses appear in pattern.
  If start is non-NIL, the search starts at that index in string.
  If end is non-NIL, only ( is considered.
  SUBSEQ string start
  end)
Example 33.1. REGEXP:MATCH
(REGEXP:MATCH"quick" "The quick brown fox jumped quickly.") ⇒#S((REGEXP:MATCH:START 4 :END 9)REGEXP:MATCH"quick" "The quick brown fox jumped quickly." :start 8) ⇒#S((REGEXP:MATCH:START 27 :END 32)REGEXP:MATCH"quick" "The quick brown fox jumped quickly." :start 8 :end 30) ⇒(NILREGEXP:MATCH"\\([a-z]*\\)[0-9]*\\(bar\\)" "foo12bar") ⇒#S(; ⇒REGEXP:MATCH:START 0 :END 8)#S(; ⇒REGEXP:MATCH:START 0 :END 3)#S(REGEXP:MATCH:START 5 :END 8)
(REGEXP:MATCH-START match)(REGEXP:MATCH-END match)match; SETF-able.
(REGEXP:MATCH-STRING string match)string corresponding
   to the given pair of start and end indices of match.
   The result is shared with string.
   If you want a fresh STRING, use COPY-SEQ or
   COERCE to SIMPLE-STRING.(REGEXP:REGEXP-QUOTE
   string &OPTIONAL extended)This function returns a regular expression STRING
  that matches exactly string and nothing else.
  This allows you to request an exact string match when calling a
  function that wants a regular expression.
  
  One use of REGEXP:REGEXP-QUOTE is to combine an exact string match with
  context described as a regular expression.
  When extended is non-NIL, also
  quote #\+ and #\?.
(REGEXP:REGEXP-COMPILE
   string &KEY :EXTENDED :IGNORE-CASE :NEWLINE :NOSUB)string into an
  object suitable for REGEXP:REGEXP-EXEC.(REGEXP:REGEXP-EXEC
     pattern string &KEY (:START 0) :END
     :NOTBOL :NOTEOL)Execute the pattern, which must be a compiled
   regular expression returned by REGEXP:REGEXP-COMPILE, against the
   appropriate portion of the string.
Negative end means (+ (LENGTH
    string) end)
Returns REGEXP:MATCH structures as multiple values (one for each
   subexpression which successfully matched and one for the whole pattern),
   unless :BOOLEAN was non-NIL, in which case
   return T as an indicator of success, but do not allocate anything.
(REGEXP:REGEXP-SPLIT
     pattern string &KEY (:START 0) :END
     :EXTENDED :IGNORE-CASE :NEWLINE :NOSUB :NOTBOL :NOTEOL)string (all
  sharing the structure with string) separated by pattern (a
  regular expression STRING or a return value of REGEXP:REGEXP-COMPILE)
 (REGEXP:WITH-LOOP-SPLIT
     (variable stream pattern &KEY (:START 0) :END
     :EXTENDED :IGNORE-CASE :NEWLINE :NOSUB :NOTBOL :NOTEOL) &BODY body)stream, split them with
  REGEXP:REGEXP-SPLIT on pattern, and bind the resulting list to
  variable.:EXTENDED :IGNORE-CASE :NEWLINE :NOSUBregex.h> for their meaning.
:NOTBOL :NOTEOLregex.h> for their meaning.
REGEXP:REGEXP-MATCHERCUSTOM:*APROPOS-MATCHER*.
   This will work only when your LOCALE is CHARSET:UTF-8
   because CLISP uses CHARSET:UTF-8 internally and POSIX constrains
   <regex.h> to use the current LOCALE.
The following code computes the number of people who use a particular shell:
#!/usr/local/bin/clisp -C (DEFPACKAGE"REGEXP-TEST" (:use "LISP" "REGEXP")) (IN-PACKAGE"REGEXP-TEST") (let ((h (make-hash-table :test #'equal :size 10)) (n 0)) (with-open-file (f "/etc/passwd") (with-loop-split (s f ":") (incf (gethash (seventh s) h 0)))) (with-hash-table-iterator (i h) (loop (multiple-value-bind (r k v) (i) (unless r (return)) (format t "[~d] ~s~30t== ~5:d~%" (incf n) k v)))))
For comparison, the same can be done by the following Perl:
#!/usr/local/bin/perl -w
use diagnostics;
use strict;
my $IN = $ARGV[0];
open(INF,"< $IN") || die "$0: cannot read file [$IN]: $!\n;";
my %hash;
while (<INF>) {
  chop;
  my @all = split($ARGV[1]);
  my $shell = ($#all >= 6 ? $all[6] : "");
  if ($hash{$shell}) { $hash{$shell} ++; }
  else { $hash{$shell} = 1; }
}
my $ii = 0;
for my $kk (keys(%hash)) {
  print "[",++$ii,"] \"",$kk,"\"  --  ",$hash{$kk},"\n";
}
close(INF);
The “READLINE” module exports most of the GNU readline functions using “FFI”.
This module is present even in the base linking set by default on platforms where both GNU readline and “FFI” are available.
When this module is present, *FEATURES*
 contains the symbol :READLINE.
This is an interface to the GNU DataBase Manager.
When this module is present, *FEATURES* contains the
 symbol :GDBM.
See modules/gdbm/test.tst
 for sample usage.
GDBM module API
(GDBM:GDBM-VERSION)Return the version string.
(GDBM:GDBM-OPEN filename
    &KEY :BLOCKSIZE :READ-WRITE :OPTION :MODE :DEFAULT-KEY-TYPE
    :DEFAULT-VALUE-TYPE)Open filename database file.
    The return value is a GDBM structure.
    :READ-WRITE can have one of following values:
    
| :READER | 
| :WRITER | 
| :WRCREAT | 
| :NEWDB | 
    and :OPTION is one of
    
| :SYNC | 
| :NOLOCK | 
| :FAST | 
CLISP can store and retrieve values of the following types:
| STRING | 
| VECTOR(meaning anything that can beCOERCEd to() | 
| EXT:32BIT-VECTOR(meaning() | 
| INTEGER | 
| SINGLE-FLOAT | 
| DOUBLE-FLOAT | 
    and :DEFAULT-KEY-TYPE
    and :DEFAULT-VALUE-TYPE-TYPE should be one of
    those.  If not specified (or NIL), the :TYPE
    argument is required in the access functions below.
If filename is actually an existing GDBM structure,
    then it is re-opened (if it has been closed), and returned as is.
The return value is EXT:FINALIZEd with
    GDBM-CLOSE.
(GDBM:GDBM-DEFAULT-KEY-TYPE db)(GDBM:GDBM-DEFAULT-VALUE-TYPE db)Return the default data conversion types.
(GDBM:GDBM-CLOSE db)(GDBM:GDBM-OPEN-P db)Check whether db has been already closed.
(GDBM:GDBM-STORE db key contents &KEY
    :FLAG)db is the GDBM structure returned by
    GDBM-OPEN.
    key is the key datum.
    contents is the data to be associated with the key.
    :FLAG can have one of following values:
    
| :INSERT | 
| :REPLACE | 
(GDBM:GDBM-FETCH db key &KEY
    (TYPE (GDBM:GDBM-DEFAULT-VALUE-TYPE db))):TYPE argument specifies the return type.
 (GDBM:GDBM-DELETE db key)key and its contents.
 (GDBM:GDBM-EXISTS db key)(GDBM:GDBM-FIRSTKEY db &KEY
    (TYPE (GDBM:GDBM-DEFAULT-KEY-TYPE db))):TYPE.
    If the database has no entries, the return value is NIL.
 (GDBM:GDBM-NEXTKEY db key &KEY
    (TYPE (GDBM:GDBM-DEFAULT-KEY-TYPE db)))key, as :TYPE,
    or NIL if there are no further entries.
 (GDBM:GDBM-REORGANIZE db)(GDBM:GDBM-SYNC db)(GDBM:GDBM-SETOPT db option value)Set options on an already open database.
    option is one of following:
    
(GDBM:GDBM-FILE-SIZE db)lseek.(GDBM:DO-DB (key db &REST options)
    &BODY body)options are
    passed to GDBM-FIRSTKEY
    and GDBM-NEXTKEY.
    body is passed to LOOP, so you can use all the standard loop
    contructs, e.g., (do-db (k db) :collect (list k (gdbm-fetch
     k))) will convert the database to an association list.
 (GDBM:WITH-OPEN-DB (db filename &REST options)
    &BODY body)filename, execute the body, close
    the database.This interface to Berkeley DB from Sleepycat Software exports most functions in the official C API. Supported versions:
| 4.2 | 
| 4.3 | 
| 4.4 | 
| 4.5 | 
| 4.6 | 
When this module is present, *FEATURES* contains the
 symbol :BERKELEY-DB.
See modules/berkeley-db/test.tst
 for sample usage.
Thie module exports the following opaque STRUCTURE-OBJECT types:
 
 They contain the internal handle (a FFI:FOREIGN-POINTER), the LIST
 of parents, and the LIST of dependents.
CLOSE will close (or commit, in the case of a
 transaction, or
 put, in the case of a lock)
 the Berkeley-DB handle objects.  garbage-collector will also call CLOSE.
 Closing an object will CLOSE all its dependents and remove the object
 itself from the dependents lists of its parents (but see
 BDB:LOCK-CLOSE).
(BDB:DB-VERSION &OPTIONAL
    subsystems-too)Return version information as multiple values:
STRING
       (from db_version)FIXNUM)FIXNUM)FIXNUM)When the optional argument is non-NIL, returns the
    association list of the subsystem versions as the 5th value.
 
(BDB:DBE-CREATE &KEY
    PASSWORD ENCRYPT HOST CLIENT-TIMEOUT SERVER-TIMEOUT)db_env_create),
    possibly connecting to a remote host
    (DB_ENV->set_rpc_server)
    and possibly using encryption with password
    (DB_ENV->set_encrypt).
 (BDB:DBE-CLOSE dbe)DB_ENV->close).
    You can also call CLOSE.(BDB:DBE-MESSAGES dbe)(BDB:DBREMOVE dbe file
    database &KEY TRANSACTION AUTO-COMMIT)DB_ENV->dbremove).
 (BDB:DBREMOVE dbe file
    database newname &KEY TRANSACTION AUTO-COMMIT)DB_ENV->dbrename).
 (BDB:DBE-OPEN dbe &KEY
    FLAGS HOME JOIN INIT-CDB INIT-LOCK INIT-LOG INIT-MPOOL INIT-TXN
    RECOVER RECOVER-FATAL USE-ENVIRON USE-ENVIRON-ROOT CREATE
    LOCKDOWN PRIVATE SYSTEM-MEM THREAD MODE)DB_ENV->open).
    :FLAGS may be the value of a previous call
    to (BDB:DBE-GET-OPTIONS dbe :OPEN).
 (BDB:DBE-REMOVE dbe &KEY
    HOME FORCE USE-ENVIRON USE-ENVIRON-ROOT)DB_ENV->remove).
 (BDB:WITH-DBE (var &KEY
    create options) &BODY body)body, close it.
    create is a list of options to be passed to BDB:DBE-CREATE,
    options is a list of options to be passed to BDB:DBE-SET-OPTIONS.
 (BDB:DBE-SET-OPTIONS dbe
   &KEY MSGFILE ERRFILE ERRPFX PASSWORD ENCRYPT LOCK-TIMEOUT TXN-TIMEOUT
   SHM-KEY TAS-SPINS TX-TIMESTAMP TX-MAX DATA-DIR TMP-DIR LG-BSIZE LG-DIR
   LG-MAX LG-REGIONMAX NCACHE CACHESIZE CACHE LK-CONFLICTS LK-DETECT
   LK-MAX-LOCKERS LK-MAX-LOCKS LK-MAX-OBJECTS AUTO-COMMIT CDB-ALLDB DIRECT-DB
   DSYNC-LOG LOG-AUTOREMOVE LOG-INMEMORY DIRECT-LOG NOLOCKING NOMMAP NOPANIC
   OVERWRITE PANIC-ENVIRONMENT REGION-INIT TXN-NOSYNC TXN-WRITE-NOSYNC YIELDCPU
   VERB-CHKPOINT VERB-DEADLOCK VERB-RECOVERY VERB-REPLICATION VERB-WAITSFOR
   VERBOSE)Set some environment options using
(BDB:DBE-GET-OPTIONS dbe
   &OPTIONAL what)Retrieve some environment options.
Values of what
NILLIST
    :TX-TIMESTAMPDB_ENV->get_tx_timestamp)
    :TX-MAXDB_ENV->set_tx_max)
    :DATA-DIRDB_ENV->get_data_dir)
    :TMP-DIRDB_ENV->get_tmp_dir).
       May be NIL.:VERBOSELIST of verbosity settings
       (DB_ENV->get_verbose).
    :AUTO-COMMIT:CDB-ALLDB:DIRECT-DB:DSYNC-LOG:LOG-AUTOREMOVE:LOG-INMEMORY:DIRECT-LOG:NOLOCKING:NOMMAP:NOPANIC:OVERWRITE:PANIC-ENVIRONMENT:REGION-INIT:TXN-NOSYNC:TXN-WRITE-NOSYNC:YIELDCPU:VERB-CHKPOINT:VERB-DEADLOCK:VERB-RECOVERY:VERB-REPLICATION:VERB-WAITSFORBOOLEAN indicator of whether this
       option is set or not
       (DB_ENV->get_verbose and
       DB_ENV->get_flags).
    :LG-BSIZEDB_ENV->get_lg_bsize).
    :LG-DIRDB_ENV->get_lg_dir).
    :LG-MAXDB_ENV->get_lg_max).
    :LG-REGIONMAXDB_ENV->get_lg_regionmax).
    :NCACHE:CACHESIZE:CACHEDB_ENV->get_cachesize).
    :LK-CONFLICTSDB_ENV->get_lk_conflicts).
    :LK-DETECTDB_ENV->get_lk_detect).
    :LK-MAX-LOCKERSDB_ENV->get_lk_max_lockers).
    :LK-MAX-LOCKSDB_ENV->get_lk_max_locks).
    :LK-MAX-OBJECTSDB_ENV->get_lk_max_objects).
    :TAS-SPINSDB_ENV->get_tas_spins).
    :SHM-KEYDB_ENV->get_shm_key).
    :LOCK-TIMEOUT:TXN-TIMEOUTDB_ENV->get_timeout).
    :ENCRYPTDB_ENV->get_encrypt_flags).
    :ERRFILENIL
       (DB_ENV->get_errfile).
    :MSGFILENIL
       (DB_ENV->get_msgfile).
    :ERRPFXSTRING or NIL
       (DB_ENV->get_errpfx).
    :DB-XIDDATASIZELENGTH of the globally unique
       (VECTOR (UNSIGNED-BYTE 8)) which must be passed to
       DB_TXN->prepare.
    :HOMEDB_ENV->get_home).
    :OPENLIST of flags passed to BDB:DBE-OPEN
       (DB_ENV->get_open_flags).
    :CACHEDB_ENV->get_cachesize).
    (BDB:DB-CREATE dbe &KEY
   XA)db_create).
(BDB:DB-CLOSE db &KEY NOSYNC)DB->close).
   You can also call CLOSE.(BDB:DB-DEL dbe key &KEY
   TRANSACTION AUTO-COMMIT)DB->del).
(BDB:DB-FD db)DB->fd).
(BDB:DB-GET db key &KEY ACTION AUTO-COMMIT
   DEGREE-2 DIRTY-READ MULTIPLE RMW TRANSACTION (ERROR T))Get items from a database
   (DB->get).
   If :ERROR is NIL and the record is not found, no ERROR is SIGNALed,
   instead :NOTFOUND is returned.
   :ACTION should be one of
   
| :CONSUME | :GET-BOTH | 
| :CONSUME-WAIT | :SET-RECNO | 
(BDB:DB-PUT db key val
   &KEY AUTO-COMMIT ACTION TRANSACTION)Store items into a database
  (DB->put).
  :ACTION should be one of
  
| :APPEND | :NODUPDATA | :NOOVERWRITE | 
(BDB:DB-STAT db &KEY FAST-STAT
   TRANSACTION)DB->get_byteswapped,
   DB->get_type,
   DB->stat).
(BDB:DB-OPEN db file &KEY
   DATABASE TYPE MODE FLAGS CREATE DIRTY-READ EXCL NOMMAP RDONLY
   THREAD TRUNCATE AUTO-COMMIT TRANSACTION)Open a database (DB->open).
   :TYPE should be one of
   
| :BTREE | :RECNO | 
| :HASH | :UNKNOWN(default) | 
| :QUEUE | 
   :FLAGS may be the value of a previous call
   to (
BDB:DB-GET-OPTIONS db :OPEN)
(BDB:DB-SYNC db)DB->sync).
(BDB:DB-TRUNCATE db &KEY
   TRANSACTION AUTO-COMMIT)DB->truncate).
(BDB:DB-UPGRADE db file
   &KEY DUPSORT)DB->upgrade).
(BDB:DB-RENAME db file database newname)DB->rename).
(BDB:DB-REMOVE db file database)DB->remove).
(BDB:DB-JOIN db cursor-sequence
   &KEY JOIN-NOSORT)DB->join).
(BDB:DB-KEY-RANGE db key
   &KEY TRANSACTION)DB->key_range).
   The underlying database must be of type Btree.
(BDB:DB-VERIFY db file &KEY
   DATABASE SALVAGE AGGRESSIVE PRINTABLE NOORDERCHK)DB->verify).
   :SALVAGE, if supplied, should be the output
   file name.  :DATABASE, if supplied,
   will force DB_ORDERCHKONLY.
(BDB:WITH-DB (var dbe file
   &KEY create options open) &BODY body)body, close it.
   create is a list of options to be passed to BDB:DB-CREATE,
   options is a list of options to be passed to BDB:DB-SET-OPTIONS,
   open is a list of options to be passed to BDB:DB-OPEN.
(BDB:DB-SET-OPTIONS db
   &KEY ERRFILE MSGFILE ERRPFX PASSWORD ENCRYPTION NCACHE CACHESIZE CACHE
   LORDER PAGESIZE BT-MINKEY H-FFACTOR H-NELEM Q-EXTENTSIZE
   RE-DELIM RE-LEN RE-PAD RE-SOURCE
   CHKSUM ENCRYPT TXN-NOT-DURABLE DUP DUPSORT INORDER RECNUM REVSPLITOFF
   RENUMBER SNAPSHOT)Set some database options using
(BDB:DB-GET-OPTIONS db
   &OPTIONAL what)Retrieve some database options.
Values of what
NILLIST
    :FLAGSDB_ENV->get_flags).
    :CHKSUM:ENCRYPT:TXN-NOT-DURABLE:DUP:DUPSORT:INORDER:RECNUM:REVSPLITOFF:RENUMBER:SNAPSHOTBOOLEAN indicator of whether this
       option is set or not
       (DB_ENV->get_verbose and
       DB_ENV->get_flags).
    :CACHEDB->get_cachesize or
       DB_ENV->get_cachesize if the
       database was created within an environment).
    :ENCRYPTIONDB_ENV->get_encrypt_flags).
    :ERRFILENIL
       (DB_ENV->get_errfile).
    :MSGFILENIL
       (DB_ENV->get_msgfile).
    :ERRPFXSTRING or NIL
       (DB_ENV->get_errpfx).
    :PAGESIZEDB->get_pagesize).
    :BT-MINKEY:BTREE leaf page
       underlying source file
       (DB->get_bt_minkey).
    :H-FFACTOR:HASH table
       (DB->get_h_ffactor).
    :H-NELEM:HASH table
       (DB->get_h_nelem).
    :Q-EXTENTSIZE:QUEUE database
       (DB->get_q_extentsize).
    :RE-DELIM:RECNO databases
       (DB->get_re_delim).
    :RE-LENDB->get_re_len).
    :RE-PADDB->get_re_pad).
    :RE-SOURCE:RECNO databases
       (DB->get_re_source).
    :LORDERDB->get_lorder).
    :DBNAMEDB->get_dbname)
    :TRANSACTIONALDB->get_transactional).
    :OPENBDB:DB-OPEN
       (DB->get_open_flags).
    Once you call a method for one type of access method,
    the handle can only be used for that type.
    The methods DB->get_re_delim
    and DB->get_re_source are for
    a :RECNO database so
    you cannot call them
    (by passing :RE-DELIM
    or :RE-SOURCE to this function)
    and then use the database handle to open a database of different type
    (e.g., :QUEUE).
(BDB:MAKE-DBC db &KEY
   DEGREE-2 DIRTY-READ WRITECURSOR TRANSACTION)DB->cursor).
(BDB:DBC-CLOSE cursor)DBCursor->close).
   You can also call CLOSE.(BDB:DBC-COUNT cursor)DBCursor->count).
(BDB:DBC-DEL cursor)DBCursor->del).
(BDB:DBC-DUP cursor &KEY POSITION)DBCursor->dup).
(BDB:DBC-GET cursor key data action
   &KEY DEGREE-2 DIRTY-READ MULTIPLE (ERROR T))Retrieve by cursor
   (DBCursor->get).
   If :ERROR is NIL and the record is not found, no ERROR is SIGNALed,
   :NOTFOUND or :KEYEMPTY
   is returned instead, as appropriate.
   action should be one of
   
| :CURRENT | :GET-RECNO | :NEXT-DUP | :SET | 
| :FIRST | :JOIN-ITEM | :NEXT-NODUP | :SET-RANGE | 
| :GET-BOTH | :LAST | :PREV | :SET-RECNO | 
| :GET-BOTH-RANGE | :NEXT | :PREV-NODUP | 
(BDB:DBC-PUT cursor key data
   flag)DBCursor->put).
(BDB:WITH-DBC (var &REST
   options) &BODY body))body, close it.
   options are passed to BDB:MAKE-DBC.
(BDB:LOCK-DETECT dbe action)DB_ENV->lock_detect).
(BDB:LOCK-ID dbe)DB_ENV->lock_id).
(BDB:LOCK-ID-FREE dbe id)DB_ENV->lock_id_free).
   All associated locks should be released first.
(BDB:LOCK-GET dbe object locker
   mode &KEY NOWAIT)DB_ENV->lock_get).
   The BDB:DBLOCK object returned by this function will
   not be released when the environment is closed.
   This permits long-lived locks.(BDB:LOCK-PUT dbe lock)DB_ENV->lock_put).
(BDB:LOCK-CLOSE lock)Release a lock
   (DB_ENV->lock_put) using the
   environment with which it has been acquired.
   This is used to EXT:FINALIZE BDB:DBLOCK objects.
If that environment has already been closed, you are in a big trouble (segfault), so you better release your locks or do not drop them.
(BDB:LOCK-STAT dbe &KEY
   STAT-CLEAR)DB_ENV->lock_stat).
(BDB:LOG-ARCHIVE dbe
   &KEY ARCH-ABS ARCH-DATA ARCH-LOG ARCH-REMOVE)DB_ENV->log_archive).
(BDB:LOG-FILE dbe lsn)lsn
   (DB_ENV->log_file).
(BDB:LOG-FLUSH dbe lsn)DB_ENV->log_flush).
(BDB:LOG-PUT dbe data
   &KEY :FLUSH)DB_ENV->log_put).
(BDB:LOG-STAT dbe
   &KEY STAT-CLEAR)DB_ENV->log_stat).
(BDB:LOG-CURSOR dbe)DB_ENV->log_cursor).
(BDB:LOGC-CLOSE logc)DB_LOGC->close).
(BDB:LOGC-GET logc action
   &KEY TYPE ERROR)Retrieve a log record
   (DB_LOGC->get).
   If :ERROR is NIL and the record is not found, no ERROR is SIGNALed,
   :NOTFOUND is returned instead.
   
Valid actions
:CURRENT:FIRST:LAST:NEXT:PREVDB_SET.
   
   Returns two values: the datum of type specified by the :TYPE
   argument and the DB:LSN value of the record retrieved
   (when action is a DB:LSN, it
   is returned unchanged).
Use EQUALP to check similarity of BDB:LSN objects.
(BDB:LOG-COMPARE lsn1 lsn2)log_compare).
(BDB:TXN-BEGIN dbe &KEY
   DEGREE-2 PARENT DIRTY-READ NOSYNC NOWAIT SYNC)DB_ENV->txn_begin).
(BDB:TXN-ABORT txn)DB_TXN->abort).
(BDB:TXN-COMMIT txn &KEY
   NOSYNC SYNC)DB_TXN->commit).
(BDB:TXN-DISCARD txn)DB_TXN->discard).
(BDB:TXN-ID txn)DB_TXN->id).
(BDB:TXN-CHECKPOINT dbe
   &KEY KBYTE MIN FORCE)DB_ENV->txn_checkpoint).
(BDB:TXN-PREPARE txn id)DB_TXN->prepare).
(BDB:TXN-RECOVER dbe &KEY
   FIRST NEXT)DB_ENV->txn_recover).
(BDB:TXN-SET-TIMEOUT txn
   timeout which)DB_TXN->set_timeout).
(BDB:TXN-STAT dbe &KEY
   STAT-CLEAR)DB_ENV->txn_stat).
This module provides some directory access from lisp, in package “LDAP”.
When this module is present, *FEATURES*
 contains the symbol :DIRKEY.
3 types of directory keys may exist, depending on the compilation environment.
valid directory key types
The following functions and macros are exported (please note that these features are experimental and the API may be modified in the future).
(LDAP:DIR-KEY-OPEN
   dkey pathname &KEY (:DIRECTION :INPUT)
   :IF-DOES-NOT-EXIST)dkey, which should
   be either an open directory key or a valid directory key type.
   The meaning of the :DIRECTION and :IF-DOES-NOT-EXIST keyword
   arguments is the same as for OPEN.(LDAP:DIR-KEY-CLOSE
    dkey)LDAP:WITH-DIR-KEY-OPEN macro.(LDAP:WITH-DIR-KEY-OPEN (variable
    dkey pathname &REST {option}*) &BODY
    body)LDAP:DIR-KEY-OPEN
   on dkey, pathname and options), bind it to variable,
   execute body, then close it with LDAP:DIR-KEY-CLOSE.
 (LDAP:DIR-KEY-TYPE
    dkey)(LDAP:DIR-KEY-PATH
                dkey)pathname argument of LDAP:DIR-KEY-OPEN if dkey was a directory key type or the
   concatenation of the pathname argument and the
   ldap:dir-key-path of dkey.
   (LDAP:DIR-KEY-DIRECTION
    dkey):INPUT, :OUTPUT and :IO, indicating
   the permitted operation on this key and its derivatives.
   (LDAP:DIR-KEY-CLOSED-P
    dkey)(LDAP:DIR-KEY-SUBKEY-DELETE
     dkey subkey)
   (LDAP:DIR-KEY-VALUE-DELETE
     dkey attribute)(LDAP:DIR-KEY-SUBKEY
    dkey)
  (LDAP:DIR-KEY-ATTRIBUTES dkey)(LDAP:DIR-KEY-VALUE dkey
    attribute &OPTIONAL
    default)GETHASH and SETFable just like GETHASH.
   (LDAP:DIR-KEY-INFO
    dkey)(LDAP:WITH-DIR-KEY-SEARCH
    (key-iter
    atribute-iter
    dkey pathname &KEY :scope)
    &BODY body)This is the main way to iterate over the subtree
   under the key dkey+pathname.
key-iter is a non-NIL symbol
    and is bound via MACROLET to a macro, each call of which returns
    the next subkey.
atribute-iter is a symbol and is
    bound, when non-NIL, to a macro, each call of which returns two
   values - the next attribute and its value.
The :scope keyword argument specifies the
    scope of the search and can be
   
:self:level:treeLDAP:WITH-DIR-KEY-SEARCH is used to implement
    LDAP:DIR-KEY-VALUES,
    LDAP:DIR-KEY-CHILDREN and
    LDAP:DIR-KEY-DUMP-TREE in
    modules/dirkey/dirkey.lisp.
    
This package offers an “FFI”-based interface to PostgreSQL.
The package “SQL”
 (nicknamed “POSTGRES”
 and “POSTGRESQL”)
 is case-sensitive,
 so you would write (sql:PQconnectdb ...)
 when you need to call
 PQconnectdb().
When this module is present, *FEATURES*
 contains the symbol :POSTGRESQL.
See modules/postgresql/test.tst
 for sample usage.
Additionally, some higher level functionality is available:
(sql:pq-finish
   connection)PQfinish the connection and mark
   it as invalid(sql:pq-clear
   result)PQclear the result and mark
   it as invalid(sql:sql-error connection result format-string
   &REST arguments)connection and result and SIGNAL an
   appropriate ERROR(sql:sql-connect
   &KEY host port options tty name login password)PQsetdbLogin and return
   the connection(sql:with-sql-connection
   (variable &REST options &KEY log &ALLOW-OTHER-KEYS)
   &BODY body)bind *sql-log*
     to the log argument
call sql:sql-connect on
     options and bind variable to the result
execute body
call sql:pq-finish on
     variable
(sql:sql-transaction connection command
   status &OPTIONAL (clear-p T))command via connection;
   if the status does not match status, ERROR is SIGNALed;
   if clear-p is
   non-NIL sql:pq-clear the result;
   otherwise return it(sql:with-sql-transaction (result connection
   command status) &BODY body)body on the result of command,
   then sql:pq-clear the result
sql:*sql-login*login
   argument to sql:sql-connect
   (initially set to "postgres")
sql:*sql-password*password
   argument to sql:sql-connect
   (initially set to "postgres")
sql:*sql-log*NIL, should be a STREAM;
   sql:sql-connect
   and sql:sql-transaction
   will write to it (initially set to NIL)
Since PQfinish and PQclear
  cannot be called on the same pointer twice, one needs to track their
  validity (sql:sql-connect
  and sql:sql-transaction take care of that).
  See Example 32.10, “Controlling validity of resources”.
The Oracle module allows a CLISP program to act as client to an Oracle database server. The module includes full SQL support, transactions (including auto-commit), support for most Oracle data types (LONG, BLOB, CLOB, RAW, etc.), automatic conversion between Oracle and Common Lisp data types, database connection caching and retry, concurrent connections to multiple databases, proper handling of Oracle errors, and more.
The module can be used to build sophisticated Oracle database applications in Common Lisp.
When this module is present, *FEATURES* contains the
 symbol :ORACLE.
Access to Oracle is via these functions and macros in
package “ORACLE”.
When any Oracle function fails, the general Lisp function
ERROR is called, with the condition string set to
include the Oracle error number, the Oracle message text,
and other context of the error (e.g., the text and parse location of a
SQL query).
(ORACLE:CONNECT
user password
server
&OPTIONAL
schema
auto-commit
prefetch-buffer-bytes
long-len
truncate-ok)
Connect to an Oracle database.  All subsequent operations will affect
this database until the next call to ORACLE:CONNECT.  A
single program can access different Oracle schemas concurrently by
repeated calls to ORACLE:CONNECT.  Database connections
are cached and re-used: if you call ORACLE:CONNECT again
with the same user,
schema, and
server, the previous Oracle connection will
be re-used.  ORACLE:CONNECT may not be called inside
WITH-TRANSACTION.
Returns: T if a cached connection was re-used, NIL if a new
connection was created (and cached).
The meaning of the arguments is as follows:
Arguments for ORACLE:CONNECT
userpasswordNIL if
   user has no password (!).
serverschemaNIL).
   If NIL, same as user.  This allows you to log on with one user's
   id/password but see the database as if you were some other user.
auto-commitT). Set this to NIL if you intend to do transactions
   and call COMMIT explicitly.  However,
   WITH-TRANSACTION is probably easier.
prefetch-buffer-byteslong-lentruncate-ok
   (below).  Setting long-len to zero and
   truncate-ok to NIL will disable long
   fetching entirely.  If long-len is NIL
   or negative, defaults to 500k bytes.truncate-oklong-len bytes on fetch; otherwise, fetches
   of LONG columns exceeding long-len bytes
   will raise an error.  Default: NIL.(ORACLE:DISCONNECT)ORACLE:CONNECT is called again.  The
connection is closed and removed from the connection cache.  Does
nothing if there is no connection.  DISCONNECT
may not be called inside WITH-TRANSACTION.
Returns NIL.
(ORACLE:RUN-SQL
sql
&OPTIONAL
params
is-select)Execute a SQL statement.  Must be ORACLE:CONNECTed
to a database.  Returns the number of rows affected by the SQL operation,
for non-SELECT statements, zero for SELECT statements.  For
destructive database operations (INSERT, UPDATE, DELETE), the results
are committed to the database immediately if
auto-commit when establishing the current
connection; see ORACLE:CONNECT.  The meaning of the
arguments is as follows: 
Arguments for RUN-SQL
sqlsql statement may contain
   Oracle "named parameters," e.g. ":myparam" whose values will
   be substituted from the parameters given
   in params.
paramsparams.
   The mapping may be passed as either (1) a hash table whose keys are
   the named parameters or (2) a list of pairs, ((name value) (name
   value) ...).  Parameter values passed from Lisp are converted to the
   appropriate Oracle data types (see FETCH).
is-select(ORACLE:DO-ROWS
vars &BODY body) Macro which loops over a SQL SELECT result,
   evaluating, for each row in the result, the forms in body,
   binding symbols given in vars to
   corresponding database columns in the SELECT result.  The
   argument vars must be a non-empty list of
   symbols matching a subset of the columns of an active SELECT query.
   If a SELECT column is an Oracle expression such as
   SUBSTR(mycol, 1, 10), it is recommended to use a
   column alias, e.g., SELECT SUBSTR(mycol, 1, 10) AS
    myvar, in which case the column alias will be used as the
   symbol bound to the column value.
As DO-ROWS expands into a DO*
   loop, it may be terminated prematurely, before all rows are fetched,
   by using RETURN anywhere in body.
It is allowed to call ORACLE:CONNECT in the
   body of the loop, but only to switch the connection to a database
   other than the one that was used to do the SELECT.  This is useful
   for reading from one database while writing to another.
  
In vars, instead of a single
   symbol, a pair (bound-var
   "column-name") may be specified, which
   will cause values from the SELECTed column or alias ,
   column-name, to be bound to Lisp variable,
   bound-var.  This is for unusual cases
   where a Lisp variable cannot be created with the same name as the
   column (e.g., a column named "T"), or when it is inconvenient or
   impossible to alias the column with SELECT ... AS.
(ORACLE:FETCH
   &OPTIONAL result-type)Fetch a single row of data.  Returns a row of values
   corresponding to the columns of an active SELECT statment.  The row
   data is returned in one of three different forms, depending on the
   value of the symbol result-type:
Return values for FETCH
ARRAYARRAY with the
    same number of columns as in the SELECT statement, in the same
    order.  This is the default.PAIRS((column, value)
     ...) is be returned.  The number and order of pairs is
    the same as the columns in the SELECT statement.
 HASHHASH-TABLE whose keys are the column names
    and whose values are the column values in the row.  The SELECT
    columns must be unique and be valid Lisp
    symbols to use this option. If you are SELECTing an expression, you
    probably want to use a column alias: SELECT <expr> AS
    some_alias ...The following data type conversions are done between Oracle datatypes and Common Lisp data types:
| Oracle type | Converts to/from Common Lisp type | 
|---|---|
| Numeric (NUMBER, INTEGER, FLOAT) | The appropriate Common Lisp numeric type ( FIXNUM,BIGNUM,FLOAT) | 
| String (CHAR, VARCHAR, VARCHAR2) | A Common Lisp STRING.  Note that CHAR will be padded out to its
      full, fixed length as defined in Oracle; VARCHAR will be a
      string of variable length.  Also note that Oracle has no
      "zero-length string" value - it returns the SQL special valueNULLwhich is converted toNIL(see below). | 
| DATE | A string of the form "YYYY-MM-DD HH:MM:SS" where HH is
      24-hour form.  If you want dates formatted differently, convert
      them to strings in Oracle using SELECT
       TO_CHAR(mydate, '; the result will then be returned as a string,
      formatted as pertemplate. | 
| RAW, LONG RAW | A hexadecimal string, with two hex digits for each byte of Oracle data. Note that this means the Lisp string will be twice the size, in bytes, as the Oracle data. | 
| "Large" types (LONG, BLOB, CLOB) | A Lisp string of (arbitrary, possibly binary) data.  Note
      that truncation may occur; see the ORACLE:CONNECTparameterslong-lenandtruncate-ok. | 
| NULL | The Common Lisp value NIL | 
(ORACLE:FETCH-ALL
&OPTIONAL
max-rows
result-type
item-type)Fetch some or all the rows from a query and return
result as a sequence of sequences.  Arguments are all optional:
max-rows limits the result to
that numbers of rows;
result-type is the type of
sequence of the rows, either
'ARRAY (the default) or
'LIST;
item-type is the type of
sequence of the column values for each row, either
'ARRAY (the default) or
'LIST.
Each row fetched always contains the full set of column values SELECTed.
FETCH-ALL is often useful in conjunction with
MAP or REDUCE to iterate
over an entire SELECT result to construct a single Lisp value.
(ORACLE:PEEK &OPTIONAL
   result-type)FETCH, except does not advance to the next row.
Repeated calls to PEEK will thus return the same
row of data.  Returns NIL if at EOF.  If data is available, returns
row data just as FETCH (see
FETCH for data format and conversions done).
Optional argument result-type is the type
of sequence of the column values for the returned row, either
ARRAY (the default) or LIST.
PEEK is a useful look-ahead
for database reporting functions that may need to "break" on changes in
data to print headers, summaries, etc.
(ORACLE:COLUMNS)Returns information on the columns of a SELECT
  result, in the form of an array of SQLCOL structures, one for each
  result column in the most recent SELECT statement.  It is not
  necessary to have called FETCH before requesting
  column information on the query, however the query must have been
  compiled and executed with RUN-SQL.  Each SQLCOL
  structure has these slots:
Slots of SQLCOL
SELECT
     expr AS
     alias, then
    alias will be returned as the column name.
 T if NULLs allowed, NIL if NULLs are
    not allowed.To access the values of the SQLCOL structures, use the standard
 accessor functions, e.g., (ORACLE:SQLCOL-NAME (elt
  (ORACLE:COLUMNS) 0))
(ORACLE:EOF)(ORACLE:INSERT-ROW
table
values)table.
Second argument values is a map of
column names to values: either a hash table whose keys are the column
names, or a list of (name, value) pairs.  Columns missing from the map
will be given the default Oracle value, or NULL.
Returns the number of rows inserted (i.e., always 1).
(ORACLE:UPDATE-ROW
table
condition
vals
&OPTIONAL
params)table.  Second argument
condition is a string expression for a WHERE
clause (without the "WHERE") which determines which rows are updated.
Third argument vals is a map of columns to
be updated to their new values: a hash table whose keys are column
names, or list of (name, value) pairs.  Optional
params specifies values for named
parameters that may occur in condition,
e.g., when the condition is a match on a primary key, e.g.: "pk_column
= :pk_val".  Returns the number of rows updated.
(ORACLE:ROW-COUNT)FETCHed (not
PEEKed) so far.  For other statements (e.g.,
INSERT, UPDATE, DELETE), returns the number of rows affected by the
last operation (e.g., inserted, updated, deleted).  Must be connected
to a database and have an active SQL statement.
(ORACLE:WITH-TRANSACTION
&BODY
body)body atomically as a
database transaction, ensuring that either all the database operations
done in body complete successfully, or none
of them do.  If pending (un-committed) changes exist when this macro
is entered, they are rolled back (undone), so
that the database is affected only by the subsequent updates inside
body.  Nesting of
WITH-TRANSACTION blocks is not allowed and will
raise an error.  There is no effect on the status of
auto-commit given in
ORACLE:CONNECT; it resumes its previous state when the
macro exits.  The value of the WITH-TRANSACTION
expression is that of the last form in body.
(ORACLE:COMMIT)auto-commit parameter to
ORACLE:CONNECT must not have been set to use this
function, nor can it be called inside a
WITH-TRANSACTION block. Always returns NIL.
(ORACLE:ROLLBACK)auto-commit parameter to
ORACLE:CONNECT must not have been set to use this
function, nor can it be called inside a
WITH-TRANSACTION block. Always returns NIL.
(ORACLE:AUTO-COMMIT)auto-commit initially
given to ORACLE:CONNECT for the current connection.
With auto-commit enabled, modifications to
the database are committed (made permanent) after each destructive SQL
operation made with calls to RUN-SQL,
INSERT-ROW, UPDATE_ROW, etc.
With auto-commit disabled, transactional
integrity is under the programmer's control and is managed either by
(1) explicitly calling COMMIT or
ROLLBACK to commit or undo the pending
operations, or (2) wrapping code blocks with database operations
inside the WITH-TRANSACTION macro.
AUTO-COMMIT returns the previous status of
auto-commit.
AUTO-COMMIT may not be called inside
WITH-TRANSACTION.
Below is a simple example script which uses Oracle's demo database
schema, SCOTT.
(setf server "orcl") ; Change this to your server's SID
(oracle:connect "scott" "tiger" server)
(oracle:run-sql "SELECT deptno, dname, loc FROM dept ORDER BY DNAME")
(oracle:do-rows (deptno dname loc)
  (format t "Dept. no is '~A', " deptno)
  (format t "Dept. name is '~A', " dname)
  (format t "Dept. loc is '~A'~%" loc))
(oracle:update-row "dept" "dname = :acctval" '(("dname" "NEWACCT")) '(("acctval" "ACCOUNTING")))
(oracle:run-sql "SELECT deptno, dname, loc FROM dept ORDER BY DNAME")
(oracle:do-rows (deptno dname loc)
  (format t "Dept. no is '~A', " deptno)
  (format t "Dept. name is '~A', " dname)
  (format t "Dept. loc is '~A'~%" loc))
(oracle:update-row "dept" "dname = :acctval" '(("dname" "ACCOUNTING")) '(("acctval" "NEWACCT")))
Obviously, a working Oracle environment is required.  It is
recommended that you first be able to log on and use the Oracle
SQL*Plus application to test your environment
before attempting Oracle access via the
CLISP module.
At a minimum you will need to set environment variables
ORACLE_HOME to the Oracle base directory and
LD_LIBRARY_PATH to include
$ and possibly other
directories.ORACLE_HOME/lib
The module uses the Oracle Call Interface (OCI)
C library.  To build the module you will need the Oracle
OCI headers and link libraries; as a quick check, make sure
you have the file oci.h somewhere
under ORACLE_HOME, probably
in $.ORACLE_HOME/rdbms/demo/oci.h
To build the module into CLISP, configure with
./configure ... --with-module=oracle ....
The full linking set will contain the module,
so you will need to use the -K option to use it.
You can test that you really have the Oracle-enabled CLISP by
evaluating (.DESCRIBE 'oracle:connect)
It may be necessary to edit file
modules/oracle/Makefile
prior to running ./configure.
This is an “FFI”-based interface to the version 2.85 of
 LibSVM (included in the source distribution in the directory
 modules/libsvm/,
 so you do not need to install it yourself).
The package “LIBSVM”
 is case-sensitive, and you do not
 need the svm_ prefix for the functions described
 in modules/libsvm/README.
When this module is present, *FEATURES*
 contains the symbol :LIBSVM.
See modules/libsvm/test.tst
 for sample usage.
All data is kept on the C side as much as possible, so these foreign types do not have a CLOS counterpart.
LIST on the lisp side.LIST on the lisp side.VECTOR on the lisp side.FFI:FOREIGN-POINTER.(problem-l problem)problem (a
    FFI:FOREIGN-VARIABLE)(problem-y problem
    &OPTIONAL (length (problem-l problem)))(VECTOR
    DOUBLE-FLOAT length) representing the targets in the
    problem (a FFI:FOREIGN-VARIABLE).(problem-y-n problem
    n &OPTIONAL (length (problem-l problem))))DOUBLE-FLOAT representing the nth
    target in the problem (a FFI:FOREIGN-VARIABLE).
 (problem-x problem
    &OPTIONAL (length (problem-l problem)))(VECTOR (VECTOR
     node) length) representing the predictors in the problem
    (a FFI:FOREIGN-VARIABLE).(problem-x-n problem
    n &OPTIONAL (length (problem-l problem))))(VECTOR node)
    representing the nth set of predictors in the problem (a
    FFI:FOREIGN-VARIABLE).(make-problem &KEY l y
    x)FFI:FOREIGN-VARIABLE representing
    a model.(destroy-problem problem)Release the memory taken by the problem
    object and invalidate the FFI:FOREIGN-VARIABLE problem.
You must call this function yourself,
     but only after deallocating all model
     objects trained from this problem.
See modules/libsvm/README
     for more information.
(load-problem filename &KEY
    (log *STANDARD-OUTPUT*))Read a problem from a file in the libsvm/svmlight format. Return two values: the problem and max index (i.e., the number of columns).
Messages go to log.
(save-problem filename problem
    &KEY (log *STANDARD-OUTPUT*))Write a problem into a file.
Messages go to log.
(destroy-model model)Release the memory taken by the model
    object and invalidate the FFI:FOREIGN-VARIABLE model.
Calls svm_destroy_model.
You do not have to call this function yourself, it is
    attached to the model by train
    and load-model via EXT:FINALIZE.
(check-parameter problem parameter)Check if the parameter is appropriate for the
    problem.
Calls svm_check_parameter.
(train problem parameter)Train a model.
Calls svm_train
    and check-parameter.
(cross-validation problem parameter
    n)Run n-fold cross-validation.
Calls svm_cross_validation
    and check-parameter.
(save-model filename model)Write a model into a file.
Calls svm_save_model.
(load-model filename)Read a model from a file.
Calls svm_load_model.
(get-svm-type model)svm_get_svm_type.
 (get-nr-class model)svm_get_nr_class.
 (get-labels model)svm_get_labels.
 (get-svr-probability model)svm_get_svr_probability.
 (predict-values model x)Return the decision values
    (a () given
    by VECTOR DOUBLE-FLOAT)model for x (a ().
   VECTOR node)
Calls svm_predict_values.
(predict model x)svm_predict.
 (predict-probability model x)svm_predict_probability.
 (check-probability-model model)svm_check_probability_model.
 (destroy-parameter parameter)Release the memory taken by the parameter
    object and invalidate the FFI:FOREIGN-VARIABLE parameter.
Does not call svm_destroy_param.
You do not have to call this function yourself, it is
    attached to the parameter by make-parameter
    via EXT:FINALIZE.
(make-parameter &KEY :v svm_type
    kernel_type degree gamma coef0 cache_size eps C nr_weight
    weight_label weight nu p shrinking probability)Allocates a new FFI:FOREIGN-VARIABLE of
    type parameter with the supplied slots.
The defaults come from vector v (such as returned
    by (), if supplied, providing
    an easy way to copy FFI:FOREIGN-VALUE parameter)parameters, otherwise the defaults
    for svm-train are used.
(parameter-alist parameter)parameter.
 This package offers an “FFI”-based interface to PARI.
The package “PARI” is case-sensitive.
When this module is present, *FEATURES* contains the
 symbol :PARI.
PARI objects are printed and read using a
 special #Z"" syntax.
This is an interface to the
 Matlab C API.
 The package “MATLAB” is
 case-sensitive, so you would write
 (matlab:engOpen ...)
 when you need to call engOpen.
When this module is present, *FEATURES*
 contains the symbol :MATLAB.
Additionally, some higher level functionality is available
 (see modules/matlab/test.tst
 for sample usage):
(matlab:matfile-content mf)VECTOR of STRINGs naming the
   variables in file mf
   (opened using matOpen).
matlab:*command*engOpen.
matlab:*engine*(matlab:engine)*engine* is valid and
   return it.(matlab:with-engine
   (&OPTIONAL engine command) &BODY body)body wuth the engine
   bound to a Matlab engine (default *engine*).
   The engine is opened with engOpen,
   then closed with engClose.
(matlab:with-MATfile
   (file name &OPTIONAL mode) &BODY body)matOpen the
   matlab file, do the body, matClose
   it.(matlab:copy-lisp-to-mxArray
   lisp-array &OPTIONAL matlab-matrix)(matlab:copy-lisp-to-matlab
   lisp-array matlab-variable &KEY engine)STRING) in the supplied engine (defaults to
  *engine*).(matlab:copy-mxArray-to-lisp
   matlab-matrix &OPTIONAL lisp-array)(matlab:copy-matlab-to-lisp
   matlab-variable &OPTIONAL lisp-array &KEY engine)(matlab:invert-matrix
   lisp-array &KEY engine)This is an interface to the Netica C API for working with Bayesian belief networks and influence diagrams.
The package “NETICA” is
 case-sensitive, e.g., you would write
 (netica:GetNodeExpectedUtils_bn ...)
 when you need to call
 GetNodeExpectedUtils_bn.
When this module is present, *FEATURES*
 contains the symbol :NETICA.
An interface to all public C functions is provided.
 Additionally, some higher level functionality is available
 (see modules/netica/demo.lisp
 for sample usage):
(netica:start-netica &KEY
   :license :verbose)NewNeticaEnviron_ns
   and InitNetica_bn and print some
   statistics; initialize netica:*env*.
(netica:check-errors &KEY
   :env :clear :severity)ClearError_ns), the errors of the
   given severity (ErrorSeverity_ns)
   and above.
   You should call this function after every call
   to a Netica function.  Every wrapper function in this list calls it,
   so you do not need to call it after a call to a wrapper function.
(netica:error-message error)Convert netica error to a STRING containing
| ErrorCategory_ns | 
| ErrorSeverity_ns | 
| ErrorNumber_ns | 
| ErrorMessage_ns | 
(netica:close-netica &KEY
   :env :verbose)netica:*env* to NIL.
(netica:make-net &KEY :name
   :comment :title :env :verbose)NewNet_bn,
   SetNetTitle_bn and
   SetNetComment_bn.
(netica:net-info net &KEY :out)Print some information about the net:
| GetNetName_bn | 
| GetNetTitle_bn | 
| GetNetComment_bn | 
| GetNetFileName_bn | 
| GetNetNodes_bn | 
(netica:make-node &KEY
   :name :net :kind :levels :states :num-states :title :comment :parents
   :cpt :x :y :env :verbose)NewNode_bn
   with the given name and many other parameters.
(netica:node-info node
   &KEY :header :out)(netica:get-beliefs node
   &KEY :env :verbose)GetNodeBeliefs_bn
   on the node.(netica:enter-finding net node
   state &KEY :env :verbose)EnterFinding_bn
   using NodeNamed_bn
   and StateNamed_bn.
(netica:save-net net &KEY
   :file :env :verbose)WriteNet_bn.
(netica:read-net file &KEY
   :env :verbose)ReadNet_bn.
(netica:with-open-dne-file (var
   file &REST opts) &BODY body)NewStreamFile_ns,
   execute body, then DeleteStream_ns
   - just like WITH-OPEN-STREAM.netica:*verbose*STREAM or NIL; the default value for
   the :VERBOSE argument (initially set to NIL).
netica:*license*:LICENSE argument.
netica:*env*:ENV argument.
This is an interface to Perl Compatible Regular Expressions.
When this module is present, *FEATURES* contains the
 symbol :PCRE.
PCRE module API
(PCRE:PCRE-VERSION)STRING and 2 FIXNUMs: major and minor numbers.
 (PCRE:PCRE-CONFIG type)Return some information about the PCRE build
    configuration.  type is one of 
| :UTF8 | 
| :NEWLINE | 
| :LINK-SIZE | 
| :POSIX-MALLOC-THRESHOLD | 
| :MATCH-LIMIT | 
(PCRE:PCRE-COMPILE string &KEY :STUDY
    :IGNORE-CASE :MULTILINE :DOTALL :EXTENDED :ANCHORED :DOLLAR-ENDONLY
    :EXTRA :NOTBOL :NOTEOL :UNGREADY :NOTEMPTY :NO-AUTO-CAPTURE)(PCRE:PATTERN-INFO pattern &OPTIONAL request)Return some information about the pattern,
    such as 
| :OPTIONS | 
| :SIZE | 
| :CAPTURECOUNT | 
| :BACKREFMAX | 
| :FIRSTBYTE | 
| :FIRSTTABLE | 
| :LASTLITERAL | 
| :NAMEENTRYSIZE | 
| :NAMECOUNT | 
| :NAMETABLE | 
| :STUDYSIZE | 
(PCRE:PCRE-NAME-TO-INDEX pattern name)(PCRE:PCRE-EXEC pattern string &KEY
    :WORK-SPACE :DFA :BOOLEAN :OFFSET :ANCHORED :NOTBOL :NOTEOL :NOTEMPTY
    :PARTIAL :DFA-SHORTEST :DFA-RESTART)Execute the compiled pattern against the
    string at the given offset with the given options.
    Returns NIL if no matches or a VECTOR of LENGTH
    CAPTURECOUNT+1 of PCRE:MATCH structures,
    unless :BOOLEAN was non-NIL, in which case
    return T as an indicator of success, but do not allocate anything.
   
:DFA argument determines
    whether pcre_dfa_exec is used instead
    of pcre_exec (PCRE v6 and better).
:WORK-SPACE is only used
    for :DFA and defaults to 20.
(PCRE:MATCH-START match)(PCRE:MATCH-END match)match. SETF-able.
 (PCRE:MATCH-SUBSTRING match string)string bounded by match.
 (PCRE:MATCH-STRINGS return-vector string)PCRE:PCRE-EXEC.
 (PCRE:MATCH-STRING return-vector which
    string &OPTIONAL pattern)which is a name of the sub-pattern (as
    opposed to its number), pattern must be supplied.
 (PCRE:PCRE-MATCHER pattern)CUSTOM:*APROPOS-MATCHER*.
 Wildcards, also called “Pathname Matching Notation”, describe sets of file names.
When this module is present, *FEATURES*
 contains the symbol :WILDCARD.
The “WILDCARD” package exports the following two symbols:
(WILDCARD:MATCH . This function returns a non-pattern
   string &KEY :START :END :case-insensitive)NIL value if the string matches
 the pattern.
(WILDCARD:WILDCARD-MATCHER
   . This function is a valid value for pattern)CUSTOM:*APROPOS-MATCHER*.
string]STRING string.
    This is called a “character class”.
    As a shorthand, string may contain ranges, which consist of two
    characters with a dash between them.
    For example, the class [a-z0-9_]
    matches a lowercase letter, a number, or an underscore.
    You can negate a class by placing a #\!
    or #\^ immediately after the opening bracket.
    Thus, [^A-Z@] matches any character
    except an uppercase letter or an at sign.
Slash characters have no special significance in the
  wildcard matching, unlike in the shell (/bin/sh),
  in which wildcards do not match them.
  Therefore, a pattern foo*bar
  can match a file name foo3/bar,
  and a pattern ./sr*sc
  can match a file name ./src/misc.
This is an “FFI”-based interface to the ZLIB.
When this module is present, *FEATURES*
 contains the symbol :ZLIB.
(ZLIB:Z-VERSION)(ZLIB:COMPRESS source &KEY level)source VECTOR.
(ZLIB:UNCOMPRESS
   source destination-length)source VECTOR (returned
   by ZLIB:COMPRESS).
   destination-length should be no less than
   the length of the uncompressed source.
(ZLIB:COMPRESS-BOUND source-length)ZLIB:COMPRESS.(ZLIB:ERROR-STRING errno)ZLIB:ZERRORERROR sometimes SIGNALed
   by ZLIB:COMPRESS
   and ZLIB:UNCOMPRESS.
   You can find the error code and the caller
   using ZLIB:ZERROR-ERRNO
   and ZLIB:ZERROR-CALLER.
This is the raw socket interface, as described in
 <sys/socket.h>.
Sockets are represented by their FIXNUM file descriptors.
When this module is present, *FEATURES* contains the
 symbol :RAWSOCK.
SOCKET:SOCKET-STREAM first!For most uses of sockets, the facilities described in
  Section 32.4, “Socket Streams” are adequate and much more convenient than these.
  You are encouraged to consider SOCKET:SOCKET-STREAMs and ensure that they
  are not adequate for your purposes before you use raw sockets.
EXT:MAKE-STREAM!You can turn such a raw socket into a usual lisp STREAM
  using EXT:MAKE-STREAM, but you should be extremely
  careful with such dubious actions!  See the <clisp-devel@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-devel)
  mailing list archives for more details.
  Note that EXT:MAKE-STREAM will duplicate the file descriptor
  (using dup),
  so you still have to CLOSE the original raw socket.
We implement access to
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
| ( | 
using same-named lisp functions in package “RAWSOCK”. Additionally,
| (callsclose. | 
| (callslisten. | 
When the OS does not provide
  socketpair, it is emulated
  using socket +
  connect +
  accept.
buffer(VECTOR (UNSIGNED-BYTE 8)).  The vector may be adjustable
   and have a fill pointer.  Whenever a function accepts a buffer
   argument, it also accepts :START and :END keyword arguments
   with the usual meaning and defaults.  You do not have to supply the
   vector length because Lisp can determine it itself, but, if you want
   to, you can use :END argument for that.
socketINTEGER (returned by
   socketpair or
   socket).familydomainNIL (stands for AF_UNSPEC),
   INTEGER, or a platform-specific keyword, e.g.,
   :INET stands for AF_INET.
typeNIL (stands for 0); INTEGER; or a
   platform-specific keyword, e.g.,
   :DGRAM stands for SOCK_DGRAM.
protocolNIL (stands for 0); INTEGER; a
   platform-specific keyword, e.g., :ETH_P_ARP stands
   for ETH_P_ARP, :IPPROTO-ICMP
   stands for IPPROTO_ICMP; or a STRING (passed
   to getprotobyname).
flagsrawsock:send
   accepts :OOB and EOR arguments,
   while rawsock:recv accepts PEEK,
   OOB and WAITALL.
addressSTRUCTURE-OBJECT RAWSOCK:SOCKADDR
   returned by
   MAKE-SOCKADDR.
   You do not need to supply its length because Lisp can determine it itself.
messageA STRUCTURE-OBJECT RAWSOCK:MESSAGE
   with the following slots:
   
| addr | a SOCKADDR. | 
| iovec | a ((:STARTand:ENDarguments are applied to this vector) | 
| control | a ( | 
| flags | a LIST | 
One can extract the list of acceptable platform-dependent keywords for, e.g., socket domain, using the following code:
(BLOCKNIL(HANDLER-BIND((TYPE-ERROR(LAMBDA(c) (FORMATT"~&error: ~A~%" c) (RETURN(CDDR(THIRD(TYPE-ERROR-EXPECTED-TYPEc))))))) (rawsock:socket "bad"NILNIL)))
The return values of the functions described in section
 Section 33.17.2, “Single System Call Functions” are derived from the return values of
 the underlying system call: if, say, the address argument is modified
 by the system call, two values are returned (in addition to the
 possible values coming from the return value of the system call):
 the (modified) address structure and its new size.
 If the system call fails, an ERROR is SIGNALed.
We do not interface to select
 or poll in this module,
 they are already available through SOCKET:SOCKET-STATUS.
We do not interface to shutdown
 in this module, it is already available through SOCKET:SOCKET-STREAM-SHUTDOWN.
We do not interface to gethostbyname
 or gethostbyaddr in this module,
 they are already available through POSIX:RESOLVE-HOST-IPADDR.
Errors in getaddrinfo
 and getnameinfo are SIGNALed
 as CONDITIONs of type RAWSOCK:EAI
 using gai_strerror.
Errors in other functions are reported as the usual OS errors
 (using strerror).
Functions that do not correspond to a single system call
(RAWSOCK:SOCK-READ
   socket buffer &KEY start end)(RAWSOCK:SOCK-WRITE
   socket buffer &KEY start end)Call one of
 read/readv or
 write/writev
   (depending on whether buffer is a ( or
   a VECTOR (UNSIGNED-BYTE 8))().
 Return the number of bytes read or written.VECTOR ()VECTOR (UNSIGNED-BYTE 8))
When readv and
  writev and not available, they are
  emulated by repeated calls to read
  and write.
On Win32 we have to use recv
  instead of read
  and send instead of
  write because Win32
  read and
  write do not work on sockets, only
  on regular files.
(RAWSOCK:PROTOCOL &OPTIONAL
   protocol)getprotobyname
   when protocol is a STRING,
   or call getprotobynumber when
   protocol is an INTEGER.
   Return a RAWSOCK:PROTOCOL structure object.
   When protocol is NIL, return a LIST of all known protocols using
   setprotoent,
   getprotoent, and
   endprotoent.
(RAWSOCK:NETWORK &OPTIONAL
   network type)getnetbyname
   when network is a STRING,
   or call getnetbynumber when
   network is an INTEGER.
   Return a RAWSOCK:NETWORK structure object.
   When network is NIL, return a LIST of all known networks
   using setnetent,
   getnetent, and
   endnetent.
(RAWSOCK:IF-NAME-INDEX &OPTIONAL
   what)if_nametoindex
   when network is a STRING and return an INTEGER;
   or call if_indextoname when
   network is an INTEGER and return a STRING.
   When what is NIL, return an association list of
   pairs (index . name)
   using if_nameindex.
(RAWSOCK:IFADDRS)getifaddrs
   and return a LIST of ifaddrs objects.
(RAWSOCK:SOCKET-OPTION socket name
   &KEY :LEVEL)(SETF (RAWSOCK:SOCKET-OPTION socket name
   &KEY :LEVEL) value)getsockopt
   and setsockopt, returns and sets
   individual (for specific option name and
   level) and multiple (when name is
   NIL and/or level is :ALL) options.
   (See also SOCKET:SOCKET-OPTIONS.)(RAWSOCK:CONVERT-ADDRESS
   family address)Convert between STRING and INTEGER IP
   address representations using
| inet_addr | inet_ntop | 
| inet_ntoa | inet_pton | 
(RAWSOCK:MAKE-SOCKADDR
   family &OPTIONAL data)data should be a sequence of (UNSIGNED-BYTE 8) or an INTEGER
   (meaning (MAKE-LIST data :initial-element 0)).
   When omitted, the standard platform-specific size is used.
(RAWSOCK:SOCKADDR-FAMILY address)family of the
   sockaddr object.(RAWSOCK:SOCKADDR-DATA address)Return a fresh VECTOR displaced to the
   data field of the
   C struct sockaddr object.
Modifying this VECTOR's content will modify the
    address argument data!
(RAWSOCK:OPEN-UNIX-SOCKET pathname
   &OPTIONAL (type :STREAM))socket and address.
(RAWSOCK:OPEN-UNIX-SOCKET-STREAM pathname
   &REST options &KEY (type :STREAM)
   &ALLOW-OTHER-KEYS)stream and address.  type is passed
   to RAWSOCK:OPEN-UNIX-SOCKET, other options
   to EXT:MAKE-STREAM (but see Do not use EXT:MAKE-STREAM!!).
(RAWSOCK:IPCSUM buffer &KEY start end)
  - IP(RAWSOCK:ICMPCSUM buffer &KEY start end)
  - ICMP(RAWSOCK:TCPCSUM buffer &KEY start end)
  - TCP(RAWSOCK:UDPCSUM buffer &KEY start end)
  - UDPbuffer is assumed to be a suitable
   packet for the protocol, with the appropriate header etc.
   The typical packet you send is both IP and TCP and thus has two
   checksums, so you would want to call two functions.
(RAWSOCK:CONFIGDEV socket name address
   &KEY promisc
   noarp)address
   with ioctl.
The FastCGI module speeds up CLISP CGI scripts launched by a Web server. Working with a FastCGI-enabled Web server such as Apache with mod_fastcgi, a CLISP program using the FastCGI protocol will run many times faster than a conventional CGI program. The performance improvements stem from the fact that the script's process remains running across HTTP requests, eliminating startup overhead and allowing for caching of data structures and other resources. This is the same approach used is in other languages (e.g., mod_perl for Perl).
When this module is present, *FEATURES* contains the
 symbol :FASTCGI.
Traditional CGI programs work by doing input/output with the Web server via the following channels:
HTTP_USER_AGENT is the
variable set by the Web server to name the browser used
FastCGI involves replacing calls the standard routines to do the above with calls in the “FASTCGI” package. These calls will then work exactly as before when the program is invoked as a CGI, but will also work when invoked by a FastCGI-enabled Web server.
FastCGI programs persist across HTTP requests, and thus incur startup overhead costs only once. For Lisp Web programs, this overhead can be substantial: code must be compiled and loaded, files and databases must be opened, etc. Further, because the program stays running from HTTP request to HTTP request, it can cache information in memory such as database connections or large in-memory data structures.
Access to FastCGI is via these functions in package “FASTCGI”.
(FASTCGI:IS-CGI)T if the CLISP program has been launched as a traditional
CGI rather than in FastCGI.  In traditional CGI, program I/O is
via operating system environment variables and standard file streams.
Under FastCGI, I/O is done directly with the Web server via
the FastCGI protocol.
(FASTCGI:ACCEPT) cgi-forms
(FASTCGI:FINISH)
In FastCGI mode, the program loops,
ACCEPTing to begin the execution of an HTTP
request, and FINISHing to signal that the script
is finished writing its response to the HTTP request.  ACCEPT
blocks until the next HTTP request comes in, returning T if there is
a new request to handle, and NIL if no more HTTP requests will
occur, usually because the Web server itself has terminated, in which
case the FastCGI server loop should also exit.
A typical FastCGI top-level server loop looks like:
(do ()
    ((not (fastcgi:accept)))
  (run-my-script)
  (fastcgi:finish))
(FASTCGI:GETENV
varname)EXT:GETENV to get the value of the environment variable
named varname, which should be a string.
Unlike EXT:GETENV, which accesses the actual host operating system environment,
FASTCGI:GETENV obtains its environment via
the Web server, over its FastCGI communications channel.
For more information, see the FastCGI Web site.
Returns NIL if varname is not defined in
the operating system environment.  See here for a
list of useful variables.  You must first have called
ACCEPT and not yet have called
FINISH.  (FASTCGI:WRITE-STDOUT
string)ACCEPT and not yet have
called FINISH.
(FASTCGI:WRITE-STDERR
string)(FASTCGI:SLURP-STDIN)METHOD="post", when the data are passed to the CGI
script via standard input rather than via the environment variable
QUERY_STRING.  There is no way to read standard input
in pieces, which could be a problem, say, for HTTP uploads of very large files.
(FASTCGI:OUT
tree)WRITE-STDOUT, except that
tree
may be an arbitrarily nested list structure containing (at the leaves)
numbers and strings.  For example,
(FASTCGI:OUT '("foo" (" " 10 " " 20)))
will write the string "foo 10 20".  This function
is useful when building strings in memory for display.
Below is a simple example CGI script using FastCGI.
#!/usr/local/bin/clisp -q -K full
(do ((count 1 (1+ count)))
    ((not (fastcgi:accept)) nil)
  (fastcgi:out "Content-type: text/plain" #\Newline #\Newline)
  (fastcgi:out
   "I am running in mode: " (if (fastcgi:is-cgi) "CGI" "FastCGI") #\Newline
   "This is execution no.: " count #\Newline
   "The browser string is '" (fastcgi:getenv "HTTP_USER_AGENT") "'" #\Newline)
  (fastcgi:finish))
It is necessary to download the FastCGI developers' kit, build it, and install it, before building CLISP with FastCGI support. You also need to upgrade your Web server to speak the FastCGI protocol. For Apache this means building in mod_fastcgi, either statically or dynamically, and then adding a line to your Apache config like:
     Addhandler fastcgi-script .fcgi
After that, you can convert foo.cgi by linking it
to a script names foo.fcgi.  Since a FastCGI
script is also a valid CGI script, it can be run unmodified in either
mode.
This is an “FFI”-based interface to GTK+ version 2.
The package “GTK” is case-sensitive.
When this module is present, *FEATURES*
 contains the symbol :GTK.
(glade-load filename)filename.(run-glade-file filename name)name described in the
    Glade-generated file filename.(gui filename)filename, normally a variation
    of modules/gtk2/ui.glade.
 Table of Contents
BLOCK and RETURN-FROMTAGBODY and GOCATCH and THROWUNWIND-PROTECTHANDLER-BINDTable of Contents
For files in CLISP binary distributions, see the section called “Files”.
#P"*.d"#P".c"FFI:*OUTPUT-C-FUNCTIONS*).
#P".lisp"#P"*.fas"#P".lib"COMPILE-FILE and used by REQUIREC sources are pre-processed with the following tools before being passed to the C compiler:
utils/comment5.cConvert /bin/sh-style comments (lines starting
  with "# ") to C-style comments
  (/**/).
The use of /bin/sh-style comments is deprecated.
utils/varbrace.dvar)
  can be used within blocks, like in C++
  and C99.utils/ccpaux.cutils/gctrigger.dGCTRIGGER statements at the
  head of function bodies (for functions marked with
  the maygc pseudo-keyword).
utils/deema.c_EMA_ instead.
utils/ccmp2c.cclx/new-clx module only.
  Allows cpp-style preprocessing before modprep processing.
  Should be merged into modprep eventually.
utils/modprep.lispsrc/lispbibl.dsrc/fsubr.dsrc/subr.dsrc/pseudofun.dsrc/constpack.dsrc/constsym.dsrc/constobj.dsrc/unix.dsrc/win32.dsrc/xthread.dsrc/modules.hsrc/spvw.dMemory management (garbage-collection), startup; some OS interface.
src/avl.dsrc/sort.dsrc/subrkw.d
src/spvwtabf.dsrc/spvwtabs.dSYMBOLs accessed by C code.
src/spvwtabo.dsrc/eval.dEvaluator (form interpreter) and bytecode interpreter.
src/bytecode.dsrc/control.dsrc/pathname.dsrc/stream.dSTREAMs of all kinds: FILE-STREAMs,
   terminal streams, STRING-STREAMs
   etc.src/socket.dTCP/IP and CLX.
src/io.dsrc/array.dARRAYs and VECTORs.
src/hashtabl.dHASH-TABLEs.
src/list.dLISTs.
src/package.dPACKAGEs.
src/record.dsrc/sequence.dSEQUENCE functions.
src/funarg.d:TEST and :KEY.
src/charstrg.dCHARACTERs and STRINGs.
src/debug.dsrc/error.dsrc/errunix.dsrc/errwin32.dsrc/misc.dsrc/time.dsrc/predtype.dsrc/symbol.dSYMBOLs.
src/unixaux.dsrc/win32aux.dsrc/foreign.dsrc/lisparit.dsrc/noreadline.dsrc/lisparit.dsrc/aridecl.dsrc/arilev0.dsrc/arilev1.dsrc/arilev1c.dsrc/arilev1i.dsrc/arilev1e.dsrc/intelem.dINTEGERs: elementary operations
src/intlog.dINTEGERs: logical connectives
src/intplus.dINTEGERs: addition and subtraction
src/intcomp.dINTEGERs: comparison
src/intbyte.dINTEGERs: byte operations LDB, DPB
src/intmal.dINTEGERs: multiplication
src/intdiv.dINTEGERs: division
src/intgcd.dINTEGERs: GCD and LCM
src/int2adic.dINTEGERs: operations on 2-adic integers
src/intsqrt.dINTEGERs: square root, n-th root
src/intprint.dINTEGER output
src/intread.dINTEGER input
src/rational.dRATIOs)
src/sfloat.dSHORT-FLOATs
src/ffloat.dSINGLE-FLOATs
src/dfloat.dDOUBLE-FLOATs
src/lfloat.dLONG-FLOATs
src/flo_konv.dFLOATs
src/flo_rest.dFLOAT operations
src/realelem.dREAL numbers
src/realrand.dsrc/realtran.dREAL numbers
src/compelem.dCOMPLEX numbers
src/comptran.dCOMPLEX numbers
src/ari68000.dsrc/ari68020.dsrc/arisparc.dsrc/arisparc64.dsrc/ari80386.dsrc/arimips.dsrc/arimips64.dsrc/arihppa.dsrc/arivaxunix.dsrc/ariarm.dsrc/sp68000.dsrc/spsparc.dsrc/spsparc64.dsrc/sp80386.dsrc/spmips.dsrc/asmi386.shsrc/asmi386.hhsrc/init.lispsrc/defseq.lispsrc/backquote.lispsrc/defmacro.lispDEFMACROsrc/macros1.lispsrc/macros2.lispsrc/defs1.lispsrc/timezone.lispsrc/places.lispsrc/floatprint.lispSYS::WRITE-FLOAT-DECIMAL
   for printing floating point numbers in base 10
src/type.lispTYPEP,
   SUBTYPEPsrc/defstruct.lispDEFSTRUCT
src/format.lispFORMAT
src/room.lispROOM
   (see also Section 25.2.7, “Function ROOM”)src/savemem.lispsrc/keyboard.lispEXT:WITH-KEYBOARD
src/runprog.lispEXT:RUN-PROGRAM, EXT:RUN-SHELL-COMMAND etc.
src/query.lispY-OR-N-P and YES-OR-NO-P
src/reploop.lispsrc/dribble.lispDRIBBLE and
   EXT:DRIBBLE-STREAM
src/complete.lispsrc/describe.lispDESCRIBE, APROPOS,
   APROPOS-LISTsrc/trace.lispsrc/macros3.lisp (optional)EXT:LETF, EXT:LETF* and EXT:ETHE
src/config.lisp(user written) site-dependent configuration, may be a link to one of the following:
src/cfgsunux.lispsrc/cfgunix.lispsrc/cfgwin32.lispsrc/compiler.lispsrc/functions.lispFUNCTION-LAMBDA-EXPRESSION et al
src/disassem.lispDISASSEMBLE
src/defs2.lispsrc/loop.lispLOOP macro
src/clos.lisploads the various parts of the CLOS:
src/clos-package.lispsrc/clos-macros.lispsrc/clos-class0.lispclass-version
     structuresrc/clos-metaobject1.lispCLOS:METAOBJECT class
  src/clos-slotdef1.lispCLOS:SLOT-DEFINITION class and its
     subclassessrc/clos-slotdef2.lispINITIALIZE-INSTANCE methods for
     CLOS:SLOT-DEFINITION and its subclassessrc/clos-slotdef3.lispCLOS:SLOT-DEFINITION objectssrc/clos-stablehash1.lispEXT:STANDARD-STABLEHASH class
  src/clos-stablehash2.lispINITIALIZE-INSTANCE methods for
     EXT:STANDARD-STABLEHASHsrc/clos-specializer1.lispCLOS:SPECIALIZER class and its subclasses
  src/clos-specializer2.lispINITIALIZE-INSTANCE methods for
     CLOS:SPECIALIZER and its subclassessrc/clos-specializer3.lispCLOS:SPECIALIZER objectssrc/clos-class1.lisppotential-class
     class and its subclassessrc/clos-class2.lispsrc/clos-class3.lispDEFCLASS macro, class definition
     and class redefinitionsrc/clos-class4.lispINITIALIZE-INSTANCE methods
     for potential-class and its
     subclassessrc/clos-class5.lispMAKE-INSTANCE,
     INITIALIZE-INSTANCE etc.src/clos-class6.lisppotential-class objects
  src/clos-method1.lispMETHOD class and its subclasses
  src/clos-method2.lispDEFMETHOD
  src/clos-method3.lispMETHOD objectssrc/clos-method4.lispSTANDARD-METHOD
     objects extensiblesrc/clos-methcomb1.lispMETHOD-COMBINATION class
  src/clos-methcomb2.lispDEFINE-METHOD-COMBINATION macro
  src/clos-methcomb3.lispINITIALIZE-INSTANCE methods for
     METHOD-COMBINATIONsrc/clos-methcomb4.lispMETHOD-COMBINATION
     objects extensiblesrc/clos-genfun1.lispGENERIC-FUNCTION class and its
     metaclass, superclass and subclassessrc/clos-genfun2a.lispsrc/clos-genfun2b.lispsrc/clos-genfun3.lispDEFMETHOD, DEFGENERICsrc/clos-genfun4.lispINITIALIZE-INSTANCE methods for
     GENERIC-FUNCTION and its subclassessrc/clos-genfun5.lispGENERIC-FUNCTION
     objects extensiblesrc/clos-slots1.lispWITH-SLOTS,
     WITH-ACCESSORSsrc/clos-slots2.lispsrc/clos-dependent.lispsrc/clos-print.lispPRINT-OBJECT
  src/clos-custom.lispsrc/condition.lispsrc/gstream.lispsrc/foreign1.lispsrc/screen.lispsrc/edit.lisp
  (optional)ED), EXT:UNCOMPILE
src/inspect.lispINSPECT (tty and HTTP frontends)
src/clhs.lispEXT:OPEN-HTTP, EXT:BROWSE-URL
src/exporting.lispsrc/threads.lispsrc/spanish.lispsrc/german.lispsrc/french.lispsrc/russian.lispsrc/dutch.lispmodules/src/NEWSsrc/_READMEmaster for the distribution's README
src/_README.ensrc/_README.desrc/_README.essrc/_README
    doc/clisp.xml.inbuild-dir/clisp.1doc/clisp.xml.in
   at build timebuild-dir/clisp.htmldoc/clisp.xml.in
   at build timedoc/impnotes.xml.inthe master DocBook/XML file for these implementation notes; includes the following files
doc/cl-ent.xmldoc/clhs-ent.xmldoc/impent.xmldoc/unix-ent.xmldoc/mop-ent.xmldoc/impbody.xmldoc/impissue.xmldoc/gray.xmldoc/mop.xmldoc/impext.xmldoc/impbyte.xmldoc/faq.xmlmodules/**/*.xmldoc/Symbol-Table.textDESCRIBE).
    doc/impnotes.htmldoc/impnotes.xml.in
   at release timesrc/po/*.potsrc/po/*.posrc/po/*.gmosrc/configure.insrc/autoconf/autoconf.m4src/m4/src/configuresrc/configure.in
src/intparam.csrc/floatparam.csrc/config.h.insrc/configure.in.
   build-dir/config.hsrc/configure.
src/makemake.insrc/_clisp.csrc/_distmakefileTable of Contents
Abstract
These are internals, which are of interest only to the
   CLISP developers.  If you are not subscribed to <clisp-devel@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-devel), this
   chapter is probably not for you.
Knowing that most malloc implementations are buggy and/or slow,
and because CLISP needs to perform garbage-collection, CLISP has its
own memory management subsystem in files src/spvw*.d,
see Section 34.3.1.2, “Internal C Modules”.
Three kinds of storage are distinguished:
A CLISP object is one word, containing a tag (partial type
information) and either immediate data or a pointer to storage.
Pointers to C data have tag = machine_type = 0,
pointers to CLISP stack have tag = system_type,
most other pointers point to CLISP data.
Immediate objects
| FIXNUM | 
| SHORT-FLOAT | 
| CHARACTER | 
In addition to the above,
| SINGLE-FLOAT(withTYPECODES) | 
Let us turn to those CLISP objects that consume regular CLISP memory.
Every CLISP object has a size which is determined when the object is
allocated (using one of the allocate_*() routines).
The size can be computed from the type tag and - if necessary
- the length field of the object's header. The length field always
contains the number of elements of the object. The number of bytes is
given by the function objsize().
CLISP objects which contain exactly 2 CLISP objects
(i.e. CONSes, COMPLEX numbers, RATIOs) are
stored in a separate area and occupy 2 words each.
All other CLISP objects have “varying” length
(more precisely, not a fixed length) and include a word for garbage-collection
purposes at their beginning.
The garbage collector is invoked by
 allocate_*() calls according to certain heuristics.
It marks all objects which are “live”
(may be reached from the “roots”),
compacts these objects and unmarks them.
Non-live objects are lost; their storage is reclaimed.
2-pointer objects are compacted by a simple hole-filling algorithm: fill the left-most object into the right-most hole, and so on, until the objects are contiguous at the right and the hole is contiguous at the left.
Variable-length objects are compacted by sliding them down (their address decreases).
CLISP implements two ways of representing object pointers. (An object pointer, C type object, contains a pointer to the memory location of the object, or - for immediate object - all bits of the object itself.) Both of them have some things in common:
CHARACTERs, FIXNUMs, SHORT-FLOATs, etc) and
   heap allocated objects.CHANGE-CLASS is called. To avoid scanning all the heap for
   references when this happens, the class information is stored in the
   heap allocated object, not in the object pointer.The HEAPCODES object representation has a minimum of type
bits in the object pointer, namely, 2 bits. They allow to distinguish
immediate objects (which have some more type bits), CONSes (which
have no type bits in the heap, since they occupy just two words in the
heap, with no header), other heap objects (many, from SIMPLE-VECTORs
to FFI:FOREIGN-POINTERs), and Subrs. Most object types are
distinguished by looking a the rectype field
in the header of the heap object.
The TYPECODES object representation has about two dozen of types
encoded in 6 or 7 bits in the object pointer.
Typically these are the upper 8 bits of a word (on a 32-bit machine) or
the upper 16 bits or 32 bits of a word (on a 64-bit machine).
The particular values of the typecodes allow many common operations to
be performed with a single bit test (e.g. CONSP and MINUSP for a
REAL are bit tests) or range check.
However, the rectype field still exists for
many types, because there are many built-in types which do not need a
particularly fast type test.
Which object representation is chosen is decided at build time
depending on the available preprocessor definitions. You can define
TYPECODES or HEAPCODES to force one or the other.
One might expect that TYPECODES is faster than HEAPCODES
because it does not need to make as many memory accesses. This effect
is, however, hardly measurable in practice (certainly not more than 5%
faster).  Apparently because, first, the situations where the type of an
object is requested but then the object is not looked into are rare.
It is much more common to look into an object, regardless of its type.
Second, due to the existence of data caches in the CPU, accessing a heap
location twice, once for the type test and then immediately afterwards
for the data, is not significantly slower than just accessing the
data.
TYPECODES is problematic on 32-bit machines, when you want to
use more than 16 MB of memory, because the type bits (at bit 31..24)
interfere with the bits of a heap address. For this reason,
HEAPCODES is the default on 32-bit platforms.
HEAPCODES is problematic on platforms whose object alignment
is less than 4. This affects only the mc680x0 CPU; however, here the
alignment can usually be guaranteed through some gcc options.
There are 6 memory models. Which one is used, depends on the operating system and is determined at build time.
Memory Models
The heap consists of one block of fixed length (allocated at startup). The variable-length objects are allocated from the left, the 2-pointer objects are allocated from the right. There is a hole between them. When the hole shrinks to 0, garbage-collect is invoked. garbage-collect slides the variable-length objects to the left and concentrates the 2-pointer objects at the right end of the block again. When no more room is available, some reserve area beyond the right end of the block is halved, and the 2-pointer objects are moved to the right accordingly.
Advantages and Disadvantages
| (+) | Simple management. | 
| (+) | No fragmentation at all. | 
| (-) | The total heap size is limited. | 
The heap consists of two big blocks, one for variable-length objects and one for 2-pointer objects. The former one has a hole to the right and is extensible to the right, the latter one has a hole to the left and is extensible to the left. Similar to the previous model, except that the hole is unmapped.
Advantages and Disadvantages
| (+) | Total heap size grows depending on the application's needs. | 
| (+) | No fragmentation at all. | 
| (*) | Works only when SINGLEMAP_MEMORY is possible as well. | 
The heap consists of two big blocks, one for variable-length objects and one for 2-pointer objects. Both have a hole to the right, but are extensible to the right.
Advantages and Disadvantages
| (+) | Total heap size grows depending on the application's needs. | 
| (+) | No fragmentation at all. | 
| (*) | Works only when SINGLEMAP_MEMORY is possible as well. | 
The heap consists of many small pages (usually around 8 KB). There are two kinds of pages: one for 2-pointer objects, one for variable-length objects. The set of all pages of a fixed kind is called a "Heap". Each page has its hole (free space) at its end. For every heap, the pages are kept sorted according to the size of their hole, using AVL trees. The garbage-collection is invoked when the used space has grown by 25% since the last GC; until that point new pages are allocated from the OS. The GC compacts the data in each page separately: data is moved to the left. Emptied pages are given back to the OS. If the holes then make up more than 25% of the occupied storage, a second GC turn moves objects across pages, from nearly empty ones to nearly full ones, with the aim to free as many pages as possible.
Advantages and Disadvantages
| (-) | Every allocation requires AVL tree operations, thus slower | 
| (+) | Total heap size grows depending on the application's needs. | 
| (+) | Works on operating systems which do not provide large contiguous areas. | 
Just like SPVW_MIXED_PAGES, except that every page contains data of only a single type tag, i.e. there is a Heap for every type tag.
Advantages and Disadvantages
| (-) | Every allocation requires AVL tree operations, thus slower | 
| (+) | Total heap size grows depending on the application's needs. | 
| (+) | Works on operating systems which do not provide large contiguous areas. | 
| (-) | More fragmentation because objects of different type never fit into the same page. | 
There is a big block of storage for each type tag. Each of these blocks has its data to the left and the hole to the right, but these blocks are extensible to the right (because there is enough room between them). A garbage-collection is triggered when the allocation amount since the last GC reaches 50% of the amount of used space at the last GC, but at least 512 KB. The garbage-collection cleans up each block separately: data is moved left.
Advantages and Disadvantages
| (+) | Total heap size grows depending on the application's needs. | 
| (+) | No 16 MB total size limit. | 
| (*) | Works only in combination with SINGLEMAP_MEMORY. | 
In page based memory models, an object larger than a page is the only object carried by its pages. There are no small objects in pages belonging to a big object.
The following combinations of memory model and
 mmap tricks are possible (the number
 indicates the order in which the respective models have been
 developed):
Table 35.1. Memory models with TYPECODES
Table 35.2. Memory models with HEAPCODES
Every subroutine marked with “can trigger GC”
or maygc may invoke garbage-collection.
garbage-collector moves all the CLISP non-immediate objects and updates the pointers.
But the garbage-collector looks only at the STACK and not in the C
variables. (Anything else would not be portable.)
Therefore at every "unsafe" point, i.e. every call to such a subroutine,
all the C variables of type object
MUST BE ASSUMED TO BECOME GARBAGE.
(Except for objects that are known to be unmovable,
 e.g. immediate objects or Subrs.)
Pointers inside CLISP data (e.g. to the characters of a STRING
or to the elements of a SIMPLE-VECTOR) become
INVALID as well.
The workaround is usually to allocate all the needed CLISP data first and do the rest of the computation with C variables, without calling unsafe routines, and without worrying about garbage-collection.
Alternatively, you can save a lisp object on the STACK using
macros pushSTACK() and popSTACK().
One should not mix these macros in one statement because C may execute different parts of the statement out of order. E.g.,
pushSTACK(listof(4));
is illegal.
Run-time GC-safety checking is available when you build CLISP with a C++ compiler, e.g.:
$ CC=g++ ./configure --with-debug build-g-gxx
When built like this, CLISP will abort
when you reference GC-unsafe data after an allocation (which could have
triggered a garbage-collection), and gdb will pinpoint the trouble spot.
Specifically, when CLISP is configured
 as above, there is a
global integer variable alloccount and the object
structure contains an integer allocstamp
slot. If these two integers are not the same, the object is invalid.
By playing with gdb, you should be able to figure out the precise spot
where an allocation increments alloccount
after the object has been retrieved from a GC-visible location.
Generational garbage-collector uses memory protection, so when passing pointers
 into the lisp heap to C functions, you may encounter errors
 (errno=EFAULT) unless you call
 handle_fault_range(protection,region_start,region_end)
 on the appropriate memory region.  See files 
| src/unixaux.d | 
| src/win32aux.d | 
| modules/syscalls/calls.c | 
| modules/rawsock/rawsock.c | 
for examples.
Pointers to C functions and to malloced data can be
hidden in CLISP objects of type machine_type;
garbage-collect will not modify its value.
But one should not dare to assume that a C stack pointer
or the address of a C function in a shared library satisfies the
same requirements.
If another pointer is to be viewed as a CLISP object, it is best
to box it, e.g. in a SIMPLE-BIT-VECTOR or in an
Fpointer (using allocate_fpointer().)
Table of Contents
Common Lisp is a programmable programming language.
CLISP can be easily extended the same way any other Common Lisp
 implementation can: create a lisp file with your variables, functions,
 macros, etc.; (optionally) compile it with COMPILE-FILE; LOAD it
 into a running CLISP, and save the memory image.
This method does not work when you need to use some functionality not available in CLISP, e.g., you want to call a C function. You are urged to use External Modules instead of adding built-in functions.
CLISP comes with an “FFI” which allows you
 to access C libraries in an easy way (including creating
 FFI:FOREIGN-FUNCTIONs dynamically).
In the rare cases when you really need to modify CLISP internals and add a truly built-in function, you should read the CLISP sources for inspiration and enlightenment, choose a file where your brand-new built-in function should go to, and then ...
LISPFUN
    form and the implementation there;LISPFUN header to
    file subr.d;constsym.d in the appropriate package
    (probably “EXT”, if there is no specific package);
  subrkw.d and you must make sure that the
    keyword symbols are declared in constsym.d;
  init.lisp;subr.d, subrkw.d and fsubr.d) are in sync.Be very careful with the GC-unsafe functions! Always remember about GC-safety!
These instructions are intentionally terse - you are encouraged to use modules and/or “FFI” instead of adding built-ins directly.
If you must be able to access the Lisp variable in the C code, follow these steps:
constsym.d in the appropriate package
    (probably “CUSTOM”, if there is no specific package);
  define_variable() call
    in function init_symbol_values()
    in file spvw.d;init.lisp;Any change that forces
 make to remake lisp.run,
 will force recompilation of all #P".lisp" files and
 re-dumping of lispinit.mem, which may be time-consuming.  This is not
 always necessary, depending on what kind of change you introduced.
On the other hand, if you change any of the following files:
| constobj.d | 
| constsym.d | 
| fsubr.d | 
| subr.d | 
| subrkw.d | 
 your lispinit.mem will have to be re-dumped.
If you change the signature of any
 system function mentioned in the FUNTAB arrays in
 file eval.d, all the #P".fas" files will
 become obsolete and will need to be recompiled.
 You will need to add a note to that effect to
 the src/NEWS file
 and augment the object version in
 file constsym.d.
  Please try to avoid this as much as possible.
Table of Contents
BLOCK and RETURN-FROMTAGBODY and GOCATCH and THROWUNWIND-PROTECTHANDLER-BINDThe CLISP compiler compiles Common Lisp programs into instruction codes for a virtual processor. This bytecode is optimized for saving space in the most common cases of Common Lisp programs. The main advantages/drawbacks of this approach, compared to native code compilation, are:
CAR/CDR), programs run with all safety
   checks enabled even when compiled.DISASSEMBLE function.
   A rule of thumb is that every elementary instruction costs 1 time
   unit, whereas a function call costs 3 to 4 time units.
  
The bytecode can be thought of as being interpreted by a virtual processor. The engine which interprets the bytecode (the “implementation of the virtual machine”) is actually a C function, but it could as well be a just-in-time compiler which translates a function's bytecode into hardware CPU instructions the first time said function is called.
The virtual machine is a stack machine with two stacks:
This two-stack architecture permits to save an unlimited number of
CLISP objects on the STACK (needed for handling of Common Lisp multiple values),
without consing[3].  Also, in a world with a compacting no-ambiguous-roots
garbage collector, STACK must only hold CLISP objects, and SP can
hold all the other data belonging to a frame, which would not fit into
STACK without tagging/untagging overhead.
The scope of STACK and SP is only valid for a given function
invocation.  Whereas the amount of STACK space needed for executing a
function (excluding other function calls) is unlimited, the amount of
SP space needed is known a priori, at compile time.  When a function
is called, no relation is specified between the caller's STACK and the
callee's STACK, and between the caller's SP and the callee's SP.
The bytecode is designed so that outgoing arguments on the caller's
STACK can be shared by the caller's incoming arguments area (on the
callee's STACK), but a virtual machine implementation may also copy
outgoing arguments to incoming arguments instead of sharing them.
The virtual machine has a special data structure,
values, containing the “top of stack”,
specially adapted to Common Lisp multiple values:
The contents of values is short-lived.
It does not survive a function call, not even a garbage-collection.
The interpretation of some bytecode instructions depends on a
constant, jmpbufsize.  This is a CPU-dependent number, the value of
SYSTEM::*JMPBUF-SIZE*.  In C, it is defined as
ceiling(sizeof(jmp_buf),sizeof(void*)).
A compiled function consists of two objects: The function itself, containing the references to all CLISP objects needed for the bytecode, and a byte vector containing only immediate data, including the bytecode proper.
Typically, the byte vector is about twice as large as the function vector. The separation thus helps the garbage collector (since the byte vector does not need to be scanned for pointers).
A function looks like this (cf. the C type Cclosure):
(SETF symbol).
   It is used for printing the function and for error messages.
   This field is immutable.codevec(VECTOR (UNSIGNED-BYTE 8)).
    This field is immutable.consts[]CONSes or VECTORs, however.)
 When a generic function's dispatch code is installed, the codevec
  and consts fields are destructively modified.
Some of the consts can play special roles.
 A function looks like this, in more detail:
codeveccodevec.
 venv-const*SIMPLE-VECTOR, which
   looks like this: #(next
   value1 ...
   valuen)
   where value1, ...,
   valuen
   are the values of the closed-up variables,
   and next is either NIL or a SIMPLE-VECTOR having the same
   structure.block-const*BLOCK tags,
   representing the BLOCK tags of the lexical environment in which
   this function was defined.  Each is a CONS containing in the
   CDR part: either a frame pointer to the block frame, or #<DISABLED>.
   The CAR is the block's name, for error messages only.
  tagbody-const*TAGBODY tags,
   representing the TAGBODY tags of the lexical environment in which
   this function was defined.  Each is a CONS containing in the
   CDR part: either a frame pointer to the TAGBODY frame, or
   #<DISABLED> if the TAGBODY has already been left.  The CAR is a
   SIMPLE-VECTOR containing the names of the TAGBODY tags,
   for error messages only.keyword-const*&KEY, here come the symbols ("keywords"), in their
   correct order.  They are used by the interpreter during function call.
  other-const*
If venv-const, block-const, tagbody-const are all absent,
the function is called autonomous.
This is the case if the function does not refer to lexical variables,
blocks or tags defined in compile code outside of the function.
In particular, it is the case if the function is defined in a null
lexical environment.
If some venv-const, block-const, or tagbody-const are
present, the function (a “closure”) is created at runtime.
The compiler only generates a prototype, containing NIL values
instead of each venv-const, block-const, tagbody-const.
At runtime, a function is created by copying this prototype and
replacing the NIL values by the definitive ones.
The list ( normally does not contain duplicates, because
the compiler removes duplicates when possible.  (Duplicates can occur
nevertheless, through the use of keyword-const*
other-const*)LOAD-TIME-VALUE.)
The codevec looks like this
 (cf. the C type Codevec):
spdepth_1 (2 bytes)SP depth.
  spdepth_jmpbufsize (2 bytes)jmpbufsize part of the maximal SP depth.
   The maximal SP depth (precomputed by the compiler) is given by
   spdepth_1 + spdepth_jmpbufsize * jmpbufsize.
  numreq (2 bytes)numopt (2 bytes)flags (1 byte)&REST parameter
    &KEY parameters
    &ALLOW-OTHER-KEYS
    signature (1 byte)numreq, numopt, flags.
    It is used for speeding up the function
    call.numkey (2 bytes, only if the
     function has &KEY)&KEY parameters.
   keyconsts (2 bytes, only if the
     function has &KEY)keyword-const in the function.
   byte* (any number of bytes)All instructions consist of one byte, denoting the opcode, and some number of operands.
The conversion from a byte (in the range 0..255) to the opcode is
performed by lookup in the table contained in the file bytecode.d.
There are the following types of operands, denoted by different letters:
k, n, m, lblabelBLOCK and RETURN-FROMTAGBODY and GOCATCH and THROWUNWIND-PROTECTHANDLER-BIND| mnemonic | description | semantics | 
|---|---|---|
| ( | Load NILinto values. | value1:=NIL,mv_count:= 1 | 
| (PUSH-NIL  | Push nNILs into theSTACK. | ntimes do: *--STACK:=NIL,
             values undefined | 
| ( | Load Tinto values. | value1:=T,mv_count:= 1 | 
| (CONST  | Load the function's nth constant into values. | value1:=consts[n],mv_count:= 1 | 
| mnemonic | description | semantics | 
|---|---|---|
| (LOAD  | Load a directly accessible local variable into values. | value1:= *(STACK+n),mv_count:= 1 | 
| (LOADI  | Load an indirectly accessible local variable into values. | k:=k1+jmpbufsize*k2,value1:= *(*(SP+k)+n),mv_count:= 1 | 
| (LOADC  | Load a closed-up variable, defined in the same function and directly accessible, into values. | value1:=SVREF(*(STACK+n),1+m),mv_count:= 1 | 
| (LOADV  | Load a closed-up variable, defined in an outer function, into values. | v:=venv-const,mtimes do:v:=SVREF(v,0),value1:=SVREF(v,m),mv_count:= 1 | 
| (LOADIC  | Load a closed-up variable, defined in the same function and indirectly accessible, into values. | k:=k1+jmpbufsize*k2,value1:=SVREF(*(*(SP+k)+n),1+m),mv_count:= 1 | 
| (STORE  | Store values into a directly accessible local variable. | *( STACK+n) :=value1,mv_count:= 1 | 
| (STOREI  | Store values into an indirectly accessible local variable. | k:=k1+jmpbufsize*k2,
              *(*(SP+k)+n) :=value1,mv_count:= 1 | 
| (STOREC  | Store values into a closed-up variable, defined in the same function and directly accessible. | SVREF(*(STACK+n),1+m) :=value1,mv_count:= 1 | 
| (STOREV  | Store values into a closed-up variable, defined in an outer function. | v:=venv-const,mtimes do:v:=SVREF(v,0),SVREF(v,m) :=value1,mv_count:= 1 | 
| (STOREIC  | Store values into a closed-up variable, defined in the same function and indirectly accessible. | k:=k1+jmpbufsize*k2,SVREF(*(*(SP+k)+n),1+m) :=value1,mv_count:= 1 | 
| mnemonic | description | semantics | 
|---|---|---|
| (GETVALUE  | Load a symbol's value into values. | value1:= symbol-value(consts[n]),mv_count:= 1 | 
| (SETVALUE  | Store values into a symbol's value. | symbol-value( consts[n]) :=value1,mv_count:= 1 | 
| (BIND  | Bind a symbol dynamically. | Bind the value of the symbol consts[n] tovalue1,
             implicitlySTACK-= 3,
             values undefined | 
| (UNBIND1) | Dissolve one binding frame. | Unbind the binding frame STACKis pointing to,
             implicitlySTACK+= 3 | 
| (UNBIND  | Dissolve nbinding frames. | ntimes do:
              Unbind the binding frameSTACKis pointing to, thereby
              incrementingSTACKThus,STACK+= 1+2*n | 
| (PROGV) | Bind a set of symbols dynamically to a set of values. | symbols:= *STACK++,
             *--SP:=STACK,
             build a single binding frame binding the symbols insymbolsto the values invalue1,
             values undefined | 
| mnemonic | description | semantics | 
|---|---|---|
| (PUSH) | Push one object onto the STACK. | *-- STACK:=value1,
             values undefined | 
| (POP) | Pop one object from the STACK, into values. | value1:= *STACK++,mv_count:= 1 | 
| (SKIP  | Restore a previous STACKpointer.
             Removenobjects from theSTACK. | STACK:=STACK+n | 
| (SKIPI  | Restore a previous STACKpointer. Remove an unknown
             number of objects from theSTACK. | k:=k1+jmpbufsize*k2,STACK:= *(SP+k),SP:=SP+k+1,STACK:=STACK+n | 
| (SKIPSP  | Restore a previous SPpointer. | k:=k1+jmpbufsize*k2,SP:=SP+k | 
| mnemonic | description | semantics | 
|---|---|---|
| (SKIP&RET  | Clean up the STACK, and return from the function. | STACK:=STACK+n,
            return from the function, returning values. | 
| (SKIP&RETGF  | Clean up the STACK, and return from the generic
             function. | If bit 3 is set in the function's flags,
                thenSTACK:=STACK+n,mv_count:= 1,
                     and return from the function.
             Otherwise: if the current function has no&RESTargument,
                thenSTACK:=STACK+n-numreq,
                     applyvalue1to thenumreqarguments
                           still on theSTACK, and
                           return from the function.
                ElseSTACK:=STACK+n-numreq-1,
                     applyvalue1to thenumreqarguments and the&RESTargument, all still on theSTACK, and
                           return from the function. | 
| (JMP  | Jump to label. | PC := label. | 
| (JMPIF  | Jump to label, ifvalue1is true. | If value1is notNIL, PC :=label. | 
| (JMPIFNOT  | Jump to label, ifvalue1is false. | If value1isNIL, PC :=label. | 
| (JMPIF1  | Jump to labeland forget secondary values,
             ifvalue1is true. | If value1is notNIL,mv_count:= 1, PC :=label. | 
| (JMPIFNOT1  | Jump to labeland forget secondary values,
             ifvalue1is false. | If value1isNIL,mv_count:= 1, PC :=label. | 
| (JMPIFATOM  | Jump to label, ifvalue1is not a cons. | If value1is not a cons, PC :=label.
             values undefined | 
| (JMPIFCONSP  | Jump to label, ifvalue1is a cons. | If value1is a cons, PC :=label.
                values undefined | 
| (JMPIFEQ  | Jump to label, ifvalue1isEQto the top-of-stack. | If eq( value1,*STACK++), PC :=label.
             values undefined | 
| (JMPIFNOTEQ  | Jump to label, ifvalue1is notEQto the top-of-stack. | If not eq( value1,*STACK++), PC :=label.
             values undefined | 
| (JMPIFEQTO  | Jump to label,
             if the top-of-stack isEQto a constant. | If eq(* STACK++,consts[n]), PC :=label.
             values undefined | 
| (JMPIFNOTEQTO  | Jump to label, if the top-of-stack is notEQto a constant. | If not eq(* STACK++,consts[n]), PC :=label.
             values undefined | 
| (JMPHASH  | Table-driven jump, depending on value1. | Lookup value1in the hash tableconsts[n].
             (The hash table's test is eitherEQorEQL.)
             If found, the hash table value is a signedFIXNUM,
             jump to it: PC := PC + value.  Else jump tolabel.
             values undefined | 
| (JMPHASHV  | Table-driven jump, depending on value1,
             inside a generic function. | Lookup value1in the hash tableSVREF(consts[0],n).
             (The hash table's test is eitherEQorEQL.)
             If found, the hash table value is a signedFIXNUM,
             jump to it: PC := PC + value.  Else jump tolabel.
             values undefined | 
| (JSR  | Subroutine call. | *-- STACK:= function. Then start interpreting the
             bytecode atlabel, with values undefined.
             When a(RET)is encountered,
             program execution is resumed at the instruction after(JSR . | 
| (JMPTAIL  | Tail subroutine call. | n>=m.
             TheSTACKframe of sizenis reduced to sizem:
             {*(STACK+n-m), ..., *(STACK+n-1)} :=
               {*STACK, ..., *(STACK+m-1)}.STACK+= n-m.
             *--STACK:= function.
             Then jump tolabel, with values undefined. | 
| mnemonic | description | semantics | 
|---|---|---|
| (VENV) | Load the venv-constinto values. | value1:=consts[0],mv_count:= 1. | 
| (MAKE-VECTOR1&PUSH  | Create a SIMPLE-VECTORused for closed-up variables. | v:= newSIMPLE-VECTORof sizen+1.SVREF(v,0) :=value1.
             *--STACK:=v.
             values undefined | 
| (COPY-CLOSURE  | Create a closure by copying the prototype and filling in the lexical environment. | f:= copy-function(consts[m]).
             Fori=0,..,n-1:f_consts[i] := *(STACK+n-1-i).STACK+=n.value1:=f,mv_count:= 1 | 
| mnemonic | description | semantics | 
|---|---|---|
| (CALL  | Calls a constant function with karguments. | The function consts[n] is called
             with the arguments *(STACK+k-1), ..., *(STACK+0).STACK+=k.
             The returned values go into values. | 
| (CALL0  | Calls a constant function with 0 arguments. | The function consts[n] is called with 0 arguments.
             The returned values go into values. | 
| (CALL1  | Calls a constant function with 1 argument. | The function consts[n] is called with one argument *STACK.STACK+= 1. The returned values go into values. | 
| (CALL2  | Calls a constant function with 2 arguments. | The function consts[n] is called
             with two arguments *(STACK+1) and *(STACK+0).STACK+= 2. The returned values go into values. | 
| (CALLS1  | Calls a system function with no &REST. | Calls the system function FUNTAB[ b].
             The right number of arguments is already on theSTACK(including#<UNBOUND>s in place of absent&OPTIONALor&KEYparameters).
             The arguments are removed from theSTACK.
             The returned values go into values. | 
| (CALLS2  | Calls a system function with no &REST. | Calls the system function FUNTAB[256+ b].
             The right number of arguments is already on theSTACK(including#<UNBOUND>s in place of absent&OPTIONALor&KEYparameters).
             The arguments are removed from theSTACK.
             The returned values go into values. | 
| (CALLSR  | Calls a system function with &REST. | Calls the system function FUNTABR[ b].
             The minimum number of arguments is already on theSTACK,
             andmadditional arguments as well.
             The arguments are removed from theSTACK.
             The returned values go into values. | 
| (CALLC) | Calls a computed compiled function with no &KEY. | Calls the compiled function value1.
             The right number of arguments is already on theSTACK(including#<UNBOUND>s in place of absent&OPTIONALparameters).
             The arguments are removed from theSTACK.
             The returned values go into values. | 
| (CALLCKEY) | Calls a computed compiled function with &KEY. | Calls the compiled function value1.
             The right number of arguments is already on theSTACK(including#<UNBOUND>s in place of absent&OPTIONALor&KEYparameters).
             The arguments are removed from theSTACK.
             The returned values go into values. | 
| (FUNCALL  | Calls a computed function. | Calls the function *( STACK+n)
             with the arguments *(STACK+n-1), ..., *(STACK+0).STACK+=n+1.
             The returned values go into values. | 
| (APPLY  | Calls a computed function with an unknown number of arguments. | Calls the function *( STACK+n)
             with the arguments *(STACK+n-1), ..., *(STACK+0)
             and a list of additional argumentsvalue1.STACK+=n+1.
             The returned values go into values. | 
| mnemonic | description | semantics | 
|---|---|---|
| (PUSH-UNBOUND  | Push n#<UNBOUND>s into theSTACK. | ntimes do: *--STACK:=#<UNBOUND>.
             values undefined | 
| (UNLIST  | Destructure a proper LIST. | 0 ≤ m≤n.ntimes do: *--STACK:=CAR(value1),value1:=CDR(value1).
             During the lastmiterations, the listvalue1may already have reached its end;
             in this case, *--STACK:=#<UNBOUND>.
             At the end,value1must beNIL.
             values undefined | 
| (UNLIST*  | Destructure a proper or dotted LIST. | 0 ≤ m≤n,n> 0.ntimes do: *--STACK:=CAR(value1),value1:=CDR(value1).
             During the lastmiterations, the listvalue1may already have reached its end;
             in this case, *--STACK:=#<UNBOUND>.
             At the end, afternCDRs, *--STACK:=value1.
             values undefined | 
| (JMPIFBOUNDP  | Jump to label, if a local variable is not unbound. | If *( STACK+n) is not#<UNBOUND>,value1:= *(STACK+n),mv_count:= 1, PC :=label.
             Else: values undefined. | 
| (BOUNDP  | Load TorNILinto values, depending on whether a local
             variable is bound. | If *( STACK+n) is not#<UNBOUND>,value1:=T,mv_count:= 1.
             Else:value1:=NIL,mv_count:= 1. | 
| (UNBOUND->NIL  | If a local variable is unbound, assign a default value NILto it. | If *( STACK+n) is#<UNBOUND>,
             *(STACK+n) :=NIL. | 
| mnemonic | description | semantics | 
|---|---|---|
| (VALUES0) | Load no values into values. | value1:=NIL,mv_count:= 0 | 
| (VALUES1) | Forget secondary values. | mv_count:= 1 | 
| ( | Pop the first nobjects fromSTACKinto values. | Load values(*( STACK+n-1),...,*(STACK+0)) into
             values.STACK+=n. | 
| (MV-TO- | Save values on STACK. | Push the mv_countvalues onto theSTACK(in order:value1comes first).STACK-=mv_count.
             values undefined | 
| (NV-TO- | Save nvalues onSTACK. | Push the first nvalues onto theSTACK(in order:value1comes first).STACK-=n.
             values undefined | 
| (MV-TO-LIST) | Convert multiple values into a list. | value1:= list of values,mv_count:= 1 | 
| (LIST-TO-MV) | Convert a LISTinto multiple values. | Call the function VALUES-LISTwithvalue1as argument.
             The returned values go into values. | 
| (MVCALLP) | Start a MULTIPLE-VALUE-CALLinvocation. | *-- SP:=STACK. *--STACK:=value1. | 
| (MVCALL) | Finish a MULTIPLE-VALUE-CALLinvocation. | newSTACK := * SP++.
             Call the function *(newSTACK-1), passing it
             *(newSTACK-2), ..., *(STACK+0) as arguments.STACK:= newSTACK.
             The returned values go into values. | 
BLOCK and RETURN-FROM| mnemonic | description | semantics | 
|---|---|---|
| (BLOCK-OPEN  | Create a BLOCKframe. | Create a BLOCKframe,STACK-= 3,SP-= 2+jmpbufsize.
   The topmost (third) object in the block frame isCONS(consts[n],frame-pointer) (itsblock-cons).
   Upon aRETURN-FROMto this frame, execution will continue atlabel.
   values undefined. | 
| (BLOCK-CLOSE) | Dissolve a BLOCKframe. | Dissolve the BLOCKframe atSTACK,STACK+= 3,SP+= 2+jmpbufsize. Mark theblock-consas invalid. | 
| (RETURN-FROM  | Leave a BLOCKwhoseblock-consis given. | block-cons:=consts[n].
             IfCDR(block-cons) =#<DISABLED>, anERRORisSIGNALed.
             ElseCDR(block-cons) is a frame-pointer.
             Unwind the stack up to this frame, pass it values. | 
| (RETURN-FROM-I  | Leave a BLOCKwhoseblock-consis indirectly accessible. | k:=k1+jmpbufsize*k2,block-cons:= *(*(SP+k)+n).
             IfCDR(block-cons) =#<DISABLED>, anERRORisSIGNALed.
             ElseCDR(block-cons) is a frame-pointer.
             Unwind the stack up to this frame, pass it values. | 
| mnemonic | description | semantics | 
|---|---|---|
| (TAGBODY-OPEN  | Create a TAGBODYframe. | Fetch consts[m], this is aSIMPLE-VECTORwithnelements, then decodenlabel operands.
             Create aTAGBODYframe,STACK-= 3+n,SP-= 1+jmpbufsize.
             The third object in theTAGBODYframe isCONS(consts[m],frame-pointer) (thetagbody-cons)
             Upon aGOto taglabelof this frame, execution
             will continue atlabell.
             values undefined | 
| (TAGBODY-CLOSE-NIL) | Dissolve a TAGBODYframe, and loadNILinto values. | Dissolve the TAGBODYframe atSTACK,STACK+= 3+m,SP+= 1+jmpbufsize.
             Mark thetagbody-consas invalid.value1:=NIL,mv_count:= 1. | 
| (TAGBODY-CLOSE) | Dissolve a TAGBODYframe. | Dissolve the TAGBODYframe atSTACK,STACK+= 3+m,SP+= 1+jmpbufsize.
             Mark thetagbody-consas invalid. | 
| (GO  | Jump into a TAGBODYwhosetagbody-consis given. | tagbody-cons:=consts[n].
             IfCDR(tagbody-cons) =#<DISABLED>, anERRORisSIGNALed.
             ElseCDR(tagbody-cons) is a frame-pointer. Unwind the stack up
             to this frame, pass it the numberlabel. | 
| (GO-I  | Jump into a TAGBODYwhosetagbody-consis indirectly
             accessible. | k:=k1+jmpbufsize*k2,tagbody-cons:= *(*(SP+k)+n).
             IfCDR(tagbody-cons) =#<DISABLED>, anERRORisSIGNALed.
             ElseCDR(tagbody-cons) is a frame-pointer. Unwind the stack up
             to this frame, pass it the numberlabel. | 
| mnemonic | description | semantics | 
|---|---|---|
| (CATCH-OPEN  | Create a CATCHframe. | Create a CATCHframe, withvalue1as tag.STACK-= 3,SP-= 2+jmpbufsize.
             Upon aTHROWto this tag execution continues atlabel. | 
| (CATCH-CLOSE) | Dissolve a CATCHframe. | Dissolve the CATCHframe atSTACK.STACK+= 3,SP+= 2+jmpbufsize. | 
| (THROW) | Non-local exit to a CATCHframe. | tag:= *STACK++.
             Search the innermostCATCHframe with tagtagon theSTACK, unwind the
             stack up to it, pass it values. | 
UNWIND-PROTECT| mnemonic | description | semantics | 
|---|---|---|
| (UNWIND-PROTECT-OPEN
              | Create an UNWIND-PROTECTframe. | Create an UNWIND-PROTECTframe.STACK-= 2,SP-= 2+jmpbufsize.
             When the stack will be unwound by a non-local exit,
             values will be saved onSTACK, and execution will be
             transferred tolabel. | 
| (UNWIND-PROTECT-NORMAL-EXIT) | Dissolve an UNWIND-PROTECTframe, and start the cleanup
             code. | Dissolve the UNWIND-PROTECTframe atSTACK.STACK+= 2,SP+= 2+jmpbufsize.
             *--SP:= 0, *--SP:= 0, *--SP:=STACK.
             Save the values on theSTACK,STACK-=mv_count. | 
| (UNWIND-PROTECT-CLOSE) | Terminate the cleanup code. | newSTACK := * SP++. Load
             values(*(newSTACK-1), ..., *(STACK+0)) into values.STACK:= newSTACK. SPword1 := *SP++, SPword2 := *SP++.
             Continue depending on SPword1 and SPword2.
             If both are 0, simply continue execution.
             If SPword2 is 0 but SPword1 is nonzero, interpret it as a
             label and jump to it. | 
| (UNWIND-PROTECT-CLEANUP) | Dissolve an UNWIND-PROTECTframe, and execute the cleanup
             code like a subroutine call. | Dissolve the UNWIND-PROTECTframe atSTACK,
             getlabelout of the frame.STACK+= 2,SP+= 2+jmpbufsize.
             *--SP:= 0, *--SP:= PC, *--SP:=STACK.
             Save the values on theSTACK,STACK-=mv_count.
             PC :=label. | 
HANDLER-BIND| mnemonic | description | semantics | 
|---|---|---|
| (HANDLER-OPEN  | Create a handler frame. | Create a handler frame, using consts[n] which
             contains theCONDITIONtypes, the corresponding labels and
             the currentSPdepth (= function entrySP- currentSP). | 
| (HANDLER-BEGIN&PUSH) | Start a handler. | Restore the same SPstate as after the HANDLER-OPEN.value1:= theCONDITIONthat was passed to the handler,mv_count:= 1.
             *--STACK:=value1. | 
| mnemonic | description | semantics | 
|---|---|---|
| (NOT) | Inlined call to NOT. | value1:= not(value1),mv_count:= 1. | 
| (EQ) | Inlined call to EQ. | value1:= eq(*STACK++,value1),mv_count:= 1. | 
| (CAR) | Inlined call to CAR. | value1:=CAR(value1),mv_count:= 1. | 
| (CDR) | Inlined call to CDR. | value1:=CDR(value1),mv_count:= 1. | 
| (CONS) | Inlined call to CONS. | value1:= cons(*STACK++,value1),mv_count:= 1. | 
| (SYMBOL-FUNCTION) | Inlined call to SYMBOL-FUNCTION. | value1:=SYMBOL-FUNCTION(value1),mv_count:= 1. | 
| (SVREF) | Inlined call to SVREF. | value1:=SVREF(*STACK++,value1),mv_count:= 1. | 
| (SVSET) | Inlined call to (. | arg1:= *(STACK+1),arg2:= *(STACK+0),STACK+= 2.SVREF(arg2,value1) :=arg1.value1:=arg1,mv_count:= 1. | 
| (LIST  | Inlined call to LIST. | value1:=LIST(*(STACK+n-1),...,*(STACK+0)),mv_count:= 1,STACK+=n. | 
| (LIST*  | Inlined call to LIST*. | value1:=LIST*(*(STACK+n-1),...,
                                     *(STACK+0),value1),mv_count:= 1,STACK+=n. | 
The most frequent short sequences of instructions have an
equivalent combined instruction.  They are only present for space and
speed optimization. The only exception is
FUNCALL&SKIP&RETGF, which is needed for
generic functions.
| mnemonic | equivalent | 
|---|---|
| (NIL&PUSH) | (NIL) (PUSH) | 
| (T&PUSH) | (T) (PUSH) | 
| (CONST&PUSH  | (CONST  | 
| (LOAD&PUSH  | (LOAD  | 
| (LOADI&PUSH  | (LOADI  | 
| (LOADC&PUSH  | (LOADC  | 
| (LOADV&PUSH  | (LOADV  | 
| (POP&STORE  | (POP) (STORE  | 
| (GETVALUE&PUSH  | (GETVALUE  | 
| (JSR&PUSH  | (JSR  | 
| (COPY-CLOSURE&PUSH  | (COPY-CLOSURE  | 
| (CALL&PUSH  | (CALL  | 
| (CALL1&PUSH  | (CALL1  | 
| (CALL2&PUSH  | (CALL2  | 
| (CALLS1&PUSH  | (CALLS1  | 
| (CALLS2&PUSH  | (CALLS2  | 
| (CALLSR&PUSH  | (CALLSR  | 
| (CALLC&PUSH) | (CALLC) (PUSH) | 
| (CALLCKEY&PUSH) | (CALLCKEY) (PUSH) | 
| (FUNCALL&PUSH  | (FUNCALL  | 
| (APPLY&PUSH  | (APPLY  | 
| (CAR&PUSH) | (CAR) (PUSH) | 
| (CDR&PUSH) | (CDR) (PUSH) | 
| (CONS&PUSH) | (CONS) (PUSH) | 
| (LIST&PUSH  | (LIST  | 
| (LIST*&PUSH  | (LIST*  | 
| (NIL&STORE  | (NIL) (STORE  | 
| (T&STORE  | (T) (STORE  | 
| (LOAD&STOREC  | (LOAD  | 
| (CALLS1&STORE  | (CALLS1  | 
| (CALLS2&STORE  | (CALLS2  | 
| (CALLSR&STORE  | (CALLSR  | 
| (LOAD&CDR&STORE  | (LOAD  | 
| (LOAD&CONS&STORE  | (LOAD  | 
| (LOAD&INC&STORE  | (LOAD  | 
| (LOAD&DEC&STORE  | (LOAD  | 
| (LOAD&CAR&STORE  | (LOAD  | 
| (CALL1&JMPIF  | (CALL1  | 
| (CALL1&JMPIFNOT  | (CALL1  | 
| (CALL2&JMPIF  | (CALL2  | 
| (CALL2&JMPIFNOT  | (CALL2  | 
| (CALLS1&JMPIF  | (CALLS1  | 
| (CALLS1&JMPIFNOT  | (CALLS1  | 
| (CALLS2&JMPIF  | (CALLS2  | 
| (CALLS2&JMPIFNOT  | (CALLS2  | 
| (CALLSR&JMPIF  | (CALLSR  | 
| (CALLSR&JMPIFNOT  | (CALLSR  | 
| (LOAD&JMPIF  | (LOAD  | 
| (LOAD&JMPIFNOT  | (LOAD  | 
| (LOAD&CAR&PUSH  | (LOAD  | 
| (LOAD&CDR&PUSH  | (LOAD  | 
| (LOAD&INC&PUSH  | (LOAD  | 
| (LOAD&DEC&PUSH  | (LOAD  | 
| (CONST&SYMBOL-FUNCTION  | (CONST  | 
| (CONST&SYMBOL-FUNCTION&PUSH  | (CONST  | 
| (CONST&SYMBOL-FUNCTION&STORE  | (CONST  | 
| (APPLY&SKIP&RET  | (APPLY  | 
| (FUNCALL&SKIP&RETGF  | (FUNCALL  | 
The functions described here are defined
 in src/compiler.lisp
 and src/record.d
 and can be used to examine the internals of a compiled closure.
These function are internal CLISP
  functions, their names are not exported, this section is
  not supposed to be comprehensive and is not guaranteed to be
  up to date.  It is intended for aspiring CLISP hackers who are
  supposed to graduate to reading the sources right away. All others
  should stick with the [ANSI CL standard] function DISASSEMBLE.
Closure name. The normal way to extract the name of a closure is
 FUNCTION-LAMBDA-EXPRESSION:
(defun my-plus-1 (x y) (declare (compile)) (+ x y)) ⇒MY-PLUS-1(function-lambda-expression #'my-plus-1) ⇒(LAMBDA (X Y) (DECLARE (COMPILE)) (+ X Y)); ⇒; ⇒TMY-PLUS-1;; works only on closure objects (sys::closure-name #'my-plus-1) ⇒MY-PLUS-1
Closure bytecode. The actual bytecode vector (if you modify it, you can get a segfault when the function is executed):
(sys::closure-codevec #'my-plus-1)
⇒ #(0 0 0 0 2 0 0 0 6 3 174 174 51 2 53 25 3)
Closure constants. A closure can depend on external and internal values:
(let ((x 123) (y 456)) (defun my-plus-2 (z) (declare (compile)) (+ x y z))) ⇒MY-PLUS-2(sys::closure-consts #'my-plus-2) ⇒(#(Y 456 X 123 NIL) 3 1)
 Use DISASSEMBLE to see how the constants are used.
Closure signature. Function SYS::SIGNATURE returns 8 values:
LIST)Mnemonic bytecodes. One can convert between numeric and mnemonic bytecodes (“LAP” stands for “Lisp Assembly Program”):
(multiple-value-bind (req-num opt-num rest-p key-p keyword-list
                      allow-other-keys-p byte-list const-list)
    (sys::signature #'my-plus-1)
  (sys::disassemble-LAP byte-list const-list))
⇒ ((0 LOAD&PUSH 2) (1 LOAD&PUSH 2) (2 CALLSR 2 53) (5 SKIP&RET 3))
(sys::assemble-LAP (mapcar #'rest *))
⇒ (174 174 51 2 53 25 3)
This section offers some insight into bytecode design in the form of questions and answers.
Question:
Does it make sense to define a new bytecode instruction for
   RESTART-CASE? Why? Why not?
RESTART-CASE is a glorified LET binding
   for SYSTEM::*ACTIVE-RESTARTS* and could well profit
   from a separate bytecode: it would make it non-consing[3].
   (Remember that RESTARTs have dynamic extent and therefore do not
   really need to be heap allocated.)
The reason HANDLER-BIND has its own bytecodes and
   RESTART-CASE does not is that HANDLER-BIND can occur in inner
   computation loops, whereas RESTART-CASE occurs only as part of
   user-interface programming and therefore not in inner loops where its
   consing could hurt much.
Question:
Consider this function and its disassembly:
 (defun foo (x y) (if (or (= x 0) (= y 0)) (+ x y) (foo y (1- x))))
 (DISASSEMBLE 'foo)
8     (LOAD&PUSH 1)
9     (LOAD&DEC&PUSH 3)
11    (JMPTAIL 2 5 L0)
    
    Why are the arguments pushed onto the STACK, just to be popped off of
    it during the JMPTAIL?
    Why not a sequence of LOAD,
    STORE and
    SKIP instructions
    followed by a JMP?
 
Using JMPTAIL requires 3
   instructions, JMP requires more.
   When JMPTAIL needs to be called, we
   usually have some stuff close to the top of the STACK which will
   become the new arguments, and some junk between these new arguments
   and the closure object.  JMPTAIL
   removes the junk.  JMPTAIL is a
   convenient shortcut which shortens the bytecode - because typically
   one would really have to clean-up the STACK by hand or make the
   calculations in src/compiler.lisp
   more complicated.
Table of Contents
Abstract
This is a list of frequently asked questions about CLISP on the CLISP mailing lists and the USENET newsgroup comp.lang.lisp. All the legitimate technical question are addressed in the CLISP documentation (CLISP impnotes, clisp(1)), and for such questions this list provides a link into the docs. The frequently asked political questions are answered here in full detail (meaning that no further explanations of the issues could be provided).
Please submit more questions (and answers!) to <clisp-list@lists.sourceforge.net> (http://lists.sourceforge.net/lists/listinfo/clisp-list).
| A.1. Meta Information | |||
| 
 | |||
| A.1.1. Miscellaneous | |||
| 
 | |||
| A.1.1.1. | What is “FAQ fine”? | ||
| We assess a nominal fine of $10 for asking a question that is answered with a link to this FAQ document. We further assess a fine of $1 for asking a question that is answered with a link to the CLISP manual. The fines are payable to the person who answered your questions. If you consider these amounts to be exorbitant, please feel free to ignore this blatant extortion and do not pay. This should not discourage you from asking questions, but rather encourage you to read the manual. | |||
| A.1.1.2. | The official CLISP documentation sucks - is anything better available? | ||
| As with all generic complaints, the answer to this one is PTC. Additionally, the nightly builds of the CLISP implementation notes documenting the current CVS head are available at http://clisp.podval.org/impnotes/. It contains both the documentation for the new features and the general improvements in the documentation. | |||
| A.1.1.3. | |||
| Because CLISP uses GNU readline. Note that this does not necessarily prevent you from distributing
 your proprietary products based on CLISP. See Note
 in  | |||
| A.1.1.4. | What about [ANSI CL standard] compliance? | ||
| CLISP purports to conform to the [ANSI CL standard] specification, so all deviations in 
 from the [ANSI CL standard] standard are bugs and are not (yet) fixed only due to lack of resources. On the other hand, some decisions made by the ANSI X3J13 committee were not as justified from the technical point of view as were most of them, and some of those questionable decisions were made after the alternative behavior has already been implemented in CLISP. The CLISP developers took pains to modify CLISP to unconditionally comply with the [ANSI CL standard] specification in all cases except for a handful of situations where they believed that the committee had made a mistake, in which cases the committee behavior is still optionally available. CLISP does not start in the ansi mode by default for historical reasons and this is not about to change. Dumping an image or passing a command line argument are easy enough. | |||
| A.1.1.5. | How do I ask for help? | ||
| Politely - please refer to  If you have a question about CLISP, you have the following options (listed in the order of decreasing audience size): 
 | |||
| A.1.1.6. | Which mailing lists should I subscribe to? | ||
| Cross-posting in the CLISP mailing lists is very actively discouraged and is virtually non-existent, thus you can subscribe to all mailing lists that are relevant to you without getting duplicate messages: 
 | |||
| A.1.1.7. | Why is my mail to a mailing list rejected? | ||
| CLISP mailing lists get a lot of spam, so the
  maintainers have to take care to protect the users.  If you get a note
  that “your message is held for moderator's approval”, you
  can safely assume that it went
   to  
 If you do not like this policy, please volunteer to maintain the mailing lists - you will be required to go through all the “held for moderator's approval” mail and approve/discard as appropriate at least twice a day. | |||
| A.1.1.8. | How do I report bugs? | ||
| A.1.1.9. | How do I help? | ||
| Please read Chapter 36, Extending CLISP and submit your patch,
  together with a  See  If your patch is more than just a few lines, it is much preferred that you make your patch available on the web and send the link to the list. The patch must be against the CVS head (reasonably recent). | |||
| A.1.1.10. | How do I debug CLISP? | ||
| When debugging the core: 
 When debugging module  
 When debugging a base module, use base instead of full and boot above. | |||
| A.1.2. Logo | |||
| 
 | |||
| A.1.2.1. | Why is CLISP using menorah as the logo? | ||
| Whimsical | If you must have some answer and you do not care whether it is correct or not, you may simply think that Common Lisp brings the Light to a programmer, and CLISP is a vehicle that carries the Light. Accordingly, CLISP enables you to see the truth, thus you can pronounce it as see-lisp. Alternatively, if you are a seasoned expert, you might pronounce it as sea-lisp. | ||
| Historical | CLISP has been using the menorah for the logo since the project was first started in the late 1980-ies by Bruno Haible and Michael Stoll. This probably reflects the authors' affection toward the Jewish people, Judaism or the State of Israel (neither of the two original authors is Jewish by birth). You may ask the original authors for details yourself. Both of them are very busy though, so do not expect a prompt reply. | ||
| A.1.2.2. | Shouldn't the logo be changed now due to the current political developments in the Middle East? | ||
| The CLISP developers, both the original creators and the current maintainers, do not subscribe to the mainstream view that blames the Jews for everything from high oil prices and Islamic extremism to El Niño and Sun spots. Moreover, today, when Jews are being pushed out of the American and European academic institutions with various obscene boycott and divestment campaigns, it is crucial for all of us to stand together against the resurgence of Nazism. For more information, please see: | |||
| A.1.2.3. | Aren't there other political issues of concern? | ||
| Yes, there are!  For example, in 1989 the
  communist
  government of the People's
   Republic of China murdered some 3000+
  student human rights protesters at the Tienanmen square in Beijing,
  and people appear to have already forgotten this crime.
  A note to that effect was kept in the file
   We also oppose software patents and support other liberal (i.e., pro-liberty) causes. | |||
| A.1.2.4. | Aren't you afraid of losing some users who are offended by the logo? | ||
| Do you have in mind people like this one? Good riddance! | |||
| A.1.2.5. | Using software to promote a political agenda is unprofessional! | ||
| Expressing their opinion is a perfectly natural thing for the authors, be it artistic preferences, political views or religious beliefs. The use of the menorah has its roots somewhere between these areas, and the authors are proud to display it. If you are unlucky enough to have lost the freedom to express your opinion, due to the constraints of a government, society, religion, or expectations of “professional relationships”, the Free World condoles with you. The authors of CLISP are not operating under such constraints. If you are unhappy about their artistic preferences, political views or religious beliefs, you are free to ignore them. Many scientists have been doing art, politics and religion. René Descartes and Isaak Newton combined mathematics and Christianity. Albert Einstein helped the U.S. to counter the danger of an atomic bomb in the hands of the Nazis. Bram Moolenaar, the author of VIM, promotes charitable donations to Uganda. | |||
| A.2. Running CLISP | |||
| 
 | |||
| A.2.1. | Where is
    | ||
| Pass  | |||
| A.2.2. | Where is the IDE? | ||
| Emacs-based. non-Emacs-based. | |||
| A.2.3. | What are the command line arguments? | ||
| See clisp(1). | |||
| A.2.4. | How do I get out of the debugger? | ||
| A.2.5. | What CLISP extensions are available? | ||
| 
 | |||
| A.2.6. | Where is the init (“RC”) file on my platform? | ||
| Read the file  | |||
| A.2.7. | Where are the modules with which I built CLISP? | ||
| In the full linking set. Run CLISP like this: 
 If your CLISP was configured with option  Making base the default linking set has some advantages: 
 See  | |||
| A.2.8. | How do I create a GUI for my CLISP program? | ||
| Use module  
    There are many other options, see "Common Lisp software running in CLISP". | |||
| A.3. Application Delivery | |||
| A.3.1. | How do I create an executable file with all my code in it? | ||
| Use  | |||
| A.3.2. | When I deliver my application with CLISP does it have to be covered by GNU GPL? | ||
| Not necessarily. CLISP is Free
  Software, covered by the GNU GPL, with special
 terms governing the distribution of applications that run in CLISP.
 The precise terms can be found in the
  In many cases, CLISP does not force an application to be covered by the GNU GPL. Nevertheless, we encourage you to release your software under an open source license. The benefits of such a license for your users are numerous, in particular they are free to modify the application when their needs/requirements change, and they are free to recompile the application when they upgrade their machine or operating system. CLISP extensions, i.e. programs which need to access non-portable CLISP internal symbols (in the packages “SYSTEM”, “CLOS”, “FFI”, etc), must be covered by GNU GPL as well. Other programs running in CLISP have to or need not to be placed under GNU GPL, depending on their distribution form: 
 | |||
| A.4. Troubles | |||
| 
 | |||
| A.4.1. | Where is the binary distribution for my platform? | ||
| The CLISP maintainers can only build CLISP binary distributions on those SourceForge CompileFarm platforms that are up an running at the time of the CLISP release and also have a reasonably modern C compiler. Note that CLISP is included in many software distributions, see the section “Get CLISP” on the CLISP's home page. | |||
| A.4.2. | But a previous release had a binary distribution for my platform, why does not the current one? | ||
| It was probably contributed by a user who did not (yet?) contribute a binary distribution for the current release. You can find out who contributed a specific binary distribution by looking at the release notes in the SourceForge Files section. | |||
| A.4.3. | Why does not CLISP build on my platform? | ||
| Please see file
   | |||
| A.4.4. | What do
   these messages mean: “ | ||
| This means that you are trying to read (“invalid
 byte”) or write (“character cannot be represented”)
 a non-ASCII character from (or to) a character stream which has
 ASCII  This may also be caused by filesystem access.
 If your  Note that this error may be signaled by the Print part of the
 read-eval-print loop and not by the function you call.
 E.g., if file  (with-open-file (s "foo" :direction :input :external-format charset:iso-8859-1) (read-line s)) If instead you type (with-open-file (s "foo" :direction :input :external-format charset:iso-8859-1) (setq l (read-line s)) nil)  CLISP will just print  | |||
| A.4.5. | What does
   this message mean: “ | ||
| CLISP uses GNU readline for command line editing and completion. You get this “Display all 1259 possibilities” message (and sometimes many screens of symbols) when you hit TAB too many times in an inappropriate place. You can turn this feature off if you are using Emacs. It is a good idea not to use TABs in your code. | |||
| A.4.6. | Why does not command line editing work? | ||
| See Section 21.2.1, “Command line editing with GNU readline”. | |||
| A.4.7. | How do I avoid stack overflow? | ||
| CLISP has two stacks, the “program stack” and the “lisp stack”, and both may occasionally overflow. Avoiding stack overflow: Generic 
 Avoiding stack overflow: Platform-specific 
 | |||
| A.4.8. | Why does my program return different values on each invocation? | ||
| The following code modifies itself: (let ((var '(a b c))) (nconc var '(1 2 3))) 
and will not work as one would naively expect.
(on the first invocation, it will return
(a b c 1 2 3),
the second invocation will produce a circular list, the third will hang
trying to  Instead you must do (let ((var (copy-list '(a b c)))) (nconc var (copy-list '(1 2 3)))) 
 See Lisp Programming Style for more useful information. | |||
| A.4.9. | Why is autoconf invoked during build? | ||
| When building from the CVS HEAD development sources, you
  will sometimes get errors when make
  tries to regenerate some  and re-run make. You can also pass  | |||
| A.4.10. | Why don't floating point arithmetics return what I want? 
(- 1.1 0.9)
⇒  | ||
| This not a bug, at least not a bug in CLISP. You may argue that this is a bug in IEEE 754, but first make sure that you do know What Every Computer Scientist Should Know About Floating-Point Arithmetic. See also  PS. If you want exact
 calculations, use  
(- 11/10 9/10)
⇒  | |||
| A.4.11. | Why does 
 always print the same number? | ||
| Reproducibility is important. See Section 12.3.1, “Random Numbers”. | |||
| A.4.12. | Why is an extra line break inserted by the pretty printer? | ||
| A.4.13. | How do I disable this annoying warning? | ||
| CLISP often issues  ( and examine the stack (see Section 25.1, “Debugging Utilities [CLHS-25.1.2]”) to see where the warning is coming from. If everything else fails, read the manual. | |||
| A.4.14. | Why does  (defun adder (val) (lambda (x) (+ x val))) ⇒ | ||
| Explanation | The above code does not conform to [ANSI CL standard], therefore CLISP can produce arbitrary results. See Section 3.2.2.3, “Semantic Constraints [CLHS-3.2.2.3]”. | ||
| Remedy | Always follow the naming convention for global special variables
  defined by  | ||
| More | 
 | ||
| A.4.15. | The error message is not helpful! | ||
| Sometimes an error message contains a compound object
  whose content you want to examine. Often this object will be available
  for  *** - READ: input stream #<INPUT STRING-INPUT-STREAM> ends within an object The following restarts are available: ABORT :R1 ABORT | |||
| A.4.16. | Why is the function  | ||
| When confronted with unexpected behavior, try looking in the CLISP impnotes. E.g., CLISP  Alternatively, since the implementation notes are organized in
 parallel to the [ANSI CL standard], and  | |||
Copyright (C) 2000, 2001, 2002 Free Software Foundation, Inc. 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA. Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed.
The purpose of this License is to make a manual, textbook, or other functional and useful document "free" in the sense of freedom: to assure everyone the effective freedom to copy and redistribute it, with or without modifying it, either commercially or noncommercially. Secondarily, this License preserves for the author and publisher a way to get credit for their work, while not being considered responsible for modifications made by others.
This License is a kind of "copyleft", which means that derivative works of the document must themselves be free in the same sense. It complements the GNU General Public License, which is a copyleft license designed for free software.
We have designed this License in order to use it for manuals for free software, because free software needs free documentation: a free program should come with manuals providing the same freedoms that the software does. But this License is not limited to software manuals; it can be used for any textual work, regardless of subject matter or whether it is published as a printed book. We recommend this License principally for works whose purpose is instruction or reference.
This License applies to any manual or other work, in any medium, that contains a notice placed by the copyright holder saying it can be distributed under the terms of this License. Such a notice grants a world-wide, royalty-free license, unlimited in duration, to use that work under the conditions stated herein. The "Document", below, refers to any such manual or work. Any member of the public is a licensee, and is addressed as "you". You accept the license if you copy, modify or distribute the work in a way requiring permission under copyright law.
A "Modified Version" of the Document means any work containing the Document or a portion of it, either copied verbatim, or with modifications and/or translated into another language.
A "Secondary Section" is a named appendix or a front-matter section of the Document that deals exclusively with the relationship of the publishers or authors of the Document to the Document's overall subject (or to related matters) and contains nothing that could fall directly within that overall subject. (Thus, if the Document is in part a textbook of mathematics, a Secondary Section may not explain any mathematics.) The relationship could be a matter of historical connection with the subject or with related matters, or of legal, commercial, philosophical, ethical or political position regarding them.
The "Invariant Sections" are certain Secondary Sections whose titles are designated, as being those of Invariant Sections, in the notice that says that the Document is released under this License. If a section does not fit the above definition of Secondary then it is not allowed to be designated as Invariant. The Document may contain zero Invariant Sections. If the Document does not identify any Invariant Sections then there are none.
The "Cover Texts" are certain short passages of text that are listed, as Front-Cover Texts or Back-Cover Texts, in the notice that says that the Document is released under this License. A Front-Cover Text may be at most 5 words, and a Back-Cover Text may be at most 25 words.
A "Transparent" copy of the Document means a machine-readable copy, represented in a format whose specification is available to the general public, that is suitable for revising the document straightforwardly with generic text editors or (for images composed of pixels) generic paint programs or (for drawings) some widely available drawing editor, and that is suitable for input to text formatters or for automatic translation to a variety of formats suitable for input to text formatters. A copy made in an otherwise Transparent file format whose markup, or absence of markup, has been arranged to thwart or discourage subsequent modification by readers is not Transparent. An image format is not Transparent if used for any substantial amount of text. A copy that is not "Transparent" is called "Opaque".
Examples of suitable formats for Transparent copies include plain ASCII without markup, Texinfo input format, LaTeX input format, SGML or XML using a publicly available DTD, and standard-conforming simple HTML, PostScript or PDF designed for human modification. Examples of transparent image formats include PNG, XCF and JPG. Opaque formats include proprietary formats that can be read and edited only by proprietary word processors, SGML or XML for which the DTD and/or processing tools are not generally available, and the machine-generated HTML, PostScript or PDF produced by some word processors for output purposes only.
The "Title Page" means, for a printed book, the title page itself, plus such following pages as are needed to hold, legibly, the material this License requires to appear in the title page. For works in formats which do not have any title page as such, "Title Page" means the text near the most prominent appearance of the work's title, preceding the beginning of the body of the text.
A section "Entitled XYZ" means a named subunit of the Document whose title either is precisely XYZ or contains XYZ in parentheses following text that translates XYZ in another language. (Here XYZ stands for a specific section name mentioned below, such as "Acknowledgements", "Dedications", "Endorsements", or "History".) To "Preserve the Title" of such a section when you modify the Document means that it remains a section "Entitled XYZ" according to this definition.
The Document may include Warranty Disclaimers next to the notice which states that this License applies to the Document. These Warranty Disclaimers are considered to be included by reference in this License, but only as regards disclaiming warranties: any other implication that these Warranty Disclaimers may have is void and has no effect on the meaning of this License.
You may copy and distribute the Document in any medium, either commercially or noncommercially, provided that this License, the copyright notices, and the license notice saying this License applies to the Document are reproduced in all copies, and that you add no other conditions whatsoever to those of this License. You may not use technical measures to obstruct or control the reading or further copying of the copies you make or distribute. However, you may accept compensation in exchange for copies. If you distribute a large enough number of copies you must also follow the conditions in section 3.
You may also lend copies, under the same conditions stated above, and you may publicly display copies.
If you publish printed copies (or copies in media that commonly have printed covers) of the Document, numbering more than 100, and the Document's license notice requires Cover Texts, you must enclose the copies in covers that carry, clearly and legibly, all these Cover Texts: Front-Cover Texts on the front cover, and Back-Cover Texts on the back cover. Both covers must also clearly and legibly identify you as the publisher of these copies. The front cover must present the full title with all words of the title equally prominent and visible. You may add other material on the covers in addition. Copying with changes limited to the covers, as long as they preserve the title of the Document and satisfy these conditions, can be treated as verbatim copying in other respects.
If the required texts for either cover are too voluminous to fit legibly, you should put the first ones listed (as many as fit reasonably) on the actual cover, and continue the rest onto adjacent pages.
If you publish or distribute Opaque copies of the Document numbering more than 100, you must either include a machine-readable Transparent copy along with each Opaque copy, or state in or with each Opaque copy a computer-network location from which the general network-using public has access to download using public-standard network protocols a complete Transparent copy of the Document, free of added material. If you use the latter option, you must take reasonably prudent steps, when you begin distribution of Opaque copies in quantity, to ensure that this Transparent copy will remain thus accessible at the stated location until at least one year after the last time you distribute an Opaque copy (directly or through your agents or retailers) of that edition to the public.
It is requested, but not required, that you contact the authors of the Document well before redistributing any large number of copies, to give them a chance to provide you with an updated version of the Document.
You may copy and distribute a Modified Version of the Document under the conditions of sections 2 and 3 above, provided that you release the Modified Version under precisely this License, with the Modified Version filling the role of the Document, thus licensing distribution and modification of the Modified Version to whoever possesses a copy of it. In addition, you must do these things in the Modified Version:
If the Modified Version includes new front-matter sections or appendices that qualify as Secondary Sections and contain no material copied from the Document, you may at your option designate some or all of these sections as invariant. To do this, add their titles to the list of Invariant Sections in the Modified Version's license notice. These titles must be distinct from any other section titles.
You may add a section Entitled "Endorsements", provided it contains nothing but endorsements of your Modified Version by various parties--for example, statements of peer review or that the text has been approved by an organization as the authoritative definition of a standard.
You may add a passage of up to five words as a Front-Cover Text, and a passage of up to 25 words as a Back-Cover Text, to the end of the list of Cover Texts in the Modified Version. Only one passage of Front-Cover Text and one of Back-Cover Text may be added by (or through arrangements made by) any one entity. If the Document already includes a cover text for the same cover, previously added by you or by arrangement made by the same entity you are acting on behalf of, you may not add another; but you may replace the old one, on explicit permission from the previous publisher that added the old one.
The author(s) and publisher(s) of the Document do not by this License give permission to use their names for publicity for or to assert or imply endorsement of any Modified Version.
You may combine the Document with other documents released under this License, under the terms defined in section 4 above for modified versions, provided that you include in the combination all of the Invariant Sections of all of the original documents, unmodified, and list them all as Invariant Sections of your combined work in its license notice, and that you preserve all their Warranty Disclaimers.
The combined work need only contain one copy of this License, and multiple identical Invariant Sections may be replaced with a single copy. If there are multiple Invariant Sections with the same name but different contents, make the title of each such section unique by adding at the end of it, in parentheses, the name of the original author or publisher of that section if known, or else a unique number. Make the same adjustment to the section titles in the list of Invariant Sections in the license notice of the combined work.
In the combination, you must combine any sections Entitled "History" in the various original documents, forming one section Entitled "History"; likewise combine any sections Entitled "Acknowledgements", and any sections Entitled "Dedications". You must delete all sections Entitled "Endorsements".
You may make a collection consisting of the Document and other documents released under this License, and replace the individual copies of this License in the various documents with a single copy that is included in the collection, provided that you follow the rules of this License for verbatim copying of each of the documents in all other respects.
You may extract a single document from such a collection, and distribute it individually under this License, provided you insert a copy of this License into the extracted document, and follow this License in all other respects regarding verbatim copying of that document.
A compilation of the Document or its derivatives with other separate and independent documents or works, in or on a volume of a storage or distribution medium, is called an "aggregate" if the copyright resulting from the compilation is not used to limit the legal rights of the compilation's users beyond what the individual works permit. When the Document is included in an aggregate, this License does not apply to the other works in the aggregate which are not themselves derivative works of the Document.
If the Cover Text requirement of section 3 is applicable to these copies of the Document, then if the Document is less than one half of the entire aggregate, the Document's Cover Texts may be placed on covers that bracket the Document within the aggregate, or the electronic equivalent of covers if the Document is in electronic form. Otherwise they must appear on printed covers that bracket the whole aggregate.
Translation is considered a kind of modification, so you may distribute translations of the Document under the terms of section 4. Replacing Invariant Sections with translations requires special permission from their copyright holders, but you may include translations of some or all Invariant Sections in addition to the original versions of these Invariant Sections. You may include a translation of this License, and all the license notices in the Document, and any Warranty Disclaimers, provided that you also include the original English version of this License and the original versions of those notices and disclaimers. In case of a disagreement between the translation and the original version of this License or a notice or disclaimer, the original version will prevail.
If a section in the Document is Entitled "Acknowledgements", "Dedications", or "History", the requirement (section 4) to Preserve its Title (section 1) will typically require changing the actual title.
You may not copy, modify, sublicense, or distribute the Document except as expressly provided for under this License. Any other attempt to copy, modify, sublicense or distribute the Document is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance.
The Free Software Foundation may publish new, revised versions of the GNU Free Documentation License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. See http://www.gnu.org/copyleft/.
Each version of the License is given a distinguishing version number. If the Document specifies that a particular numbered version of this License "or any later version" applies to it, you have the option of following the terms and conditions either of that specified version or of any later version that has been published (not as a draft) by the Free Software Foundation. If the Document does not specify a version number of this License, you may choose any version ever published (not as a draft) by the Free Software Foundation.
To use this License in a document you have written, include a copy of the License in the document and put the following copyright and license notices just after the title page:
Copyright (C) YEAR YOUR NAME.
Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, no Front-Cover Texts, and no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".
If you have Invariant Sections, Front-Cover Texts and Back-Cover Texts, replace the "with...Texts." line with this:
with the Invariant Sections being LIST THEIR TITLES, with the Front-Cover Texts being LIST, and with the Back-Cover Texts being LIST.
If you have Invariant Sections without Cover Texts, or some other combination of the three, merge those two alternatives to suit the situation.
If your document contains nontrivial examples of program code, we recommend releasing these examples in parallel under your choice of free software license, such as the GNU General Public License, to permit their use in free software.
Version 2, June 1991
Copyright © 1989, 1991 Free Software Foundation, Inc.
Version 2, June 1991
Table of Contents
The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software - to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too.
When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things.
To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it.
For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights.
We protect your rights with two steps:
copyright the software, and
offer you this license which gives you legal permission to copy, distribute and/or modify the software.
Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations.
Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all.
The precise terms and conditions for copying, distribution and modification follow.
This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a “work based on the Program ” means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term “modification ”.) Each licensee is addressed as “you”.
Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does.
You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program.
You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee.
You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions:
You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change.
You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License.
If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License.
If the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.)
These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it.
Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program.
In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License.
You may copy and distribute the Program (or a work based on it, under Section 2 in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following:
Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or,
Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or,
Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.)
The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable.
If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code.
You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance.
You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it.
Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License.
If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program.
If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances.
It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice.
This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License.
If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License.
The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns.
Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation.
If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally.
BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION.
IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES.
END OF TERMS AND CONDITIONS
If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms.
To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found.
<one line to give the program's name and a brief idea of what it does.> Copyright (C) <year> <name of author>
This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version.
This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details.
You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
Also add information on how to contact you by electronic and paper mail.
If the program is interactive, make it output a short notice like this when it starts in an interactive mode:
Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details.
The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program.
You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names:
Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker.
<signature of Ty Coon>, 1 April 1989 Ty Coon, President of Vice
This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Lesser General Public License instead of this License.
[CLtL1] Common Lisp: the Language (1st Edition). 1984. 465 pages. ISBN 0-932376-41-X. Digital Press.
[CLtL2] Common Lisp: the Language (2nd Edition). 1990. 1032 pages. ISBN 1-555-58041-6. Digital Press.
[AMOP] The Art of the Metaobject Protocol. 1991. 335 pages. ISBN 0-262-61074-4. MIT Press.
[ANSI CL] ANSI CL standard1994. ANSI Common Lisp standard X3.226-1994 - Information Technology - Programming Language - Common Lisp.
[CLHS] Common Lisp HyperSpecCommon Lisp HyperSpec.
| These notes document CLISP version 2.44 | Last modified: 2008-02-02 |