merged MNA cleanups patch (sbcl-devel 2002-03-05)...
...correct FTYPE for SAPINT-TO-CORE, which has been
renamed to SAP-INT-TO-CORE
...dead code removal
...*TARGET-MOST-NEGATIVE-FIXNUM*" is renamed to
+TARGET-MOST-NEGATIVE-FIXNUM+, as well as being defined
as a constant now (same for the POSITIVE).
...SB!KERNEL::ARG-COUNT-ERROR is defined as a stub, to silence
the flood of style-warnings a little bit.
...some other FIXMEs (renaming DEFINE-STORAGE-CLASSES to
!DEFINE-STORAGE-CLASSES, introducing SB-SHOW
dependencies)
further cleanups of MOST-FOOATIVE-FIXNUM stuff...
...renamed again, this time to SB!XC:MOST-FOOATIVE-FIXNUM
...removed now-redundant DEFCONSTANTs in toplevel.lisp
...removed now-redundant #. wrappers
other tweaks to the patch...
...Instead of defining a second version of ARG-COUNT-ERROR
for use at compile time, move the definition of
ARG-COUNT-ERROR earlier so it'll be visible in more
of the code which uses it.
moved src/code/globals.lisp much earlier in build-order.lisp,
since there's no such thing as too early and since the
previous location was too late for some uses of
SB!DEBUG:*STACK-TOP-HINT*
s/sap-int-type/sap-int/
read without being an expert in ancient languages and so that
can delete a thousand lines of implement-ITERATE macrology.)
+Arthur Lemmens:
+ He found and fixed a number of SBCL bugs while partially porting SBCL
+ to bootstrap under <some other Common Lisp system, which could
+ probably be found in the sbcl-devel archives>.
+
Robert MacLachlan:
He has continued to answer questions about, and contribute fixes to,
the CMU CL project. Some of these fixes, especially for compiler
He has done various low-level work on SBCL, especially for the
SPARC port (and for CPU-architecture-neutral things motivated by
it, like *BACKEND-FEATURES*). He's also contributed miscellaneous
- bug fixes. As of 2002-01-17, he seems to be mostly done with a port
- of SBCL to the SPARC CPU.
+ bug fixes.
Raymond Toy:
He continued to work on CMU CL after the SBCL fork, especially on
INITIALS GLOSSARY (helpful when reading comments, CVS commit logs, etc.)
+AL Arthur Lemmens
MNA Martin Atzmueller
DB Daniel Barlow
DTC Douglas Crosher
;; leaking into target SBCL code.
("src/code/backq")
+ ;; It's difficult to be too early with a DECLAIM SPECIAL (or DEFVAR
+ ;; or whatever) thanks to the sullenly-do-the-wrong-thing semantics
+ ;; of CL special binding when the variable is undeclared.
+ ("src/code/globals" :not-host)
+
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; various DEFSETFs and/or other DEFMACROish things, defined as early as
;; possible so we don't need to fiddle with any subtleties of defining them
("src/code/primordial-extensions")
- ;; for various constants e.g. SB!VM:*TARGET-MOST-POSITIVE-FIXNUM* and
+ ;; for various constants e.g. SB!XC:MOST-POSITIVE-FIXNUM and
;; SB!VM:N-LOWTAG-BITS, needed by "early-objdef" and others
("src/compiler/generic/early-vm")
("src/compiler/generic/early-objdef")
;; and stuff."
;; Dunno exactly what this meant or whether it still holds. -- WHN 19990803
;; FIXME: more informative and up-to-date comment?
- ("src/code/globals" :not-host)
("src/code/kernel" :not-host)
("src/code/toplevel" :not-host)
("src/code/cold-error" :not-host)
; "compiler/generic/core"
("src/code/eval" :not-host) ; uses INFO, wants compiler macro
- ("src/code/target-sap" :not-host) ; uses SAP-INT-TYPE
+ ("src/code/target-sap" :not-host) ; uses SAP-INT type
("src/code/target-package" :not-host) ; needs "code/package"
("src/code/target-random" :not-host) ; needs "code/random"
("src/code/target-hash-table" :not-host) ; needs "code/hash-table"
"REMOVE-FD-HANDLER" "REMOVE-PORT-DEATH-HANDLER"
"REMOVE-PORT-OBJECT"
"RESOLVE-LOADED-ASSEMBLER-REFERENCES"
- "SAP+" "SAP-" "SAP-INT" "SAP-INT-TYPE"
+ "SAP+" "SAP-" "SAP-INT"
"SAP-REF-16" "SAP-REF-32" "SAP-REF-64" "SAP-REF-8"
"SAP-REF-DESCRIPTOR"
"SAP-REF-DOUBLE" "SAP-REF-LONG"
#!-gencgc "DYNAMIC-1-SPACE-START"
#!-gencgc "DYNAMIC-1-SPACE-END"
"READ-ONLY-SPACE-START" "READ-ONLY-SPACE-END"
- "TARGET-BYTE-ORDER"
- "TARGET-HEAP-ADDRESS-SPACE" "*TARGET-MOST-NEGATIVE-FIXNUM*"
- "*TARGET-MOST-POSITIVE-FIXNUM*"
+ "TARGET-BYTE-ORDER" "TARGET-HEAP-ADDRESS-SPACE"
"STATIC-SPACE-START" "STATIC-SPACE-END"
"TRACE-TABLE-CALL-SITE"
"TRACE-TABLE-FUN-EPILOGUE" "TRACE-TABLE-FUN-PROLOGUE"
:translation integer
:inherits (rational real number generic-number))
(fixnum
- :translation (integer #.sb!vm:*target-most-negative-fixnum*
- #.sb!vm:*target-most-positive-fixnum*)
+ :translation (integer #.sb!xc:most-negative-fixnum
+ #.sb!xc:most-positive-fixnum)
:inherits (integer rational real number
generic-number)
:codes (#.sb!vm:even-fixnum-lowtag #.sb!vm:odd-fixnum-lowtag))
(defstruct (system-area-pointer (:constructor make-sap)
(:conc-name "SAP-"))
;; the integer representation of the address
- (int (error "missing SAP-INT argument") :type sap-int-type :read-only t))
+ (int (error "missing SAP-INT argument") :type sap-int :read-only t))
;;; cross-compilation-host analogues of target-CMU CL primitive SAP operations
(defun int-sap (int)
(make-sap :int int))
(defun sap+ (sap offset)
- (declare (type system-area-pointer sap) (type sap-int-type offset))
+ (declare (type system-area-pointer sap) (type sap-int offset))
(make-sap :int (+ (sap-int sap) offset)))
#.`(progn
,@(mapcar (lambda (info)
;;; Is X a fixnum in the target Lisp?
(defun fixnump (x)
(and (integerp x)
- (<= sb!vm:*target-most-negative-fixnum*
- x
- sb!vm:*target-most-positive-fixnum*)))
+ (<= sb!xc:most-negative-fixnum x sb!xc:most-positive-fixnum)))
;;; (This was a useful warning when trying to get bootstrapping
;;; to work, but it's mostly irrelevant noise now that the system
(block ,(fun-name-block-name name)
,@forms)))
(lambda `(lambda ,@lambda-guts))
+ #-sb-xc-host
(named-lambda `(named-lambda ,name ,@lambda-guts))
(inline-lambda
(cond (;; Does the user not even want to inline?
(%compiler-set-up-layout dd inherits)
- (let* ((dd-name (dd-name dd))
- (dtype (dd-declarable-type dd))
- (class (sb!xc:find-class dd-name)))
+ (let* ((dtype (dd-declarable-type dd)))
(let ((copier-name (dd-copier-name dd)))
(when copier-name
:metaclass-name metaclass-name
:metaclass-constructor metaclass-constructor
:dd-type dd-type))
- (conc-name (concatenate 'string (symbol-name class-name) "-"))
(dd-slots (dd-slots dd))
(dd-length (1+ (length slot-names)))
(object-gensym (gensym "OBJECT"))
#!+sb-doc
"the exclusive upper bound on the rank of an array")
-(defconstant sb!xc:array-dimension-limit sb!vm:*target-most-positive-fixnum*
+(defconstant sb!xc:array-dimension-limit sb!xc:most-positive-fixnum
#!+sb-doc
"the exclusive upper bound on any given dimension of an array")
-(defconstant sb!xc:array-total-size-limit sb!vm:*target-most-positive-fixnum*
+(defconstant sb!xc:array-total-size-limit sb!xc:most-positive-fixnum
#!+sb-doc
"the exclusive upper bound on the total number of elements in an array")
(first-try (ash native-address -2))
;; final encoding
(second-try
- (if (<= first-try sb!vm:*target-most-positive-fixnum*)
+ (if (<= first-try sb!xc:most-positive-fixnum)
;; looks good
first-try
;; When the naive encoding fails to make a FIXNUM
;; because the sign is wrong, subtracting *T-M-P-F*
;; should fix it.
- (- first-try sb!vm:*target-most-positive-fixnum*))))
- (aver (<= second-try sb!vm:*target-most-positive-fixnum*))
+ (- first-try sb!xc:most-positive-fixnum))))
+ (aver (<= second-try sb!xc:most-positive-fixnum))
second-try)))
;;; a FIXNUM, to be interpreted as a native pointer, which serves
(declare (type index size))
(do ((n (1- size) (1- n)))
((minusp n))
- (declare (type (integer -1 #.most-positive-fixnum) n))
+ (declare (type index-or-minus-1 n))
(setf (%instance-ref res n) (pop-stack)))
res))
assert-prompt check-type-error case-body-error print-object
describe-object sb!pcl::check-wrapper-validity))
-;;; Gray streams functions not defined until after PCL is loaded.
+;;; Gray streams functions not defined until after PCL is loaded
(declaim (ftype (function * *)
stream-advance-to-column stream-clear-input
stream-clear-output stream-finish-output stream-force-output
`(unsigned-byte ,high-length))
(t
`(mod ,(1+ high)))))
- ((and (= low sb!vm:*target-most-negative-fixnum*)
- (= high sb!vm:*target-most-positive-fixnum*))
+ ((and (= low sb!xc:most-negative-fixnum)
+ (= high sb!xc:most-positive-fixnum))
'fixnum)
((and (= low (lognot high))
(= high-count high-length)
(in-package "SB!KERNEL")
-;;; We save space in macro definitions by calling this function.
-(defun arg-count-error (error-kind name args lambda-list minimum maximum)
- (let (#-sb-xc-host
- (sb!debug:*stack-top-hint* (nth-value 1 (find-caller-name-and-frame))))
- (error 'arg-count-error
- :kind error-kind
- :name name
- :args args
- :lambda-list lambda-list
- :minimum minimum
- :maximum maximum)))
-
(define-condition defmacro-lambda-list-bind-error (error)
((kind :reader defmacro-lambda-list-bind-error-kind
:initarg :kind)
*arg-tests*)))
(values env-arg-used minimum explicit-maximum))))
+;;; We save space in macro definitions by calling this function.
+(defun arg-count-error (error-kind name args lambda-list minimum maximum)
+ (let (#-sb-xc-host
+ (sb!debug:*stack-top-hint* (nth-value 1 (find-caller-name-and-frame))))
+ (error 'arg-count-error
+ :kind error-kind
+ :name name
+ :args args
+ :lambda-list lambda-list
+ :minimum minimum
+ :maximum maximum)))
+
(defun push-sub-list-binding (variable path object name error-kind error-fun)
(let ((var (gensym "TEMP-")))
(push `(,variable
;;; Convert an integer into a SAP.
(defun int-sap (int)
- (declare (type sap-int-type int))
+ (declare (type sap-int int))
(int-sap int))
;;; Return the 8-bit byte at OFFSET bytes from SAP.
(in-package "SB!IMPL")
\f
-(defconstant most-positive-fixnum #.sb!vm:*target-most-positive-fixnum*
- #!+sb-doc
- "the fixnum closest in value to positive infinity")
-
-(defconstant most-negative-fixnum #.sb!vm:*target-most-negative-fixnum*
- #!+sb-doc
- "the fixnum closest in value to negative infinity")
-\f
;;;; magic specials initialized by GENESIS
;;; FIXME: The DEFVAR here is redundant with the (DECLAIM (SPECIAL ..))
(defvar *target-object-file-names*)
-;;; KLUDGE..
-;;;
-;;; CMU CL (as of 2.4.6 for Debian, anyway) issues warnings (and not
-;;; just STYLE-WARNINGs, either, alas) when it tries to interpret code
-;;; containing references to undefined functions. The most common
-;;; problem is that macroexpanded code refers to this function, which
-;;; isn't defined until late.
-;;;
-;;; This
-;;; #+cmu (defun sb!kernel::arg-count-error (&rest rest)
-;;; (error "stub version of ARG-COUNT-ERROR, rest=~S" rest))
-;;; doesn't work, with or without this
-;;; (compile 'sb!kernel::arg-count-error))
-;;; so perhaps I should try
-;;; (declaim (ftype ..) ..)
-;;; instead?
-(declaim (ftype (function (&rest t) nil) sb!kernel::arg-count-error))
-
(let ((reversed-target-object-file-names nil))
(do-stems-and-flags (stem flags)
(unless (position :not-target flags)
;;; values of special variables such as *** and +, anyway). Set up
;;; machinery to warn us when/if we change it.
;;;
-;;; FIXME: All this machinery should probably be conditional on
-;;; #!+SB-SHOW, i.e. we should be able to wrap #!+SB-SHOW around both
-;;; the LOAD and the DEFVAR here.
-(load "src/cold/snapshot.lisp")
-(defvar *cl-snapshot* (take-snapshot "COMMON-LISP"))
+;;; All code depending on this is itself dependent on #!+SB-SHOW.
+#!+sb-show
+(progn
+ (load "src/cold/snapshot.lisp")
+ (defvar *cl-snapshot* (take-snapshot "COMMON-LISP")))
\f
;;;; master list of source files and their properties
,error)))))
\f
-;;; PSEUDO-ATOMIC -- Handy macro for making sequences look atomic.
-;;;
+;;; a handy macro for making sequences look atomic
(defmacro pseudo-atomic ((&key (extra 0)) &rest forms)
`(progn
(inst addq alloc-tn 1 alloc-tn)
,@forms
(inst lda alloc-tn (1- ,extra) alloc-tn)
(inst stl zero-tn 0 alloc-tn)))
-
-
\f
-;;;; Memory accessor vop generators
+;;;; memory accessor vop generators
(deftype load/store-index (scale lowtag min-offset
&optional (max-offset min-offset))
;;; a handy macro so we don't have to keep changing all the numbers
;;; whenever we insert a new storage class.
-;;;
-;;; FIXME: This macro is not needed in the runtime target.
-(defmacro define-storage-classes (&rest classes)
+(defmacro !define-storage-classes (&rest classes)
(do ((forms (list 'progn)
(let* ((class (car classes))
(sc-name (car class))
;;; and seems to be working so far -dan
(defconstant sb!vm::kludge-nondeterministic-catch-block-size 7)
-(define-storage-classes
+(!define-storage-classes
- ;; Non-immediate contstants in the constant pool
+ ;; non-immediate constants in the constant pool
(constant constant)
;; ZERO and NULL are in registers.
(foldable flushable))
(defknown hash-table-size (hash-table) index (flushable))
(defknown hash-table-test (hash-table) symbol (foldable flushable))
-(defknown sxhash (t) (integer 0 #.sb!vm:*target-most-positive-fixnum*)
+(defknown sxhash (t) (integer 0 #.sb!xc:most-positive-fixnum)
(foldable flushable))
\f
;;;; from the "Arrays" chapter
;;; a mask to extract the type from a data block header word
(defconstant widetag-mask (1- (ash 1 n-widetag-bits)))
-;;; FIXME: Couldn't/shouldn't these be DEFCONSTANT instead of
-;;; DEFPARAMETER? (It might seem even more tempting to make them
-;;; SB!XC:MOST-POSITIVE-FIXNUM and SB!XC:MOST-NEGATIVE-FIXNUM,
-;;; but that's probably not a good idea, since then we'd need
-;;; to worry about the effect of UNCROSS in expressions like
-;;; (DEFTYPE INDX3 () `(INTEGER 3 ,SB!XC:MOST-POSITIVE-FIXNUM)).)
-(defparameter *target-most-positive-fixnum* (1- (ash 1 29))
+(defconstant sb!xc:most-positive-fixnum (1- (ash 1 29))
#!+sb-doc
- "most-positive-fixnum in the target architecture")
-(defparameter *target-most-negative-fixnum* (ash -1 29)
+ "the fixnum closest in value to positive infinity")
+(defconstant sb!xc:most-negative-fixnum (ash -1 29)
#!+sb-doc
- "most-negative-fixnum in the target architecture")
+ "the fixnum closest in value to negative infinity")
(read-wordindexed address 0))
;;; (Note: In CMU CL, this function expected a SAP-typed ADDRESS
-;;; value, instead of the SAPINT we use here.)
-(declaim (ftype (function (sb!vm:word descriptor) (values)) note-load-time-value-reference))
+;;; value, instead of the SAP-INT we use here.)
+(declaim (ftype (function (sb!vm:word descriptor) (values))
+ note-load-time-value-reference))
(defun note-load-time-value-reference (address marker)
(cold-push (cold-cons
(cold-intern :load-time-value-fixup)
- (cold-cons (sapint-to-core address)
+ (cold-cons (sap-int-to-core address)
(cold-cons
(number-to-core (descriptor-word-offset marker))
*nil-descriptor*)))
(float (float-to-core number))
(t (error "~S isn't a cold-loadable number at all!" number))))
-(declaim (ftype (function (sb!vm:word) descriptor) sap-to-core))
-(defun sapint-to-core (sapint)
+(declaim (ftype (function (sb!vm:word) descriptor) sap-int-to-core))
+(defun sap-int-to-core (sap-int)
(let ((des (allocate-unboxed-object *dynamic*
sb!vm:n-word-bits
(1- sb!vm:sap-size)
sb!vm:sap-widetag)))
(write-wordindexed des
sb!vm:sap-pointer-slot
- (make-random-descriptor sapint))
+ (make-random-descriptor sap-int))
des))
;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR.
(write-wordindexed symbol
sb!vm:symbol-hash-slot
(make-fixnum-descriptor
- (1+ (random sb!vm:*target-most-positive-fixnum*))))
+ (1+ (random sb!xc:most-positive-fixnum))))
(write-wordindexed symbol sb!vm:symbol-plist-slot *nil-descriptor*)
(write-wordindexed symbol sb!vm:symbol-name-slot
(string-to-core name *dynamic*))
;;;; symbols
#!+x86
-(defknown symbol-hash (symbol) (integer 0 #.*target-most-positive-fixnum*)
+(defknown symbol-hash (symbol) (integer 0 #.sb!xc:most-positive-fixnum)
(flushable movable))
(define-primitive-object (symbol :lowtag other-pointer-lowtag
;;; Compile FORM and arrange for it to be called at load-time. Return
;;; the dumper handle and our best guess at the type of the object.
-(defun compile-load-time-value
- (form &optional
- (name (let ((*print-level* 2) (*print-length* 3))
- (format nil "load time value of ~S"
- (if (and (listp form)
- (eq (car form) 'make-value-cell))
- (second form)
- form)))))
- (let ((lambda (compile-load-time-stuff form name t)))
+(defun compile-load-time-value (form)
+ (let ((lambda (compile-load-time-stuff form t)))
(values
(fasl-dump-load-time-value-lambda lambda *compile-object*)
(let ((type (leaf-type lambda)))
;;; Compile the FORMS and arrange for them to be called (for effect,
;;; not value) at load time.
-(defun compile-make-load-form-init-forms (forms name)
- (let ((lambda (compile-load-time-stuff `(progn ,@forms) name nil)))
+(defun compile-make-load-form-init-forms (forms)
+ (let ((lambda (compile-load-time-stuff `(progn ,@forms) nil)))
(fasl-dump-toplevel-lambda-call lambda *compile-object*)))
;;; Do the actual work of COMPILE-LOAD-TIME-VALUE or
;;; COMPILE-MAKE-LOAD-FORM-INIT-FORMS.
-(defun compile-load-time-stuff (form name for-value)
+(defun compile-load-time-stuff (form for-value)
(with-ir1-namespace
(let* ((*lexenv* (make-null-lexenv))
(lambda (ir1-toplevel form *current-path* for-value)))
(fasl-note-handle-for-constant
constant
(compile-load-time-value
- creation-form
- (format nil "creation form for ~A" name))
+ creation-form)
*compile-object*)
nil)
(compiler-error "circular references in creation form for ~S"
\f
-;;; PSEUDO-ATOMIC -- Handy macro for making sequences look atomic.
-;;;
+;;; a handy macro for making sequences look atomic
(defmacro pseudo-atomic ((&key (extra 0)) &rest forms)
(let ((n-extra (gensym)))
`(let ((,n-extra ,extra))
- ;; Set the pseudo-atomic flag
+ ;; Set the pseudo-atomic flag.
(without-scheduling ()
(inst add alloc-tn 4))
,@forms
- ;; Reset the pseudo-atomic flag
+ ;; Reset the pseudo-atomic flag.
(without-scheduling ()
#+nil (inst taddcctv alloc-tn (- ,n-extra 4))
- ;; Remove the pseudo-atomic flag
+ ;; Remove the pseudo-atomic flag.
(inst add alloc-tn (- ,n-extra 4))
- ;; Check to see if pseudo-atomic interrupted flag is set (bit 0 = 1)
+ ;; Check to see if pseudo-atomic interrupted flag is set (bit 0 = 1).
(inst andcc zero-tn alloc-tn 3)
;; The C code needs to process this correctly and fixup alloc-tn.
- (inst t :ne pseudo-atomic-trap)
- ))))
+ (inst t :ne pseudo-atomic-trap)))))
;;; FIXME: test typing macros. Should(?) be in type-vops.lisp, except
;;; that they're also used in subprim.lisp
(list ,@(mapcar (lambda (name)
(symbolicate name "-OFFSET"))
regs))))))
- ;; "c.f. src/runtime/sparc-lispregs.h
+ ;; c.f. src/runtime/sparc-lispregs.h
;; Globals. These are difficult to extract from a sigcontext.
(defreg zero 0) ; %g0
(defregset *register-arg-offsets*
a0 a1 a2 a3 a4 a5))
\f
-;;;; SB and SC definition:
+;;;; SB and SC definition
(define-storage-base registers :finite :size 32)
(define-storage-base float-registers :finite :size 64)
(define-storage-base constant :non-packed)
(define-storage-base immediate-constant :non-packed)
-;;; Handy macro so we don't have to keep changing all the numbers whenever
-;;; we insert a new storage class.
-;;;
-;;; FIXME: This macro is not needed in the runtime target.
-(defmacro define-storage-classes (&rest classes)
+;;; handy macro so we don't have to keep changing all the numbers
+;;; whenever we insert a new storage class
+(defmacro !define-storage-classes (&rest classes)
(do ((forms (list 'progn)
(let* ((class (car classes))
(sc-name (car class))
;;; arbitrarily taken for alpha, too. - Christophe
(defconstant sb!vm::kludge-nondeterministic-catch-block-size 7)
-(define-storage-classes
+(!define-storage-classes
- ;; Non-immediate contstants in the constant pool
+ ;; non-immediate constants in the constant pool
(constant constant)
;; ZERO and NULL are in registers.
;; Anything else that can be an immediate.
(immediate immediate-constant)
-
- ;; **** The stacks.
+ ;;
+ ;; the stacks
+ ;;
;; The control stack. (Scanned by GC)
(control-stack control-stack)
(flet ((ash-outer (n s)
(when (and (fixnump s)
(<= s 64)
- (> s sb!vm:*target-most-negative-fixnum*))
+ (> s sb!xc:most-negative-fixnum))
(ash n s)))
;; KLUDGE: The bare 64's here should be related to
;; symbolic machine word size values somehow.
(ash-inner (n s)
(if (and (fixnump s)
- (> s sb!vm:*target-most-negative-fixnum*))
+ (> s sb!xc:most-negative-fixnum))
(ash n (min s 64))
(if (minusp n) -1 0))))
(or (and (csubtypep n-type (specifier-type 'integer))
;;; the size of an INTEGER representation of a SYSTEM-AREA-POINTER, i.e.
;;; size of a native memory address
-(deftype sap-int-type () '(unsigned-byte 32))
-;;; FIXME: This should just named be SAP-INT, not SAP-INT-TYPE. And
-;;; grep for SAPINT in the code and replace it with SAP-INT as
-;;; appropriate.
+(deftype sap-int () '(unsigned-byte 32))
\f
;;;; register specs
;;; a handy macro so we don't have to keep changing all the numbers whenever
;;; we insert a new storage class
;;;
-;;; FIXME: This macro is not needed in the runtime target.
-(defmacro define-storage-classes (&rest classes)
+(defmacro !define-storage-classes (&rest classes)
(collect ((forms))
(let ((index 0))
(dolist (class classes)
(eval-when (:compile-toplevel :load-toplevel :execute)
(defconstant kludge-nondeterministic-catch-block-size 6))
-(define-storage-classes
+(!define-storage-classes
- ;; non-immediate contstants in the constant pool
+ ;; non-immediate constants in the constant pool
(constant constant)
;; some FP constants can be generated in the i387 silicon
;;; for internal versions, especially for internal versions off the
;;; main CVS branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".)
-"0.7.1.31"
+"0.7.1.32"