Copyright © 1992-2010 Bruno Haible
Copyright © 1998-2010 Sam Steingold
Legal Status of the CLISP Implementation Notes
These notes are dually licensed under GNU FDL 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 FDL. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License (FDL), 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 the software and the documentaion).
See Q: A.1.1.5 for information on CLISP support.
Table of Contents
STREAM-EXTERNAL-FORMAT
STREAM-ELEMENT-TYPE
EXT:MAKE-STREAM
FILE-POSITION
EXT:ELASTIC-NEWLINE
OPEN
CLEAR-INPUT
CLOSE
OPEN-STREAM-P
BROADCAST-STREAM
EXT:MAKE-BUFFERED-INPUT-STREAM
and EXT:MAKE-BUFFERED-OUTPUT-STREAM
WRITE
& WRITE-TO-STRING
PRINT-UNREADABLE-OBJECT
List of Figures
List of Tables
EVAL
/APPLY
TYPECODES
HEAPCODES
List of Examples
TRACE
EXT:FILL-STREAM
usagegethostname
from CLISPREGEXP:MATCH
REGEXP:REGEXP-QUOTE
These 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 [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”
STREAM
s.
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 | ( |
Bytecode instruction | (STOREV |
First mention of an entity | firstterm |
External module | libsvm , bindings/glibc |
Command line argument | -x |
Interaction | Computer output |
Table of Contents
STREAM-EXTERNAL-FORMAT
STREAM-ELEMENT-TYPE
EXT:MAKE-STREAM
FILE-POSITION
EXT:ELASTIC-NEWLINE
OPEN
CLEAR-INPUT
CLOSE
OPEN-STREAM-P
BROADCAST-STREAM
EXT:MAKE-BUFFERED-INPUT-STREAM
and EXT:MAKE-BUFFERED-OUTPUT-STREAM
WRITE
& WRITE-TO-STRING
PRINT-UNREADABLE-OBJECT
Table 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
.
A newline character can be entered by the user by pressing the Enter key.
See also Section 21.13, “Function CLEAR-INPUT
”.
Safety settings are ignored by the interpreted code;
therefore where the standard uses the phrase “should signal an
error”, an ERROR
is SIGNAL
ed.
See Section 3.3.4, “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
#,
#Y
FUNCTION
objects and input STREAM
's EXT:ENCODING
s
#""
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-OBJECT
s lacking a keyword
constructor#<ARRAY type
dimensions
>
ARRAY
s except STRING
s, if
*PRINT-ARRAY*
is NIL
#<SYSTEM-FUNCTION name
>
#<ADD-ON-SYSTEM-FUNCTION
name
>
#<SPECIAL-OPERATOR
name
>
#<COMPILED-FUNCTION
name
>
CUSTOM:*PRINT-CLOSURE*
is NIL
#<FUNCTION name
...>
CUSTOM:*PRINT-CLOSURE*
is NIL
#<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
).
Table 3.1. Function call limits
CALL-ARGUMENTS-LIMIT | 212=4096 |
MULTIPLE-VALUES-LIMIT | 27=128 |
LAMBDA-PARAMETERS-LIMIT | 212=4096 |
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.
DEFINE-SYMBOL-MACRO
The macro DEFINE-SYMBOL-MACRO
establishes SYMBOL-MACRO
s with
global scope (as opposed to SYMBOL-MACRO
s 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.
“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 SIGNAL
s 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
...)
EVAL-WHEN
EVAL-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.
THE
The 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.
Constant LAMBDA-LIST-KEYWORDS
. (
&OPTIONAL
&REST
&KEY
&ALLOW-OTHER-KEYS
&AUX
&BODY
&WHOLE
&ENVIRONMENT
)
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
.
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 ”.
Function EXT:ARGLIST
. Function (
returns the lambda list of
the function or macro that EXT:ARGLIST
name
)name
names and SIGNAL
s an ERROR
if name
is
not FBOUNDP
. It also SIGNAL
s an ERROR
when the macro lambda list is not
available due to the compiler optimization settings
(see Section 3.3.6, “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.
Compiler macros are expanded in the compiled code only, and ignored by the interpreter.
When a DEFUN
form is EVAL
uated, 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;value
is lexical (defun adder-i (value) (lambda (x) (+ x value))) ⇒ADDER-I
; interpreted function;value
is lexical (defparameter add-c-10 (adder-c 10)) ⇒ADD-C-10
; compiled function (defparameter 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-I
andADD-I-10
but notADDER-C
andADD-C-10
(funcall add-c-10 32) ⇒42
; as before (funcall add-i-10 32) ⇒44
;value
is 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 FUNCALL
s)
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 DEFUN
s 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 re-evaluate according the current environment, if it has changed. CLISP implements ad-hoc look-up for variables (but not for macros, see Section 3.2.2.2, “Minimal Compilation ”).
Hash tables are externalizable objects.
Both COMPILE
and EVAL
may SIGNAL
the EXT:SOURCE-PROGRAM-ERROR
CONDITION
which derives from PROGRAM-ERROR
and which contains
additional slots with accessors
EXT:SOURCE-PROGRAM-ERROR-FORM
ERROR
was
SIGNAL
edEXT:SOURCE-PROGRAM-ERROR-DETAIL
ERROR
The declarations (
,
TYPE
type
variable
...)(
,
are ignored by both the interpreter and the compiler.FTYPE
type
function
...)
SPECIAL
Declaration 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.
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. See also
Section 3.2.2.3, “Semantic Constraints ”.
Function EXT:SPECIAL-VARIABLE-P
. You can use the function (
to check whether the EXT:SPECIAL-VARIABLE-P
symbol
&OPTIONAL
environment
)symbol
is a
dynamic variable. 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.
EXT:CONSTANT-NOTINLINE
Constants defined by DEFCONSTANT
but proclaimed EXT:CONSTANT-NOTINLINE
will not be inlined by the compiler. This is useful for variables
which remain constant within an a single Lisp process but may vary
between processes and machines (such as endianness or word size) thus
they should be written to #P".fas"
s as symbols, not values.
CONSTANTP
Function 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
(
.
Use IF
(CONSTANTP
form
) (EVAL
form
))EVAL-WHEN
if you need recognition and the value during
compile-time. See also Section 31.11.5, “Macro EXT:COMPILE-TIME-VALUE
”.
SAFETY
Declaration (
results in “safe” compiled code: function calls are never
eliminated. This guarantees the semantics described in
[sec_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 the compiled version of form
.
(LET
((x 0)) (FLET
((inc () (DECLARE
(compile)) (INCF
x)) (dec () (DECF
x))) (VALUES
#'inc #'dec)))
returns two functions. The first is compiled and increments x
, the
second is interpreted (slower) and decrements the same x
.
This declaration can also be used to name the resulting compiled closure:
(LAMBDA
(x) (DECLARE
(compile ident)) x) ⇒(
#<
COMPILED-FUNCTION
IDENT>FUNCTION-LAMBDA-EXPRESSION
*
) ⇒; source is not preserved ⇒
NIL
⇒
T
IDENT
(FBOUNDP
'ident) ⇒; sic!
NIL
SPACE
The 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.
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
type
&OPTIONAL
once-p
)type
is a user-defined type specifier 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 type
was a user-defined type specifier.
The possible results of TYPE-OF
CONS
SYMBOL
, NULL
, BOOLEAN
,
KEYWORD
BIT
, (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
, COMPLEX
CHARACTER
, 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-FUNCTION
STREAM
, FILE-STREAM
, SYNONYM-STREAM
,
BROADCAST-STREAM
, CONCATENATED-STREAM
, TWO-WAY-STREAM
,
ECHO-STREAM
, STRING-STREAM
PACKAGE
, 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-FUNCTION
EXT: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-INTERNAL
ADDRESS
(should not
occur)SYMBOL
(structure types or CLOS
classes)Function COERCE
. FIXNUM
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 COERCE
s FIXNUM
s to
CHARACTER
s via CODE-CHAR
.
When CUSTOM:*COERCE-FIXNUM-CHAR-ANSI*
is non-NIL
, FIXNUM
s cannot be
COERCE
d to CHARACTER
s.
The CLOS symbols are EXPORT
ed from the package “CLOS”.
“COMMON-LISP” uses (as in USE-PACKAGE
) “CLOS” and EXT:RE-EXPORT
s the
[ANSI CL standard] standard exported symbols (the CLISP extensions, e.g.,
those described in Chapter 29, Meta-Object Protocol, are not EXT:RE-EXPORT
ed).
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”) (SHADOW
symbol
"CL-NO-CLOS")) (DO-SYMBOLS
(symbol
"CL-NO-CLOS") (EXPORT
symbol
"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
[sec_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 CONS
es
and NUMBER
s, due to the performance concerns.
Among those classes listed in Figure
4-8, only the following are instances of BUILT-IN-CLASS
:
T
CHARACTER
NUMBER
, COMPLEX
, REAL
, FLOAT
,
RATIONAL
, RATIO
, INTEGER
SEQUENCE
ARRAY
, VECTOR
, BIT-VECTOR
,
STRING
LIST
, CONS
SYMBOL
, NULL
FUNCTION
HASH-TABLE
PACKAGE
PATHNAME
, LOGICAL-PATHNAME
RANDOM-STATE
READTABLE
STREAM
, 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.
Table of Contents
&KEY
markers in DEFSETF
lambda lists are supported, but the
corresponding keywords must appear literally in the program text.
An attempt to modify read-only data SIGNAL
s 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.
(
,
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.
Additional 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-FLOAT
s to digits
bits.
VALUES-LIST
(
is equivalent to SETF
(VALUES-LIST
list
) form
)(
.VALUES-LIST
(SETF
list
(MULTIPLE-VALUE-LIST
form
)))
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.
DESTRUCTURING-BIND
This macro does not perform full error checking.
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 [sec_3-1-2-1-2-2]) and, as such, are rather efficient.
DEFCONSTANT
The 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.
constant variables may not be bound dynamically or lexically.
See also Section 3.3.2, “Declaration EXT:CONSTANT-NOTINLINE
”.
If you need to undo the effects of a DEFCONSTANT
form,
PROCLAIM
the symbol SPECIAL
(to turn the constant variable into a dynamic variable),
and then PROCLAIM
it EXT:NOTSPECIAL
(to turn the dynamic variable into a lexical variable).
If you follow the usual variable naming convention
(*FOO*
for DEFVAR
and DEFPARAMETER
,
+BAR+
for DEFCONSTANT
, ZOT
for LET
/LET*
), you will save yourself a lot of trouble.
See also Q: A.4.14.
CUSTOM:*SUPPRESS-SIMILAR-CONSTANT-REDEFINITION-WARNING*
If the variable being defined by DEFCONSTANT
is already bound to
a value which is not EQL
to the new value, a WARNING
is issued.
If, however, the new value is visually similar
(prints to the same string, as is commonly the case when re-loading files)
to the old one, the warning can be suppressed by setting
CUSTOM:*SUPPRESS-SIMILAR-CONSTANT-REDEFINITION-WARNING*
to a non-NIL
value.
The initial value of CUSTOM:*SUPPRESS-SIMILAR-CONSTANT-REDEFINITION-WARNING*
is NIL
.
EXT:FCASE
This 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.4, “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
.
EQ
EQ
compares CHARACTER
s and FIXNUM
s as EQL
does.
No unnecessary copies are made of CHARACTER
s and NUMBER
s.
Nevertheless, one should use EQL
as it is more portable across Common Lisp
implementations.
(
always
returns LET
((x
y
)) (EQ
x
x
))T
for any Lisp object y
.
See also Equality of foreign values.
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
)
Table of Contents
Mixing termination test clauses with different default return values is not allowed because it is not specifed whether
(loop repeat 1 thereis nil never nil)
should return T
(the default return value
from NEVER
) of NIL
(the default return value from
THEREIS
).
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 SIGNAL
ed.
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 SIGNAL
ed, 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-SLOTS
LIST
of effective slot definition metaobjects.
EXT:STRUCTURE-DIRECT-SLOTS
LIST
of direct slot definition metaobjects.
EXT:STRUCTURE-KEYWORD-CONSTRUCTOR
SYMBOL
) of the keyword
constructor function for the structure, or NIL
if the structure has
no keyword constructor.EXT:STRUCTURE-BOA-CONSTRUCTORS
LIST
of names (SYMBOL
s)
of BOA constructors for the structure.EXT:STRUCTURE-COPIER
SYMBOL
) of the copier for the
structure.EXT:STRUCTURE-PREDICATE
SYMBOL
) 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 debugger commands.
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.8, “Class EXT:FILL-STREAM
”).
Contrary to the recommendation of the standard, CLISP usually
does print the name of the containing function to simplify debugging
in batch mode, see EXT:EXIT-ON-ERROR
.
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
}*)
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
}*)
Function COMPUTE-RESTARTS
. COMPUTE-RESTARTS
and FIND-RESTART
behave as specified in
[ANSI CL standard]: If the optional condition
argument is non-NIL
,
only RESTART
s associated with that CONDITION
and RESTART
s 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.
Macro EXT:MUFFLE-CERRORS
. The macro (
executes the EXT:MUFFLE-CERRORS
{form
}*)form
s; when a continuable ERROR
occurs whose CONTINUE
RESTART
can be invoked non-interactively (this includes all continuable ERROR
s 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
}*)form
s; when a continuable ERROR
occurs whose CONTINUE
RESTART
can be invoked non-interactively (this includes all continuable ERROR
s SIGNAL
ed
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
}*)form
s; 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
}*)form
s; 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 FUNCALL
able (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
'ABORT
condition)))
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 by EXT:WITHOUT-GLOBAL-HANDLERS
&BODY
body
)(
, executes EXT:SET-GLOBAL-HANDLER
NIL
NIL
)body
(where unhandled conditions now
invoke the debugger), and then restores the handlers.
The prompt for replacement values (RESTART
s STORE-VALUE
,
USE-VALUE
et al) is terminated with CUSTOM:*PROMPT-FINISH*
to indicate that
the value entered is treated as usual for the Lisp read-eval-print loop, i.e., it is
EVAL
uated.
No notes.
Table of Contents
The [ANSI CL standard] packages present in CLISP
MAKE-PACKAGE
The default value of the :USE
argument is
(“COMMON-LISP”)
.
MAKE-PACKAGE
accepts additional keyword arguments
:CASE-SENSITIVE
and :CASE-INVERTED
(but not :MODERN
!)
DEFPACKAGE
DEFPACKAGE
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):MODERN
if “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" (:MODERN
T
) (:USE
"COMMON-LISP" "EXT"))
is equivalent to
(DEFPACKAGE
"FOO" (:CASE-SENSITIVE
T
) (:CASE-INVERTED
T
) (:USE
"CS-COMMON-LISP" "EXT"))
:NICKNAMES
RENAME-PACKAGE
:DOCUMENTATION
(SETF
DOCUMENTATION
)
:SHADOW
SHADOW
:SHADOWING-IMPORT-FROM
SHADOWING-IMPORT
:USE
USE-PACKAGE
and UNUSE-PACKAGE
:IMPORT-FROM
IMPORT
:INTERN
INTERN
(but not UNINTERN
)
:EXPORT
INTERN
and EXPORT
(but not
UNEXPORT
):SIZE
EXT:RE-EXPORT
The function (
re-EXT:RE-EXPORT
FROM-PACK
TO-PACK
)EXPORT
s all external
SYMBOL
s from FROM-PACK
also from
TO-PACK
, provided it already uses
FROM-PACK
; and SIGNAL
s an ERROR
otherwise.
EXT:PACKAGE-CASE-INVERTED-P
Returns T
if the argument is a
case-inverted package.
This function is SETF
able, although it is probably not a good idea
to change the case-inverted status of an existing package.
EXT:PACKAGE-CASE-SENSITIVE-P
Returns T
if the argument is a :CASE-SENSITIVE
PACKAGE
.
This function is SETF
able, although it is probably not a good idea
to change the case-sensitive status of an existing package.
Locking discussed in this section has nothing to do with
MT:MUTEX-LOCK
.
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 SIGNAL
ed 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
EXPORT
s all CLOS-specific symbols, including some
additional symbols.
EXPORT
ed symbols. It defines many system internals.
EXT:RE-EXPORT
s
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”):
“POSIX”, “SOCKET”, “GSTREAM”, “GRAY”,
“I18N”, “CUSTOM”.EXPORT
s some character sets, for use with
EXT:MAKE-ENCODING
and as :EXTERNAL-FORMAT
argument.
:CASE-SENSITIVE
versions of “COMMON-LISP” and “COMMON-LISP-USER”.
See Section 11.5, “Package Case-Sensitivity”.All pre-existing packages except “COMMON-LISP-USER” belong to the implementation, in the sense that the programs that do not follow [sec_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") (DEFUN
FOO () ...)
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.1.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.1.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-name
cs-cl:intern
cs-cl:find-symbol
cs-cl:symbol-name
.cs-cl:shadow
cs-cl:find-all-symbols
cs-cl:string=
cs-cl:string/=
cs-cl:string<
cs-cl:string>
cs-cl:string<=
cs-cl:string>=
cs-cl:string-trim
cs-cl:string-left-trim
cs-cl:string-right-trim
SYMBOL
to a STRING
and therefore
exist in a variant that uses cs-cl:symbol-name
instead of SYMBOL-NAME
.cs-cl:make-package
PACKAGE
.
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) ⇒(
T
EQ
':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-CASE*
to :DOWNCASE
.
For packages to be located in the “modern”
(case-sensitive) world, you need to augment their DEFPACKAGE
declaration by adding the option (
,
see Section 11.1.2, “Macro :MODERN
T
)DEFPACKAGE
”.
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
.
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 SIGNAL
s 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
= (GCD
x1
...xn
) = (+ (*k1
x1
) ... (*kn
xn
))
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
)
DECODE-FLOAT
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-DIGITS
number
digits
))digits
)
Byte specifiers are objects of built-in type BYTE,
not INTEGER
s.
Function EXPT
. (
is not very precise if EXPT
base
exponent
)exponent
has a large
absolute value.
Function LOG
. (
LOG
number
base
)SIGNAL
s 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
SIGNAL
s 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*
.
See also *READ-DEFAULT-FLOAT-FORMAT*
.
Macro EXT:WITHOUT-FLOATING-POINT-UNDERFLOW
. The macro (
executes the
EXT:WITHOUT-FLOATING-POINT-UNDERFLOW
{form
}*)form
s, with errors of type FLOATING-POINT-UNDERFLOW
inhibited.
Floating point operations will silently return zero instead of
SIGNAL
ing an ERROR
of type FLOATING-POINT-UNDERFLOW
.
Condition FLOATING-POINT-INVALID-OPERATION
. This CONDITION
is never SIGNAL
ed by CLISP.
Condition FLOATING-POINT-INEXACT
. This CONDITION
is never SIGNAL
ed by CLISP.
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 |
BIGNUM
s 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
)SETF
ed.
They are not constant variables.
Since the exponent of a
LONG-FLOAT
is a signed 32-bits
integer, MOST-POSITIVE-LONG-FLOAT
is about
2231
,
which is much larger that the largest
representable BIGNUM
, which is less than
2221
.
This, obviously, means that ROUND
, TRUNCATE
, FLOOR
and CEILING
SIGNAL
s an ERROR
on large LONG-FLOAT
s.
Less obviously, this means that (
also fails.FORMAT
NIL
"~E
"
MOST-POSITIVE-LONG-FLOAT
)
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-FLOAT
s 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-FLOAT
s 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-FLOAT
s 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-FLOAT
s 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
(i.e., 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) decided 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
[sec_12-1-4-4]!)
{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-FLOAT
s,
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-FLOAT
s when only
SHORT-FLOAT
s 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
[sec_12-1-4-1]!)
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)
,
which has a real part of exactly #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))
,
with #C
(-9.0 0.0)x
=
-
evaluates to #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
'(RANDOM
1s0)'
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-STATE
T
))))'$
clisp -norc-M
foo.mem-x
'(RANDOM
1s0)'
or by placing (
into your RC file.SETQ
*RANDOM-STATE*
(MAKE-RANDOM-STATE
T
))
Table of Contents
CHAR-CODE
CHAR-CODE
takes values from 0
(inclusive) to
CHAR-CODE-LIMIT
(exclusive), i.e., the implementation
supports exactly CHAR-CODE-LIMIT
characters.
Table 13.1. Number of characters
binaries built | without UNICODE support | with UNICODE support |
---|---|---|
CHAR-CODE-LIMIT | 28 = 256 | 17 * 216 = 1114112 |
BASE-CHAR
The 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
. The value is
See also function EXT:STRING-WIDTH
.
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).
Table 13.3. Semi-standard characters
character | code |
---|---|
#\Backspace | #x08 |
#\Tab | #x09 |
#\Linefeed | #x0A |
#\Page | #x0C |
#\Return | #x0D |
#\Newline is the line terminator.
Table 13.5. 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 ”.
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 lc
uc
and of lc
is uc
uc
and of lc
is lc
The 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:ENCODING
s,
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 the [ANSI CL standard] in
[sec_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
).
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:MAPCAP
function
x1
...xn
) ≡ (APPLY
#'APPEND
(MAPCAR
function
x1
...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:MAPLAP
function
x1
...xn
) ≡ (APPLY
#'APPEND
(MAPLIST
function
x1
...xn
))
(Actually a bit more efficient that this would have been.)
Table of Contents
Function MAKE-ARRAY
. MAKE-ARRAY
can return specialized arrays for the ARRAY-ELEMENT-TYPE
s
(
,
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
.
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 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 |
Table of Contents
String comparison (STRING<
and friends) is based on the
function CHAR<=
(see Section 13.9, “Ordering of Characters ”).
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-WIDTH
s 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-SORT
SORT
and STABLE-SORT
accept two additional keyword arguments
:START
and :END
:
(SORT
sequence
predicate
&KEY
:KEY
:START
:END
) (STABLE-SORT
sequence
predicate
&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
If you “visibly modify” a key, consequences are unpredictable:
(LET
((hash-table
(MAKE-HASH-TABLE
:test 'EQUALP
))) (SETF
(GETHASH
hash-table
hash-table
)T
) (GETHASH
hash-table
hash-table
)) ⇒; ⇒
NIL
NIL
because (
modifies SETF
GETHASH
)hash-table
, the very next
GETHASH
does not find it in itself.
MAKE-HASH-TABLE
MAKE-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-EQ
EXT:STABLEHASH-EQ
SYMBOL
,
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 SIGNAL
ed 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-TABLE
s
and EXT:WEAK-POINTER
s, it is garbage-collected and removed from the weak
HASH-TABLE
.
The SETF
able 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-TABLE
s cannot be printed readably.
See also Section 31.7.9, “Weak Hash Tables”.
HASH-TABLE
s and garbage-collectionWhen a hash table contains keys to be compared by identity - such
as NUMBER
s in HASH-TABLE
s with the HASH-TABLE-TEST
EQ
;
or CONS
es in tables which test with EQ
or EQL
;
or VECTOR
s 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-TABLE
s 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-TEST
You 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
)name
can be passed as the :TEST
argument to MAKE-HASH-TABLE
.
E.g.:
(EXT:DEFINE-HASH-TABLE-TEST
stringSTRING=
SXHASH
) ⇒STRING
(MAKE-HASH-TABLE
:test 'string) ⇒#S(HASH-TABLE :TEST (#<SYSTEM-FUNCTION STRING=> . #<SYSTEM-FUNCTION SXHASH>))
(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:
(FUNCALL
test-function
x
y
) ⇒ (=
(FUNCALL
hash-function
x
) (FUNCALL
hash-function
y
))
This means that the following definition:
(EXT:DEFINE-HASH-TABLE-TEST
number=
SXHASH
) ; broken!
is not correct because
(=
1 1d0) ⇒; same object! (
T
=
(SXHASH
1) (SXHASH
1d0)) ⇒; different buckets!
NIL
The correct way is, e.g.:
(EXT:DEFINE-HASH-TABLE-TEST
number=
(LAMBDA
(x) (SXHASH
(COERCE
x 'SHORT-FLOAT
))))
Note that COERCE
ing to a SHORT-FLOAT
does not cons up
fresh objects while COERCE
ing to a DOUBLE-FLOAT
does.
HASH-TABLE-TEST
Function HASH-TABLE-TEST
returns either one of
EXT:FASTHASH-EQ | EXT:FASTHASH-EQUAL |
EXT:STABLEHASH-EQ | EXT:STABLEHASH-EQUAL |
EXT:FASTHASH-EQL | EQUALP |
EXT:STABLEHASH-EQL |
(but not EQ
, EQL
nor EQUAL
anymore), or, for HASH-TABLE
s
created with a user-defined HASH-TABLE-TEST
(see macro EXT:DEFINE-HASH-TABLE-TEST
),
a CONS
cell (test-function
. hash-function
).
EXT:DOHASH
For iteration through a HASH-TABLE
, a macro EXT:DOHASH
,
similar to DOLIST
, can be used instead of MAPHASH
:
(EXT:DOHASH
(key-var
value-var
hash-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 xxx and type
yy |
".yy" | for a pathname with type yy and no
name or with name .yy and no type,
depending on the value of CUSTOM:*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
host
NIL
device
NIL
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 ) |
name
type
NIL
or SIMPLE-STRING
, may contain wildcard characters "?"
and
"*"
(may also be specified as :WILD
)
version
NIL
or :WILD
or :NEWEST
(after merging the defaults)A UNIX filename is split into name and type.
Pathname components
host
NIL
or SIMPLE-STRING
, wildcard characters may
occur but do not act as wildcardsdevice
NIL
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 ) |
name
type
NIL
or SIMPLE-STRING
, may contain wildcard characters "?"
and
"*"
(may also be specified as :WILD
)
version
NIL
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-PATHNAME
s, as required by
[sec_19-3-2-1].
External notation of pathnames (cf. PARSE-NAMESTRING
and
NAMESTRING
), of course without spaces, [,],{,}:
[ "/" ] | "/" denotes absolute pathnames |
{ name "/" } | each name is a subdirectory |
[ name ["." type ] ] | filename with type (extension) |
Name and type may be STRING
s of any LENGTH
(consisting of printing CHARACTER
s, except "/"
).
[ [drivespec ] : ] | a letter "*" |a |...|z |A |...|Z |
{ name [. type ] \ } | each name is a subdirectory, "\" may be
replaced by "/" |
[ name [. type ] ] | filename with type (extension) |
Name and type may be STRING
s of any LENGTH
(consisting of printing CHARACTER
s, 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-PATHNAME
TRANSLATE-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-PATHNAME
TRANSLATE-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 SYMBOL
s 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-TRANSLATIONS
When 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 repeatedly 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 host
or host
.host
, in that directory, is READ
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.
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 SIGNAL
s an ERROR
when passed a
directory.
CLISP provides separate directory functions, such as
EXT:DELETE-DIRECTORY
, EXT:RENAME-DIRECTORY
et al.
You can use DIRECTORY
or EXT:PROBE-PATHNAME
to figure out whether a
given namestring refers to a file or a directory.
EXT:PROBE-PATHNAME
Function EXT:PROBE-PATHNAME
figures out whether the argument refers to
an existing directory or an existing regular file, and returns 4 values
if the filesystem object exists:
or NIL
if it does not exist.
E.g., if you have a file file
, a directory directory
,
a symbolic link link-file
pointing to file
and a symbolic link link-dir
pointing to directory
,
then
(EXT:PROBE-PATHNAME
#P"filename") ⇒#P"/.../filename"
⇒#P"/.../filename"
⇒3427467015
⇒3171976
(EXT:PROBE-PATHNAME
#P"filename/") ⇒#P"/.../filename"
⇒#P"/.../filename"
⇒3427467015
⇒3171976
(EXT:PROBE-PATHNAME
#P"directory") ⇒#P"/.../directory/"
⇒#P"/.../directory/"
⇒3426940352
⇒1024
(EXT:PROBE-PATHNAME
#P"directory/") ⇒#P"/.../directory/"
⇒#P"/.../directory/"
⇒3426940352
⇒1024
(EXT:PROBE-PATHNAME
#P"link-file") ⇒#P"/.../filename"
⇒#P"/.../link-file"
⇒3427467015
⇒3171976
(EXT:PROBE-PATHNAME
#P"link-file/") ⇒#P"/.../filename"
⇒#P"/.../link-file"
⇒3427467015
⇒3171976
(EXT:PROBE-PATHNAME
#P"link-dir") ⇒#P"/.../directory/"
⇒#P"/.../link-dir/"
⇒3426940352
⇒1024
(EXT:PROBE-PATHNAME
#P"link-dir/") ⇒#P"/.../directory/"
⇒#P"/.../link-dir/"
⇒3426940352
⇒1024
PROBE-FILE
PROBE-FILE
cannot be used to check whether a directory exists.
Use functions EXT:PROBE-DIRECTORY
, EXT:PROBE-PATHNAME
or DIRECTORY
for this.
FILE-AUTHOR
FILE-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.).
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 SIGNAL
ed.
To remove a directory, use EXT:DELETE-DIRECTORY
instead.
RENAME-FILE
This functions accepts and extra keyword argument :IF-EXISTS
.
When it is :ERROR
(the default), an ERROR
is SIGNAL
ed if the destination
pathname names an existing file, otherwise (e.g., if it is :OVERWRITE
)
the destination file atomically overwritten.
When CUSTOM:*ANSI*
is non-NIL
, only the standard two arguments are accepted,
and and ERROR
is SIGNAL
ed when the destination pathname names an existing file.
This function cannot operate on directories,
use EXT:RENAME-DIRECTORY
to rename a directory.
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.
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 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
"**/*"))
Keyword arguments accepted by DIRECTORY
:FULL
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
).
:CIRCLE
NIL
, DIRECTORY
avoids
endless loops that may result from symbolic links.
:IF-DOES-NOT-EXIST
This argument controls the treatment of links pointing to non-existent files and can take the following values:
:DISCARD
(default):ERROR
ERROR
is SIGNAL
ed 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
)
EXT:RENAME-DIRECTORY
(
renames a
subdirectory to a new name.EXT:RENAME-DIRECTORY
old-directory
new-directory
)
Table of Contents
STREAM-EXTERNAL-FORMAT
STREAM-ELEMENT-TYPE
EXT:MAKE-STREAM
FILE-POSITION
EXT:ELASTIC-NEWLINE
OPEN
CLEAR-INPUT
CLOSE
OPEN-STREAM-P
BROADCAST-STREAM
EXT:MAKE-BUFFERED-INPUT-STREAM
and EXT:MAKE-BUFFERED-OUTPUT-STREAM
Interactive streams are those whose next input might depend on a prompt one might output.
When run interactively, CLISP creates a single “terminal”
STREAM
and binds *TERMINAL-IO*
to it.
All other standard streams (*STANDARD-INPUT*
, *STANDARD-OUTPUT*
*ERROR-OUTPUT*
, *TRACE-OUTPUT*
, *QUERY-IO*
, *DEBUG-IO*
)
are SYNONYM-STREAM
s pointing to *TERMINAL-IO*
.
This has the benefit of avoiding unwanted blank lines from FRESH-LINE
,
see Section 21.6, “Newline Convention”.
However, there may be situations, especially in batch mode,
when one wants to use a C-style i/o where *STANDARD-OUTPUT*
and *ERROR-OUTPUT*
point to different OS file descriptor so that they can be
redirected
to files in the command line and examined separately.
Often CLISP can detect such situations (stdout
and stderr
not being
the terminal) and handle them just as expected.
However, there may be cases when one needs to do something like:
(SETQ
*STANDARD-INPUT*
(EXT:MAKE-STREAM
:INPUT
)*STANDARD-OUTPUT*
(EXT:MAKE-STREAM
:OUTPUT
:BUFFERED
T
)*ERROR-OUTPUT*
(EXT:MAKE-STREAM
:ERROR
:BUFFERED
T
))
in the script or init function.
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.
If you run it as
$
./configure --with-readline
it will fail if it cannot find a valid modern GNU readline installation.
--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.h
in 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.4.1, “Input Characters” for accessing them):
char
the CHARACTER
for standard keys
(accessed with CHARACTER
)
For non-standard keys CHARACTER
SIGNAL
s an ERROR
, use EXT:CHAR-KEY
:
(EXT:WITH-KEYBOARD
(LOOP
:forchar
= (READ-CHAR
EXT:*KEYBOARD-INPUT*
) :forkey
= (OR
(EXT:CHAR-KEY
char
) (CHARACTER
char
)) :do (LIST
char
key
)) :when (EQL
key
#\Space) :return (LIST
char
key
)))
key
the key name, for non-standard keys
(accessed with EXT:CHAR-KEY
):
bits
:HYPER
:SUPER
:CONTROL
:META
font
0
.
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.
READ-BYTE
,
EXT:READ-INTEGER
& EXT:READ-FLOAT
The 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-FLOAT
The 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
.
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 INTEGER
s 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
.
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)INTEGER
s 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
.
The rationale for EXT:READ-CHAR-SEQUENCE
, EXT:READ-BYTE-SEQUENCE
, EXT:WRITE-CHAR-SEQUENCE
and
EXT:WRITE-BYTE-SEQUENCE
is that some STREAM
s 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.
The answer is complicated. There is an antagonism between
the “old Lisp way” of outputting a newline before the
line's contents (exemplified by the functions PRINT
and PPRINT
) and
the “Unix way” of outputting a newline after the line's
contents. Which one is “right”?
A newline convention is, by definition, a consistent way to use
the TERPRI
and FRESH-LINE
functions or - in FORMAT
notation -
~%
and ~&
directives in such a way that the
resulting output is properly subdivided into lines.
Three newline conventions are conceivable:
The most important criterion is interoperability. Two newline conventions are interoperable if, when parts of a program use one of the convention and other parts of the program use the other conventions, lines are still properly separated. It is easily seen that A and B are interoperable, B and C are interoperable as well, but A and C are not interoperable: When an output with convention A is followed by output in convention C, two lines are appended without a line separator. This should not happen.
Therefore, in what follows, we consider five kinds of programs:
Which of these five kinds of programs operation is satisfactory? Let us consider different criteria:
FRESH-LINE
prints a newline when
it is not needed, i.e. when it cannot tell for sure whether the
current column is 0? (This situation happens, for example, when
logging to a file: After the user has entered a line interactively,
the column on screen is 0, but since the input has not been echoed in
the log file, the column in the log file is usually not 0, and
FRESH-LINE
must output a newline. Then a blank
line is visible on the screen.)FRESH-LINE
omits a newline when it
would be needed?
(This is more rare, but can happen, for example, when standard output
and standard error are different streams but are joined outside the
Lisp implementation, at the OS level.
Such as in lisp | cat.)Is it possible to reliably output a blank line before or after a paragraph of text? I.e. what happens with
FRESH-LINE
, namely a conditional newline that is annullated if the
next output on the stream will be a
newline. (EXT:ELASTIC-NEWLINE
, see below.)Each approach has its advantages and disadvantages.
When used globally (i.e. no interoperability requirements), A, B, C can be compared as follows:
For CLISP built-ins, however, the interoperability requirement with both A and C is a major requirement. Therefore we have to choose B, and accept the drawbacks:
And to minimize the drawbacks, we recommend the user programs to use approach B or C, but not A.
Another drawback of B is, however, that in interactive sessions the cursor is nearly always positioned at the beginning of a line, pointing the user's focus to the wrong point and taking away a screen line.
To solve this, we introduce the concept of an elastic
newline, output by the function EXT:ELASTIC-NEWLINE
.
This is the converse of FRESH-LINE
: It waits for the next character
and outputs a newline when the next character is not a newline; then
the next character is processed normally.
As a FORMAT
directive, we write it ~.
.
EXT:ELASTIC-NEWLINE
followed by FRESH-LINE
leads to exactly one newline
always.
Elastic newline leads to a slightly different newline convention:
The five programs being considered are now:
FORCE-OUTPUT
. This is a general problem with buffered streams;
CLISP's FRESH-LINE
contains a workaround that is limited to
*STANDARD-OUTPUT*
and *ERROR-OUTPUT*
.Now criterium 1 is satisfied perfectly. We therefore choose B', not B, for use inside CLISP, and programs can use either A or C without problems during normal operation.
STREAM-EXTERNAL-FORMAT
STREAM-EXTERNAL-FORMAT
is SETF
able: (
,
SETF
(STREAM-EXTERNAL-FORMAT
stream
[direction
]) encoding
)direction
can be :INPUT
, :OUTPUT
, or NIL
.
If no direction
is given, the operation is nonrecursive.
This will not work on *TERMINAL-IO*
et al, use CUSTOM:*TERMINAL-ENCODING*
instead.
STREAM-ELEMENT-TYPE
STREAM-ELEMENT-TYPE
is SETF
able. The STREAM-ELEMENT-TYPE
of
STREAM
s 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-TYPE
s 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-FUNCTION
s, see
Chapter 30, Gray streams.
CLISP expects to be able to
do CHARACTER
i/o on standard streams like *TERMINAL-IO*
,
*STANDARD-OUTPUT*
, *STANDARD-INPUT*
, *ERROR-OUTPUT*
,
*QUERY-IO*
et al, thus is is a very bad idea
to change their STREAM-ELEMENT-TYPE
even when you can. Use
EXT:MAKE-STREAM
instead, see Section 21.8.1, “Binary input from *STANDARD-INPUT*
”.
*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-BYTE
8)WITH-OPEN-STREAM
(in (EXT:MAKE-STREAM
:INPUT
:ELEMENT-TYPE
'(
)) (UNSIGNED-BYTE
8)READ-SEQUENCE
buf in)) buf)
EXT:MAKE-STREAM
Function 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
stdin
(0 on UNIX):OUTPUT
stdout
(1 on UNIX):ERROR
stderr
(2 on UNIX)STREAM
FILE-STREAM
or a SOCKET:SOCKET-STREAM
When there are several Lisp STREAM
s 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 STREAM
s,
and bulk input for input STREAM
s.
The handle is duplicated (with dup
),
so it is safe to CLOSE
a STREAM
returned by EXT:MAKE-STREAM
.
FILE-POSITION
FILE-POSITION
works on any FILE-STREAM
.
FILE-STREAM
, its file position is increased by 2 since #\Newline is
encoded as CR/LF in the file.
EXT:ELASTIC-NEWLINE
The 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 Section 21.6, “Newline Convention”.
OPEN
OPEN
accepts an additional keyword :BUFFERED
.
The acceptable values for the arguments to the
file/pipe/socket STREAM
functions
:ELEMENT-TYPE
types 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-FORMAT
EXT:ENCODING
s, (constant) SYMBOL
s in the
“CHARSET” package, STRING
s (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.
:BUFFERED
NIL
, 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-STREAM
s 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!
CUSTOM:*REOPEN-OPEN-FILE*
When an already opened file is opened again, and not both the
existing and the new STREAM
s are read-only (i.e., :DIRECTION
is
:INPUT
or :INPUT-IMMUTABLE
), the streams can
mess up each other and produce unexpected results.
The user variable CUSTOM:*REOPEN-OPEN-FILE*
controls how CLISP
handles the situation and can take 4 values:
CLEAR-INPUT
Calling CLEAR-INPUT
on a STREAM
removes the end-of-stream
state,
thus making it available for further input.
This allows reading from a file as it is being appended to, as if with tail -f.
CLOSE
Function CLOSE
is a GENERIC-FUNCTION
, see
Chapter 30, Gray streams.
When the :ABORT
argument is non-NIL
, CLOSE
will not
SIGNAL
s 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
(with (
).
This is not recommended though because garbage-collection is not deterministic.
Please use CLOSE
stream
:ABORT
T
)WITH-OPEN-STREAM
etc.
OPEN-STREAM-P
Function OPEN-STREAM-P
is a GENERIC-FUNCTION
, see
Chapter 30, Gray streams.
BROADCAST-STREAM
INPUT-STREAM-P
and INTERACTIVE-STREAM-P
return false for
BROADCAST-STREAM
s.
(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 CHARACTER
s 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 CHARACTER
s 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:
NIL
FILE-STREAM
,
i.e. function
is calledT
end-of-stream
, i.e. one can assume that further characters will always
arrive, without calling function
FUNCTION
FUNCTION
tells, upon call, if further
non-empty string
s 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
WRITE
& WRITE-TO-STRING
PRINT-UNREADABLE-OBJECT
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
, a readable syntax is used for closures:
This feature is turned off by WITH-STANDARD-IO-SYNTAX
because
it is easy to get wrong (see below) and non-portable.
Closures often refer to value cells or other entities from the
lexical environment. The correct operation of a FUNCTION
may depend on the access
to the same value cells as some other, related FUNCTION
s.
If you want to WRITE
and READ
back FUNCTION
s so that their semantics
is preserved, you have to WRITE
and READ
all FUNCTION
s that share
some structure in the lexical environment together, and you have to
either bind *PRINT-READABLY*
to T
or use WITH-STANDARD-IO-SYNTAX
:
(SETF
(VALUES
my-pop my-push) `(LET
((storage ())) (VALUES
(LAMBDA
() (POP
storage)) (LAMBDA
(x) (PUSH
x storage))))) (LET
((pair (READ-FROM-STRING
(WITH-STANDARD-IO-SYNTAX
(LET
((CUSTOM:*PRINT-CLOSURE*
T
)) (PRIN1-TO-STRING
(CONS
my-pop my-push))))))) (SETQ
my-pop-1 (CAR
pair) my-push-1 (CDR
pair)))
Note that my-pop
and my-push
share environment between themselves but not with
my-pop-1
and my-push-1
which
can be easily seen if you do
(LET
((CUSTOM:*PRINT-CLOSURE*
T
) (*PRINT-CIRCLE*
T
)) (LIST
my-pop my-push my-pop-1 my-push-1)))
but which is not at all obvious from the usual
#<
output.
CUSTOM:*PRINT-CLOSURE*
is initially set to NIL
.
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
.
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
.
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.
E.g., when you type (
you want want to see a terse one-line output when FORMAT
T
"return value: ~S~%" v
)v
is something
short (like 0
or NIL
or T
), but you probably want to see
something nice, like
return value: (long list which does not fit on one line)
instead of
return value: (long list which does not fit on one line)
when it does not.
CUSTOM:*PPRINT-FIRST-NEWLINE*
has no effect if *PRINT-PRETTY*
is NIL
.
CUSTOM:*PPRINT-FIRST-NEWLINE*
is initially set to T
.
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 FLOAT
s are printed.
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 x1
... xn
)#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
is used.
Otherwise, the syntax #
rank
Acontents
#A(
is used.element-type
dimensions
contents
)
As explicitly permitted by this section, specialized BIT
and
CHARACTER
ARRAY
s 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 ARRAY
s, 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
which often loses the dimension information.#
rank
Acontents
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:
.
Otherwise, when the variable #-
CLISP #P
"..."
#+
CLISP #S
(PATHNAME
...)CUSTOM:*PRINT-PATHNAMES-ANSI*
is non-NIL
, the
#P
notation is used as per [sec_1-5-1-4-1]
“Resolution of Apparent Conflicts in Exceptional Situations”.
The #S
notation for PATHNAME
s 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 SIGNAL
ed.
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).
FORMAT
The 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 |
.
The output is in English, according to the American conventions, and
these conventions are identical to the British conventions only in the
range n
| <
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-STRING
The functions WRITE
and WRITE-TO-STRING
have an additional
keyword argument :CLOSURE
which is used to bind
CUSTOM:*PRINT-CLOSURE*
.
PRINT-UNREADABLE-OBJECT
Variable 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.
*PRINT-PRETTY*
is initially NIL
but set to T
in config.lisp
. This makes screen output prettier.
*PRINT-ARRAY*
is initially set to T
.
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
[sec_23-1-3-2]When non-NIL
recursive-p
argument is passed to a top-level READ
call, an ERROR
is SIGNAL
ed.
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-FILE
COMPILE-FILE
compiles a file to a platform-independent
bytecode:
(COMPILE-FILE
filename
&KEY
:OUTPUT-FILE
:LISTING:EXTERNAL-FORMAT
((:WARNINGS
CUSTOM:*COMPILE-WARNINGS*
)CUSTOM:*COMPILE-WARNINGS*
) ((:VERBOSE
*COMPILE-VERBOSE*
)*COMPILE-VERBOSE*
) ((*COMPILE-PRINT*
)*COMPILE-PRINT*
))
Options for COMPILE-FILE
filename
:OUTPUT-FILE
NIL
or T
or a pathname designator or an
output STREAM
. The default is T
.:LISTING
NIL
or T
or a pathname designator or an
output STREAM
. The default is NIL
.:EXTERNAL-FORMAT
EXT:ENCODING
of the filename
.
:WARNINGS
:VERBOSE
:PRINT
The 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-FILE is not NIL | #P".fas" | can be loaded using the LOAD function |
auxiliary output file | only if :OUTPUT-FILE is not NIL | #P".lib" | used by COMPILE-FILE when compiling a REQUIRE form referring
to the input file |
listing file | only if :LISTING is not NIL | #P".lis" | disassembly of the output file |
C output file | only if :OUTPUT-FILE is not NIL | #P".c" | “FFI”; this file is created only if the source contains “FFI” forms |
COMPILE-FILE-PATHNAME
The default for the :OUTPUT-FILE
argument is
T
, which means #P".fas"
.
REQUIRE
The function REQUIRE
receives as the optional argument either
a PATHNAME
or a LIST
of PATHNAME
s: files to be LOAD
ed
if the required module is not already present.
LOAD
locationsIn addition to (and before) CUSTOM:*LOAD-PATHS*
, REQUIRE
tries to
find the file to LOAD
in the following locations:
Platform Dependent: Only in CLISP built without configure flag --without-dynamic-modules
.
The system-wide external modules directory
(
.MERGE-PATHNAMES
"dynmod/" CUSTOM:*LIB-DIRECTORY*
)
Platform Dependent: Only in CLISP built without configure flag --without-dynamic-modules
.
The user external modules directory (
(when MERGE-PATHNAMES
"dynmod/" CUSTOM:*USER-LIB-DIRECTORY*
)CUSTOM:*USER-LIB-DIRECTORY*
is non-NIL
).
REQUIRE
was called while LOAD
ing, the
directory with the file being loaded (i.e., (MAKE-PATHNAME
:name NIL
:type NIL
:defaults *LOAD-TRUENAME*
)
).
COMPILE-FILE
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.
If neither is found, (
is called.REQUIRE
#P"foo"
)
It is a very bad
idea to name your files the same way as CLISP modules
(whether system-supplied
or user-installed)
because then REQUIRE
will use different files at compile
and execution times.
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.
LOAD
LOAD
accepts four additional keyword arguments :ECHO
,
:COMPILING
, :EXTRA-FILE-TYPES
, and :OBSOLETE-ACTION
.
(LOAD
filename
&KEY
((:VERBOSE
*LOAD-VERBOSE*
)*LOAD-VERBOSE*
) ((*LOAD-PRINT*
)*LOAD-PRINT*
) ((:ECHO
CUSTOM:*LOAD-ECHO*
)CUSTOM:*LOAD-ECHO*
):IF-DOES-NOT-EXIST
((:COMPILING
CUSTOM:*LOAD-COMPILING*
)CUSTOM:*LOAD-COMPILING*
):EXTRA-FILE-TYPES
((:OBSOLETE-ACTION
CUSTOM:*LOAD-OBSOLETE-ACTION*
)CUSTOM:*LOAD-OBSOLETE-ACTION*
))
:VERBOSE
LOAD
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.
:PRINT
LOAD
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.
:COMPILING
COMPILE-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-TYPES
Specifies 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-ACTION
Specifies 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
:DELETE
#P".fas"
and proceed as with NIL
:ERROR
SIGNAL
an ERROR
:COMPILE
CUSTOM:*LOAD-PATHS*
)
and LOAD
the resultNIL
(default)WARN
and look
for another matching file
If no file can be loaded and :IF-DOES-NOT-EXIST
is non-NIL
, an ERROR
is SIGNAL
ed.
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 SIGNAL
s an ERROR
, three RESTART
s are
available:
SKIP
RETRY
STOP
Variable 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
:INTERPRETER
EVAL
is implemented:COMPILER
COMPILE
and COMPILE-FILE
are implemented
:SOCKETS
:MT
:GENERIC-STREAMS
:LOGICAL-PATHNAMES
:FFI
:GETTEXT
:UNICODE
:LOOP
LOOP
form is implemented
:CLOS
:MOP
:WORD-SIZE=64
:WIN32
hardware
= PC (clone) and operating system
= Win32
(Windows 95/98/Me/NT/2000/XP):PC386
hardware
= 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).:UNIX
operating system
= UNIX (in this case the hardware
is irrelevant!)
:BEOS
operating system
= BeOS (in that case :UNIX
is also present)
:CYGWIN
:UNIX
is also present)
:MACOS
operating 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
The 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.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:
EVAL
and APPLY
frames are considered.
Every evaluation of a form in the interpreter corresponds to an
EVAL
frame. This is the default.APPLY
frames are considered.
Every invocation of an interpreted function corresponds to one
APPLY
frame.Table 25.3. Commands common to the debugger and the stepper
command | abbreviation | operation |
---|---|---|
Error | :e | print the last error object. |
Inspect | :i | INSPECT the last error object. |
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. |
Mode mode | :m mode | sets the current stack mode |
Frame-limit l | :fl | set the frame-limit: this many frames will be printed by Backtrace at most. |
Backtrace [mode [l ]] | :bt [mode [l ]] | lists the stack in the given mode , bottom frame first, top
frame last; at most l frames are printed. |
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 value | :rt value | leaves the current frame, returning the given value. |
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
FUNCTION
s, 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 (argline)
(format t "don't panic~@[ because of ~A~], ~D~%"
(and (plusp (length argline)) argline)
(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 (argline)
(format t "~A: ~A!~%" argline
(aref curses (random (length curses))))))
(list (format nil "~%swear :e curse")
(cons "swear" #'swear)
(cons ":e" #'swear)))))))
List of Examples
DISASSEMBLE
DISASSEMBLE
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:UNCOMPILE
The 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.
DOCUMENTATION
No on-line documentation is available for the system functions
(yet), but see Section 25.2.4, “Function DESCRIBE
”.
DESCRIBE
When 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.
To do this, DESCRIBE
will retrieve the appropriate tables from
CUSTOM:CLHS-ROOT
and CUSTOM:IMPNOTES-ROOT
on the first relevant invocation.
These operations are logged to CUSTOM:*HTTP-LOG-STREAM*
.
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.ai.mit.edu/projects/iiip/doc/CommonLISP/HyperSpec/ or /usr/doc/HyperSpec/
.
If the return value is NIL
, the feature is completely disabled.
CUSTOM:*CLHS-ROOT-DEFAULT*
is initialized in config.lisp
based on
the --hyperspec
passed to the top-level configure
script when CLISP was built.
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
List of Examples
(
makes the
functions TRACE
function-name
...)function-name
, ... traced. Each function-name
should be either
a function name or a LIST
(
, wherefunction-name
&KEY
:SUPPRESS-IF
:MAX-DEPTH
:STEP-IF
:BINDINGS
:PRE
:POST
:PRE-BREAK-IF
:POST-BREAK-IF
:PRE-PRINT
:POST-PRINT
:PRINT
)
:SUPPRESS-IF
form
form
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
form
form
is true
:BINDINGS
((variable
form
)...)variable
s to the result of evaluation of
form
s around evaluation of all of the following forms
:PRE
form
form
before calling the function
:POST
form
form
after return from the function
:PRE-BREAK-IF
form
form
is true:POST-BREAK-IF
form
form
is true:PRE-PRINT
form
form
before calling the
function:POST-PRINT
form
form
after return from the
function:PRINT
form
form
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:
and after evaluating the form it prints:
trace level
. Trace: form
where “trace level” is the total nesting level.
trace level
. Trace: function-name
==> result
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.
Example 25.1. Identifying Individual Calls in TRACE
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
INSPECT
The function INSPECT
accepts a keyword argument
:FRONTEND
, which specifies the way CLISP will
interact with the user, and defaults
to CUSTOM:*INSPECT-FRONTEND*
.
Available :FRONTEND
s for
INSPECT
in CLISP
:TTY
*TERMINAL-IO*
stream. Please use the help command to get the list of all
available commands.:HTTP
A 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 accepts 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 or slots printed in detail
when a sequence or a structure or a CLOS object is inspected.
TIME
The timing data printed by the macro TIME
includes:
GET-INTERNAL-REAL-TIME
),