(belated 0.6.11.2 checkin notes):
[sbcl.git] / src / code / early-extensions.lisp
1 ;;;; This file contains definitions and declarations for the
2 ;;;; EXTENSIONS package which must be available at early cross-compile
3 ;;;; time, and perhaps also some things which might as well be built
4 ;;;; at cross-compile time even if they're not strictly needed, since
5 ;;;; that's harmless. Things which can't be built at cross-compile
6 ;;;; time (e.g. because they need machinery which only exists inside
7 ;;;; CMU CL's implementation of the LISP package) do not belong in
8 ;;;; this file.
9
10 ;;;; This software is part of the SBCL system. See the README file for
11 ;;;; more information.
12 ;;;;
13 ;;;; This software is derived from the CMU CL system, which was
14 ;;;; written at Carnegie Mellon University and released into the
15 ;;;; public domain. The software is in the public domain and is
16 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
17 ;;;; files for more information.
18
19 (in-package "SB!IMPL")
20
21 ;;; something not EQ to anything we might legitimately READ
22 (defparameter *eof-object* (make-symbol "EOF-OBJECT"))
23
24 ;;; a type used for indexing into arrays, and for related quantities
25 ;;; like lengths of lists
26 ;;;
27 ;;; It's intentionally limited to one less than the
28 ;;; ARRAY-DIMENSION-LIMIT for efficiency reasons, because in SBCL
29 ;;; ARRAY-DIMENSION-LIMIT is MOST-POSITIVE-FIXNUM, and staying below
30 ;;; that lets the system know it can increment a value of this type
31 ;;; without having to worry about using a bignum to represent the
32 ;;; result.
33 ;;;
34 ;;; (It should be safe to use ARRAY-DIMENSION-LIMIT as an exclusive
35 ;;; bound because ANSI specifies it as an exclusive bound.)
36 (def!type index () `(integer 0 (,sb!xc:array-dimension-limit)))
37
38 ;;; the default value used for initializing character data. The ANSI
39 ;;; spec says this is arbitrary. CMU CL used #\NULL, which we avoid
40 ;;; because it's not in the ANSI table of portable characters.
41 (defconstant default-init-char #\space)
42
43 ;;; CHAR-CODE values for ASCII characters which we care about but
44 ;;; which aren't defined in section "2.1.3 Standard Characters" of the
45 ;;; ANSI specification for Lisp
46 ;;;
47 ;;; KLUDGE: These are typically used in the idiom (CODE-CHAR
48 ;;; FOO-CHAR-CODE). I suspect that the current implementation is
49 ;;; expanding this idiom into a full call to CODE-CHAR, which is an
50 ;;; annoying overhead. I should check whether this is happening, and
51 ;;; if so, perhaps implement a DEFTRANSFORM or something to stop it.
52 ;;; (or just find a nicer way of expressing characters portably?) --
53 ;;; WHN 19990713
54 (defconstant bell-char-code 7)
55 (defconstant tab-char-code 9)
56 (defconstant form-feed-char-code 12)
57 (defconstant return-char-code 13)
58 (defconstant escape-char-code 27)
59 (defconstant rubout-char-code 127)
60 \f
61 ;;;; miscellaneous iteration extensions
62
63 (defmacro dovector ((elt vector &optional result) &rest forms)
64   #!+sb-doc
65   "just like DOLIST, but with one-dimensional arrays"
66   (let ((index (gensym))
67         (length (gensym))
68         (vec (gensym)))
69     `(let ((,vec ,vector))
70        (declare (type vector ,vec))
71        (do ((,index 0 (1+ ,index))
72             (,length (length ,vec)))
73            ((>= ,index ,length) ,result)
74          (let ((,elt (aref ,vec ,index)))
75            ,@forms)))))
76
77 (defmacro dohash ((key-var value-var table &optional result) &body body)
78   #!+sb-doc
79   "DOHASH (Key-Var Value-Var Table [Result]) Declaration* Form*
80    Iterate over the entries in a hash-table."
81   (multiple-value-bind (forms decls) (parse-body body nil)
82     (let ((gen (gensym))
83           (n-more (gensym)))
84       `(with-hash-table-iterator (,gen ,table)
85          (loop
86           (multiple-value-bind (,n-more ,key-var ,value-var) (,gen)
87             ,@decls
88             (unless ,n-more (return ,result))
89             ,@forms))))))
90 \f
91 ;;;; hash cache utility
92
93 (eval-when (:compile-toplevel :load-toplevel :execute)
94   (defvar *profile-hash-cache* nil))
95
96 ;;; :INIT-WRAPPER is set to COLD-INIT-FORMS in type system definitions
97 ;;; so that caches will be created before top-level forms run.
98 (defmacro define-hash-cache (name args &key hash-function hash-bits default
99                                   (init-wrapper 'progn)
100                                   (values 1))
101   #!+sb-doc
102   "DEFINE-HASH-CACHE Name ({(Arg-Name Test-Function)}*) {Key Value}*
103   Define a hash cache that associates some number of argument values to a
104   result value. The Test-Function paired with each Arg-Name is used to compare
105   the value for that arg in a cache entry with a supplied arg. The
106   Test-Function must not error when passed NIL as its first arg, but need not
107   return any particular value. Test-Function may be any thing that can be
108   placed in CAR position.
109
110   Name is used to define these functions:
111
112   <name>-CACHE-LOOKUP Arg*
113       See whether there is an entry for the specified Args in the cache. If
114       not present, the :DEFAULT keyword (default NIL) determines the result(s).
115
116   <name>-CACHE-ENTER Arg* Value*
117       Encache the association of the specified args with Value.
118
119   <name>-CACHE-CLEAR
120       Reinitialize the cache, invalidating all entries and allowing the
121       arguments and result values to be GC'd.
122
123   These other keywords are defined:
124
125   :HASH-BITS <n>
126       The size of the cache as a power of 2.
127
128   :HASH-FUNCTION function
129       Some thing that can be placed in CAR position which will compute a value
130       between 0 and (1- (expt 2 <hash-bits>)).
131
132   :VALUES <n>
133       The number of values cached.
134
135   :INIT-WRAPPER <name>
136       The code for initializing the cache is wrapped in a form with the
137       specified name. Default PROGN."
138
139   (let* ((var-name (symbolicate "*" name "-CACHE-VECTOR*"))
140          (nargs (length args))
141          (entry-size (+ nargs values))
142          (size (ash 1 hash-bits))
143          (total-size (* entry-size size))
144          (default-values (if (and (consp default) (eq (car default) 'values))
145                              (cdr default)
146                              (list default)))
147          (n-index (gensym))
148          (n-cache (gensym)))
149
150     (unless (= (length default-values) values)
151       (error "The number of default values ~S differs from :VALUES ~D."
152              default values))
153
154     (collect ((inlines)
155               (forms)
156               (inits)
157               (tests)
158               (sets)
159               (arg-vars)
160               (values-indices)
161               (values-names))
162       (dotimes (i values)
163         (values-indices `(+ ,n-index ,(+ nargs i)))
164         (values-names (gensym)))
165       (let ((n 0))
166         (dolist (arg args)
167           (unless (= (length arg) 2)
168             (error "bad argument spec: ~S" arg))
169           (let ((arg-name (first arg))
170                 (test (second arg)))
171             (arg-vars arg-name)
172             (tests `(,test (svref ,n-cache (+ ,n-index ,n)) ,arg-name))
173             (sets `(setf (svref ,n-cache (+ ,n-index ,n)) ,arg-name)))
174           (incf n)))
175
176       (when *profile-hash-cache*
177         (let ((n-probe (symbolicate "*" name "-CACHE-PROBES*"))
178               (n-miss (symbolicate "*" name "-CACHE-MISSES*")))
179           (inits `(setq ,n-probe 0))
180           (inits `(setq ,n-miss 0))
181           (forms `(defvar ,n-probe))
182           (forms `(defvar ,n-miss))
183           (forms `(declaim (fixnum ,n-miss ,n-probe)))))
184
185       (let ((fun-name (symbolicate name "-CACHE-LOOKUP")))
186         (inlines fun-name)
187         (forms
188          `(defun ,fun-name ,(arg-vars)
189             ,@(when *profile-hash-cache*
190                 `((incf ,(symbolicate  "*" name "-CACHE-PROBES*"))))
191             (let ((,n-index (* (,hash-function ,@(arg-vars)) ,entry-size))
192                   (,n-cache ,var-name))
193               (declare (type fixnum ,n-index))
194               (cond ((and ,@(tests))
195                      (values ,@(mapcar (lambda (x) `(svref ,n-cache ,x))
196                                        (values-indices))))
197                     (t
198                      ,@(when *profile-hash-cache*
199                          `((incf ,(symbolicate  "*" name "-CACHE-MISSES*"))))
200                      ,default))))))
201
202       (let ((fun-name (symbolicate name "-CACHE-ENTER")))
203         (inlines fun-name)
204         (forms
205          `(defun ,fun-name (,@(arg-vars) ,@(values-names))
206             (let ((,n-index (* (,hash-function ,@(arg-vars)) ,entry-size))
207                   (,n-cache ,var-name))
208               (declare (type fixnum ,n-index))
209               ,@(sets)
210               ,@(mapcar #'(lambda (i val)
211                             `(setf (svref ,n-cache ,i) ,val))
212                         (values-indices)
213                         (values-names))
214               (values)))))
215
216       (let ((fun-name (symbolicate name "-CACHE-CLEAR")))
217         (forms
218          `(defun ,fun-name ()
219             (do ((,n-index ,(- total-size entry-size) (- ,n-index ,entry-size))
220                  (,n-cache ,var-name))
221                 ((minusp ,n-index))
222               (declare (type fixnum ,n-index))
223               ,@(collect ((arg-sets))
224                   (dotimes (i nargs)
225                     (arg-sets `(setf (svref ,n-cache (+ ,n-index ,i)) nil)))
226                   (arg-sets))
227               ,@(mapcar #'(lambda (i val)
228                             `(setf (svref ,n-cache ,i) ,val))
229                         (values-indices)
230                         default-values))
231             (values)))
232         (forms `(,fun-name)))
233
234       (inits `(unless (boundp ',var-name)
235                 (setq ,var-name (make-array ,total-size))))
236
237       `(progn
238          (defvar ,var-name)
239          (declaim (type (simple-vector ,total-size) ,var-name))
240          #!-sb-fluid (declaim (inline ,@(inlines)))
241          (,init-wrapper ,@(inits))
242          ,@(forms)
243          ',name))))
244
245 (defmacro defun-cached ((name &rest options &key (values 1) default
246                               &allow-other-keys)
247                         args &body body-decls-doc)
248   #!+sb-doc
249   "DEFUN-CACHED (Name {Key Value}*) ({(Arg-Name Test-Function)}*) Form*
250   Some syntactic sugar for defining a function whose values are cached by
251   DEFINE-HASH-CACHE."
252   (let ((default-values (if (and (consp default) (eq (car default) 'values))
253                             (cdr default)
254                             (list default)))
255         (arg-names (mapcar #'car args)))
256     (collect ((values-names))
257       (dotimes (i values)
258         (values-names (gensym)))
259       (multiple-value-bind (body decls doc) (parse-body body-decls-doc)
260         `(progn
261            (define-hash-cache ,name ,args ,@options)
262            (defun ,name ,arg-names
263              ,@decls
264              ,doc
265              (multiple-value-bind ,(values-names)
266                  (,(symbolicate name "-CACHE-LOOKUP") ,@arg-names)
267                (if (and ,@(mapcar #'(lambda (val def)
268                                       `(eq ,val ,def))
269                                   (values-names) default-values))
270                    (multiple-value-bind ,(values-names)
271                                         (progn ,@body)
272                      (,(symbolicate name "-CACHE-ENTER") ,@arg-names
273                       ,@(values-names))
274                      (values ,@(values-names)))
275                    (values ,@(values-names))))))))))
276 \f
277 ;;;; package idioms
278
279 ;;; Note: Almost always you want to use FIND-UNDELETED-PACKAGE-OR-LOSE
280 ;;; instead of this function. (The distinction only actually matters when
281 ;;; PACKAGE-DESIGNATOR is actually a deleted package, and in that case
282 ;;; you generally do want to signal an error instead of proceeding.)
283 (defun %find-package-or-lose (package-designator)
284   (or (find-package package-designator)
285       (error 'sb!kernel:simple-package-error
286              :package package-designator
287              :format-control "The name ~S does not designate any package."
288              :format-arguments (list package-designator))))
289
290 ;;; ANSI specifies (in the section for FIND-PACKAGE) that the
291 ;;; consequences of most operations on deleted packages are
292 ;;; unspecified. We try to signal errors in such cases.
293 (defun find-undeleted-package-or-lose (package-designator)
294   (let ((maybe-result (%find-package-or-lose package-designator)))
295     (if (package-name maybe-result)     ; if not deleted
296         maybe-result
297         (error 'sb!kernel:simple-package-error
298                :package maybe-result
299                :format-control "The package ~S has been deleted."
300                :format-arguments (list maybe-result)))))
301 \f
302 ;;;; miscellany
303
304 ;;; Is NAME a legal function name?
305 (defun legal-function-name-p (name)
306   (or (symbolp name)
307       (and (consp name)
308            (eq (car name) 'setf)
309            (consp (cdr name))
310            (symbolp (cadr name))
311            (null (cddr name)))))
312
313 ;;; Given a function name, return the name for the BLOCK which
314 ;;; encloses its body (e.g. in DEFUN, DEFINE-COMPILER-MACRO, or FLET).
315 (declaim (ftype (function ((or symbol cons)) symbol) function-name-block-name))
316 (defun function-name-block-name (function-name)
317   (cond ((symbolp function-name)
318          function-name)
319         ((and (consp function-name)
320               (= (length function-name) 2)
321               (eq (first function-name) 'setf))
322          (second function-name))
323         (t
324          (error "not legal as a function name: ~S" function-name))))
325
326 ;;; Is X a (possibly-improper) list of at least N elements?
327 (declaim (ftype (function (t index)) list-of-length-at-least-p))
328 (defun list-of-length-at-least-p (x n)
329   (or (zerop n) ; since anything can be considered an improper list of length 0
330       (and (consp x)
331            (list-of-length-at-least-p (cdr x) (1- n)))))
332
333 ;;; Return a list of N gensyms. (This is a common suboperation in
334 ;;; macros and other code-manipulating code.)
335 (declaim (ftype (function (index) list) make-gensym-list))
336 (defun make-gensym-list (n)
337   (loop repeat n collect (gensym)))
338
339 ;;; ANSI guarantees that some symbols are self-evaluating. This
340 ;;; function is to be called just before a change which would affect
341 ;;; that. (We don't absolutely have to call this function before such
342 ;;; changes, since such changes are given as undefined behavior. In
343 ;;; particular, we don't if the runtime cost would be annoying. But
344 ;;; otherwise it's nice to do so.)
345 (defun about-to-modify (symbol)
346   (declare (type symbol symbol))
347   (cond ((eq symbol t)
348          (error "Veritas aeterna. (can't change T)"))
349         ((eq symbol nil)
350          (error "Nihil ex nihil. (can't change NIL)"))
351         ((keywordp symbol)
352          (error "Keyword values can't be changed."))
353         ;; (Just because a value is CONSTANTP is not a good enough
354         ;; reason to complain here, because we want DEFCONSTANT to
355         ;; be able to use this function, and it's legal to DEFCONSTANT
356         ;; a constant as long as the new value is EQL to the old
357         ;; value.)
358         ))
359 \f
360 ;;;; DEFPRINTER
361
362 ;;; These functions are called by the expansion of the DEFPRINTER
363 ;;; macro to do the actual printing.
364 (declaim (ftype (function (symbol t stream &optional t) (values))
365                 defprinter-prin1 defprinter-princ))
366 (defun defprinter-prin1 (name value stream &optional indent)
367   (declare (ignore indent))
368   (defprinter-prinx #'prin1 name value stream))
369 (defun defprinter-princ (name value stream &optional indent)
370   (declare (ignore indent))
371   (defprinter-prinx #'princ name value stream))
372 (defun defprinter-prinx (prinx name value stream)
373   (declare (type function prinx))
374   (when *print-pretty*
375     (pprint-newline :linear stream))
376   (format stream ":~A " name)
377   (funcall prinx value stream)
378   (values))
379 (defun defprinter-print-space (stream)
380   (write-char #\space stream))
381
382 ;;; Define some kind of reasonable PRINT-OBJECT method for a
383 ;;; STRUCTURE-OBJECT class.
384 ;;;
385 ;;; NAME is the name of the structure class, and CONC-NAME is the same
386 ;;; as in DEFSTRUCT.
387 ;;;
388 ;;; The SLOT-DESCS describe how each slot should be printed. Each
389 ;;; SLOT-DESC can be a slot name, indicating that the slot should
390 ;;; simply be printed. A SLOT-DESC may also be a list of a slot name
391 ;;; and other stuff. The other stuff is composed of keywords followed
392 ;;; by expressions. The expressions are evaluated with the variable
393 ;;; which is the slot name bound to the value of the slot. These
394 ;;; keywords are defined:
395 ;;;
396 ;;; :PRIN1    Print the value of the expression instead of the slot value.
397 ;;; :PRINC    Like :PRIN1, only princ the value
398 ;;; :TEST     Only print something if the test is true.
399 ;;;
400 ;;; If no printing thing is specified then the slot value is printed
401 ;;; as if by PRIN1.
402 ;;;
403 ;;; The structure being printed is bound to STRUCTURE and the stream
404 ;;; is bound to STREAM.
405 (defmacro defprinter ((name &key (conc-name (concatenate 'simple-string
406                                                          (symbol-name name)
407                                                          "-")))
408                       &rest slot-descs)
409   (let ((first? t)
410         maybe-print-space
411         (reversed-prints nil)
412         (stream (gensym "STREAM")))
413     (flet ((sref (slot-name)
414              `(,(symbolicate conc-name slot-name) structure)))
415       (dolist (slot-desc slot-descs)
416         (if first?
417             (setf maybe-print-space nil
418                   first? nil)
419             (setf maybe-print-space `(defprinter-print-space ,stream)))
420         (cond ((atom slot-desc)
421                (push maybe-print-space reversed-prints)
422                (push `(defprinter-prin1 ',slot-desc ,(sref slot-desc) ,stream)
423                      reversed-prints))
424               (t
425                (let ((sname (first slot-desc))
426                      (test t))
427                  (collect ((stuff))
428                    (do ((option (rest slot-desc) (cddr option)))
429                        ((null option)
430                         (push `(let ((,sname ,(sref sname)))
431                                  (when ,test
432                                    ,maybe-print-space
433                                    ,@(or (stuff)
434                                          `((defprinter-prin1
435                                              ',sname ,sname ,stream)))))
436                               reversed-prints))
437                      (case (first option)
438                        (:prin1
439                         (stuff `(defprinter-prin1
440                                   ',sname ,(second option) ,stream)))
441                        (:princ
442                         (stuff `(defprinter-princ
443                                   ',sname ,(second option) ,stream)))
444                        (:test (setq test (second option)))
445                        (t
446                         (error "bad option: ~S" (first option)))))))))))
447     `(def!method print-object ((structure ,name) ,stream)
448        ;; FIXME: should probably be byte-compiled
449        (pprint-logical-block (,stream nil)
450          (print-unreadable-object (structure ,stream :type t)
451            (when *print-pretty*
452              (pprint-indent :block 2 ,stream))
453            ,@(nreverse reversed-prints))))))
454 \f
455 #|
456 ;;; REMOVEME when done testing byte cross-compiler
457 (defun byte-compiled-foo (x y)
458   (declare (optimize (speed 0) (debug 1)))
459   (if x
460       x
461       (cons y y)))
462 |#