0.9.1.51:
[sbcl.git] / src / compiler / globaldb.lisp
1 ;;;; This file provides a functional interface to global information
2 ;;;; about named things in the system. Information is considered to be
3 ;;;; global if it must persist between invocations of the compiler. The
4 ;;;; use of a functional interface eliminates the need for the compiler
5 ;;;; to worry about the actual representation. This is important, since
6 ;;;; the information may well have several representations.
7 ;;;;
8 ;;;; The database contains arbitrary Lisp values, addressed by a
9 ;;;; combination of Name, Class and Type. The Name is a EQUAL-thing
10 ;;;; which is the name of the thing we are recording information
11 ;;;; about. Class is the kind of object involved. Typical classes are
12 ;;;; :FUNCTION, :VARIABLE, :TYPE, ... A Type names a particular piece
13 ;;;; of information within a given class. Class and Type are keywords,
14 ;;;; and are compared with EQ.
15
16 ;;;; This software is part of the SBCL system. See the README file for
17 ;;;; more information.
18 ;;;;
19 ;;;; This software is derived from the CMU CL system, which was
20 ;;;; written at Carnegie Mellon University and released into the
21 ;;;; public domain. The software is in the public domain and is
22 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
23 ;;;; files for more information.
24
25 (in-package "SB!C")
26
27 (!begin-collecting-cold-init-forms)
28 #!+sb-show (!cold-init-forms (/show0 "early in globaldb.lisp cold init"))
29
30 ;;; The DEFVAR for this appears later.
31 ;;; FIXME: centralize
32 (declaim (special *universal-type*))
33
34 ;;; This is sorta semantically equivalent to SXHASH, but optimized for
35 ;;; legal function names.
36 ;;;
37 ;;; Why optimize? We want to avoid the fully-general TYPECASE in ordinary
38 ;;; SXHASH, because
39 ;;;   1. This hash function has to run when we're initializing the globaldb,
40 ;;;      so it has to run before the type system is initialized, and it's
41 ;;;      easier to make it do this if we don't try to do a general TYPECASE.
42 ;;;   2. This function is in a potential bottleneck for the compiler,
43 ;;;      and avoiding the general TYPECASE lets us improve performance
44 ;;;      because
45 ;;;     2a. the general TYPECASE is intrinsically slow, and
46 ;;;     2b. the general TYPECASE is too big for us to easily afford
47 ;;;         to inline it, so it brings with it a full function call.
48 ;;;
49 ;;; Why not specialize instead of optimize? (I.e. why fall through to
50 ;;; general SXHASH as a last resort?) Because the INFO database is used
51 ;;; to hold all manner of things, e.g. (INFO :TYPE :BUILTIN ..)
52 ;;; which is called on values like (UNSIGNED-BYTE 29). Falling through
53 ;;; to SXHASH lets us support all manner of things (as long as they
54 ;;; aren't used too early in cold boot for SXHASH to run).
55 #!-sb-fluid (declaim (inline globaldb-sxhashoid))
56 (defun globaldb-sxhashoid (x)
57   (logand sb!xc:most-positive-fixnum
58           (cond ((symbolp x) (sxhash x))
59                 ((and (listp x)
60                       (eq (first x) 'setf)
61                       (let ((rest (rest x)))
62                         (and (symbolp (car rest))
63                              (null (cdr rest)))))
64                  ;; We need to declare the type of the value we're feeding to
65                  ;; SXHASH so that the DEFTRANSFORM on symbols kicks in.
66                  (let ((symbol (second x)))
67                    (declare (symbol symbol))
68                    (logxor (sxhash symbol) 110680597)))
69                 (t (sxhash x)))))
70
71 ;;; Given any non-negative integer, return a prime number >= to it.
72 ;;;
73 ;;; FIXME: This logic should be shared with ALMOST-PRIMIFY in
74 ;;; hash-table.lisp. Perhaps the merged logic should be
75 ;;; PRIMIFY-HASH-TABLE-SIZE, implemented as a lookup table of primes
76 ;;; after integral powers of two:
77 ;;;    #(17 37 67 131 ..)
78 ;;; (Or, if that's too coarse, after half-integral powers of two.) By
79 ;;; thus getting rid of any need for primality testing at runtime, we
80 ;;; could punt POSITIVE-PRIMEP, too.
81 (defun primify (x)
82   (declare (type unsigned-byte x))
83   (do ((n (logior x 1) (+ n 2)))
84       ((positive-primep n) n)))
85 \f
86 ;;;; info classes, info types, and type numbers, part I: what's needed
87 ;;;; not only at compile time but also at run time
88
89 ;;;; Note: This section is a blast from the past, a little trip down
90 ;;;; memory lane to revisit the weird host/target interactions of the
91 ;;;; CMU CL build process. Because of the way that the cross-compiler
92 ;;;; and target compiler share stuff here, if you change anything in
93 ;;;; here, you'd be well-advised to nuke all your fasl files and
94 ;;;; restart compilation from the very beginning of the bootstrap
95 ;;;; process.
96
97 ;;; At run time, we represent the type of info that we want by a small
98 ;;; non-negative integer.
99 (eval-when (:compile-toplevel :load-toplevel :execute)
100   (def!constant type-number-bits 6))
101 (deftype type-number () `(unsigned-byte ,type-number-bits))
102
103 ;;; Why do we suppress the :COMPILE-TOPLEVEL situation here when we're
104 ;;; running the cross-compiler? The cross-compiler (which was built
105 ;;; from these sources) has its version of these data and functions
106 ;;; defined in the same places we'd be defining into. We're happy with
107 ;;; its version, since it was compiled from the same sources, so
108 ;;; there's no point in overwriting its nice compiled version of this
109 ;;; stuff with our interpreted version. (And any time we're *not*
110 ;;; happy with its version, perhaps because we've been editing the
111 ;;; sources partway through bootstrapping, tch tch, overwriting its
112 ;;; version with our version would be unlikely to help, because that
113 ;;; would make the cross-compiler very confused.)
114 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
115
116 (defstruct (class-info
117             (:constructor make-class-info (name))
118             #-no-ansi-print-object
119             (:print-object (lambda (x s)
120                              (print-unreadable-object (x s :type t)
121                                (prin1 (class-info-name x)))))
122             (:copier nil))
123   ;; name of this class
124   (name nil :type keyword :read-only t)
125   ;; list of Type-Info structures for each type in this class
126   (types () :type list))
127
128 ;;; a map from type numbers to TYPE-INFO objects. There is one type
129 ;;; number for each defined CLASS/TYPE pair.
130 ;;;
131 ;;; We build its value at build-the-cross-compiler time (with calls to
132 ;;; DEFINE-INFO-TYPE), then generate code to recreate the compile time
133 ;;; value, and arrange for that code to be called in cold load.
134 ;;; KLUDGE: We don't try to reset its value when cross-compiling the
135 ;;; compiler, since that creates too many bootstrapping problems,
136 ;;; instead just reusing the built-in-the-cross-compiler version,
137 ;;; which is theoretically a little bit ugly but pretty safe in
138 ;;; practice because the cross-compiler is as close to the target
139 ;;; compiler as we can make it, i.e. identical in most ways, including
140 ;;; this one. -- WHN 2001-08-19
141 (defvar *info-types*)
142 (declaim (type simple-vector *info-types*))
143 #-sb-xc ; as per KLUDGE note above
144 (eval-when (:compile-toplevel :execute)
145   (setf *info-types*
146         (make-array (ash 1 type-number-bits) :initial-element nil)))
147
148 (defstruct (type-info
149             #-no-ansi-print-object
150             (:print-object (lambda (x s)
151                              (print-unreadable-object (x s)
152                                (format s
153                                        "~S ~S, Number = ~W"
154                                        (class-info-name (type-info-class x))
155                                        (type-info-name x)
156                                        (type-info-number x)))))
157             (:copier nil))
158   ;; the name of this type
159   (name (missing-arg) :type keyword)
160   ;; this type's class
161   (class (missing-arg) :type class-info)
162   ;; a number that uniquely identifies this type (and implicitly its class)
163   (number (missing-arg) :type type-number)
164   ;; a type specifier which info of this type must satisfy
165   (type nil :type t)  
166   ;; a function called when there is no information of this type
167   (default (lambda () (error "type not defined yet")) :type function)
168   ;; called by (SETF INFO) before calling SET-INFO-VALUE
169   (validate-function nil :type (or function null)))
170
171 ;;; a map from class names to CLASS-INFO structures
172 ;;;
173 ;;; We build the value for this at compile time (with calls to
174 ;;; DEFINE-INFO-CLASS), then generate code to recreate the compile time
175 ;;; value, and arrange for that code to be called in cold load.
176 ;;; KLUDGE: Just as for *INFO-TYPES*, we don't try to rebuild this
177 ;;; when cross-compiling, but instead just reuse the cross-compiler's
178 ;;; version for the target compiler. -- WHN 2001-08-19
179 (defvar *info-classes*)
180 (declaim (hash-table *info-classes*))
181 #-sb-xc ; as per KLUDGE note above
182 (eval-when (:compile-toplevel :execute)
183   (setf *info-classes* (make-hash-table)))
184
185 ;;; If NAME is the name of a type in CLASS, then return the TYPE-INFO,
186 ;;; otherwise NIL.
187 (defun find-type-info (name class)
188   (declare (type keyword name) (type class-info class))
189   (dolist (type (class-info-types class) nil)
190     (when (eq (type-info-name type) name)
191       (return type))))
192
193 ;;; Return the info structure for an info class or type, or die trying.
194 (declaim (ftype (function (keyword) class-info) class-info-or-lose))
195 (defun class-info-or-lose (class)
196   (declare (type keyword class))
197   #+sb-xc (/noshow0 "entering CLASS-INFO-OR-LOSE, CLASS=..")
198   #+sb-xc (/nohexstr class)
199   (prog1
200       (or (gethash class *info-classes*)
201           (error "~S is not a defined info class." class))
202     #+sb-xc (/noshow0 "returning from CLASS-INFO-OR-LOSE")))
203 (declaim (ftype (function (keyword keyword) type-info) type-info-or-lose))
204 (defun type-info-or-lose (class type)
205   #+sb-xc (/noshow0 "entering TYPE-INFO-OR-LOSE, CLASS,TYPE=..")
206   #+sb-xc (/nohexstr class)
207   #+sb-xc (/nohexstr type)
208   (prog1
209       (or (find-type-info type (class-info-or-lose class))
210           (error "~S is not a defined info type." type))
211     #+sb-xc (/noshow0 "returning from TYPE-INFO-OR-LOSE")))
212
213 ) ; EVAL-WHEN
214 \f
215 ;;;; info classes, info types, and type numbers, part II: what's
216 ;;;; needed only at compile time, not at run time
217
218 ;;; FIXME: Perhaps this stuff (the definition of DEFINE-INFO-CLASS
219 ;;; and the calls to it) could/should go in a separate file,
220 ;;; perhaps info-classes.lisp?
221
222 (eval-when (:compile-toplevel :execute)
223
224 ;;; Set up the data structures to support an info class.
225 ;;;
226 ;;; comment from CMU CL:
227 ;;;   We make sure that the class exists at compile time so that
228 ;;;   macros can use it, but we don't actually store the init function
229 ;;;   until load time so that we don't break the running compiler.
230 ;;; KLUDGE: I don't think that's the way it is any more, but I haven't
231 ;;; looked into it enough to write a better comment. -- WHN 2001-03-06
232 (#+sb-xc-host defmacro
233  #-sb-xc-host sb!xc:defmacro
234      define-info-class (class)
235   (declare (type keyword class))
236   `(progn
237      ;; (We don't need to evaluate this at load time, compile time is
238      ;; enough. There's special logic elsewhere which deals with cold
239      ;; load initialization by inspecting the info class data
240      ;; structures at compile time and generating code to recreate
241      ;; those data structures.)
242      (eval-when (:compile-toplevel :execute)
243        (unless (gethash ,class *info-classes*)
244          (setf (gethash ,class *info-classes*) (make-class-info ,class))))
245      ,class))
246
247 ;;; Find a type number not already in use by looking for a null entry
248 ;;; in *INFO-TYPES*.
249 (defun find-unused-type-number ()
250   (or (position nil *info-types*)
251       (error "no more INFO type numbers available")))
252
253 ;;; a list of forms for initializing the DEFAULT slots of TYPE-INFO
254 ;;; objects, accumulated during compilation and eventually converted
255 ;;; into a function to be called at cold load time after the
256 ;;; appropriate TYPE-INFO objects have been created
257 ;;;
258 ;;; Note: This is quite similar to the !COLD-INIT-FORMS machinery, but
259 ;;; we can't conveniently use the ordinary !COLD-INIT-FORMS machinery
260 ;;; here. The problem is that the natural order in which the
261 ;;; default-slot-initialization forms are generated relative to the
262 ;;; order in which the TYPE-INFO-creation forms are generated doesn't
263 ;;; match the relative order in which the forms need to be executed at
264 ;;; cold load time.
265 (defparameter *!reversed-type-info-init-forms* nil)
266
267 ;;; Define a new type of global information for CLASS. TYPE is the
268 ;;; name of the type, DEFAULT is the value for that type when it
269 ;;; hasn't been set, and TYPE-SPEC is a type specifier which values of
270 ;;; the type must satisfy. The default expression is evaluated each
271 ;;; time the information is needed, with NAME bound to the name for
272 ;;; which the information is being looked up. 
273 ;;;
274 ;;; The main thing we do is determine the type's number. We need to do
275 ;;; this at macroexpansion time, since both the COMPILE and LOAD time
276 ;;; calls to %DEFINE-INFO-TYPE must use the same type number.
277 (#+sb-xc-host defmacro
278  #-sb-xc-host sb!xc:defmacro
279     define-info-type (&key (class (missing-arg))
280                            (type (missing-arg))
281                            (type-spec (missing-arg))
282                            (validate-function)
283                            default)
284   (declare (type keyword class type))
285   `(progn
286      (eval-when (:compile-toplevel :execute)
287        ;; At compile time, ensure that the type number exists. It will
288        ;; need to be forced to exist at cold load time, too, but
289        ;; that's not handled here; it's handled by later code which
290        ;; looks at the compile time state and generates code to
291        ;; replicate it at cold load time.
292        (let* ((class-info (class-info-or-lose ',class))
293               (old-type-info (find-type-info ',type class-info)))
294          (unless old-type-info
295            (let* ((new-type-number (find-unused-type-number))
296                   (new-type-info
297                    (make-type-info :name ',type
298                                    :class class-info
299                                    :number new-type-number)))
300              (setf (aref *info-types* new-type-number) new-type-info)
301              (push new-type-info (class-info-types class-info)))))
302        ;; Arrange for TYPE-INFO-DEFAULT and TYPE-INFO-TYPE to be set
303        ;; at cold load time. (They can't very well be set at
304        ;; cross-compile time, since they differ between the
305        ;; cross-compiler and the target. The DEFAULT slot values
306        ;; differ because they're compiled closures, and the TYPE slot
307        ;; values differ in the use of SB!XC symbols instead of CL
308        ;; symbols.)
309        (push `(let ((type-info (type-info-or-lose ,',class ,',type)))
310                 (setf (type-info-validate-function type-info)
311                       ,',validate-function)
312                 (setf (type-info-default type-info)
313                        ;; FIXME: This code is sort of nasty. It would
314                        ;; be cleaner if DEFAULT accepted a real
315                        ;; function, instead of accepting a statement
316                        ;; which will be turned into a lambda assuming
317                        ;; that the argument name is NAME. It might
318                        ;; even be more microefficient, too, since many
319                        ;; DEFAULTs could be implemented as (CONSTANTLY
320                        ;; NIL) instead of full-blown (LAMBDA (X) NIL).
321                        (lambda (name)
322                          (declare (ignorable name))
323                          ,',default))
324                 (setf (type-info-type type-info) ',',type-spec))
325              *!reversed-type-info-init-forms*))
326      ',type))
327
328 ) ; EVAL-WHEN
329 \f
330 ;;;; generic info environments
331
332 ;;; Note: the CACHE-NAME slot is deliberately not shared for
333 ;;; bootstrapping reasons. If we access with accessors for the exact
334 ;;; type, then the inline type check will win. If the inline check
335 ;;; didn't win, we would try to use the type system before it was
336 ;;; properly initialized.
337 (defstruct (info-env (:constructor nil)
338                      (:copier nil))
339   ;; some string describing what is in this environment, for
340   ;; printing/debugging purposes only
341   (name (missing-arg) :type string))
342 (def!method print-object ((x info-env) stream)
343   (print-unreadable-object (x stream :type t)
344     (prin1 (info-env-name x) stream)))
345 \f
346 ;;;; generic interfaces
347
348 ;;; FIXME: used only in this file, needn't be in runtime
349 (defmacro do-info ((env &key (name (gensym)) (class (gensym)) (type (gensym))
350                         (type-number (gensym)) (value (gensym)) known-volatile)
351                    &body body)
352   #!+sb-doc
353   "DO-INFO (Env &Key Name Class Type Value) Form*
354   Iterate over all the values stored in the Info-Env Env. Name is bound to
355   the entry's name, Class and Type are bound to the class and type
356   (represented as keywords), and Value is bound to the entry's value."
357   (once-only ((n-env env))
358     (if known-volatile
359         (do-volatile-info name class type type-number value n-env body)
360         `(if (typep ,n-env 'volatile-info-env)
361              ,(do-volatile-info name class type type-number value n-env body)
362              ,(do-compact-info name class type type-number value
363                                n-env body)))))
364
365 (eval-when (#-sb-xc :compile-toplevel :load-toplevel :execute)
366
367 ;;; Return code to iterate over a compact info environment.
368 (defun do-compact-info (name-var class-var type-var type-number-var value-var
369                                  n-env body)
370   (let ((n-index (gensym))
371         (n-type (gensym))
372         (punt (gensym)))
373     (once-only ((n-table `(compact-info-env-table ,n-env))
374                 (n-entries-index `(compact-info-env-index ,n-env))
375                 (n-entries `(compact-info-env-entries ,n-env))
376                 (n-entries-info `(compact-info-env-entries-info ,n-env))
377                 (n-info-types '*info-types*))
378       `(dotimes (,n-index (length ,n-table))
379          (declare (type index ,n-index))
380          (block ,punt
381            (let ((,name-var (svref ,n-table ,n-index)))
382              (unless (eql ,name-var 0)
383                (do-anonymous ((,n-type (aref ,n-entries-index ,n-index)
384                                        (1+ ,n-type)))
385                              (nil)
386                  (declare (type index ,n-type))
387                  ,(once-only ((n-info `(aref ,n-entries-info ,n-type)))
388                     `(let ((,type-number-var
389                             (logand ,n-info compact-info-entry-type-mask)))
390                        ,(once-only ((n-type-info
391                                      `(svref ,n-info-types
392                                              ,type-number-var)))
393                           `(let ((,type-var (type-info-name ,n-type-info))
394                                  (,class-var (class-info-name
395                                               (type-info-class ,n-type-info)))
396                                  (,value-var (svref ,n-entries ,n-type)))
397                              (declare (ignorable ,type-var ,class-var
398                                                  ,value-var))
399                              ,@body
400                              (unless (zerop (logand ,n-info
401                                                     compact-info-entry-last))
402                                (return-from ,punt))))))))))))))
403
404 ;;; Return code to iterate over a volatile info environment.
405 (defun do-volatile-info (name-var class-var type-var type-number-var value-var
406                                   n-env body)
407   (let ((n-index (gensym)) (n-names (gensym)) (n-types (gensym)))
408     (once-only ((n-table `(volatile-info-env-table ,n-env))
409                 (n-info-types '*info-types*))
410       `(dotimes (,n-index (length ,n-table))
411          (declare (type index ,n-index))
412          (do-anonymous ((,n-names (svref ,n-table ,n-index)
413                                   (cdr ,n-names)))
414                        ((null ,n-names))
415            (let ((,name-var (caar ,n-names)))
416              (declare (ignorable ,name-var))
417              (do-anonymous ((,n-types (cdar ,n-names) (cdr ,n-types)))
418                            ((null ,n-types))
419                (let ((,type-number-var (caar ,n-types)))
420                  ,(once-only ((n-type `(svref ,n-info-types
421                                               ,type-number-var)))
422                     `(let ((,type-var (type-info-name ,n-type))
423                            (,class-var (class-info-name
424                                         (type-info-class ,n-type)))
425                            (,value-var (cdar ,n-types)))
426                        (declare (ignorable ,type-var ,class-var ,value-var))
427                        ,@body))))))))))
428
429 ) ; EVAL-WHEN
430 \f
431 ;;;; INFO cache
432
433 ;;;; We use a hash cache to cache name X type => value for the current
434 ;;;; value of *INFO-ENVIRONMENT*. This is in addition to the
435 ;;;; per-environment caching of name => types.
436
437 ;;; The value of *INFO-ENVIRONMENT* that has cached values.
438 ;;; *INFO-ENVIRONMENT* should never be destructively modified, so if
439 ;;; it is EQ to this, then the cache is valid.
440 (defvar *cached-info-environment*)
441 (!cold-init-forms
442   (setf *cached-info-environment* nil))
443
444 ;;; the hash function used for the INFO cache
445 #!-sb-fluid (declaim (inline info-cache-hash))
446 (defun info-cache-hash (name type)
447   (logand
448     (the fixnum
449          (logxor (globaldb-sxhashoid name)
450                  (ash (the fixnum type) 7)))
451     #x3FF))
452
453 (!cold-init-forms
454   (/show0 "before initialization of INFO hash cache"))
455 (define-hash-cache info ((name eq) (type eq))
456   :values 2
457   :hash-function info-cache-hash
458   :hash-bits 10
459   :default (values nil :empty)
460   :init-wrapper !cold-init-forms)
461 (!cold-init-forms
462   (/show0 "clearing INFO hash cache")
463   (info-cache-clear)
464   (/show0 "done clearing INFO hash cache"))
465
466 ;;; If the info cache is invalid, then clear it.
467 #!-sb-fluid (declaim (inline clear-invalid-info-cache))
468 (defun clear-invalid-info-cache ()
469   ;; Unless the cache is valid..
470   (unless (eq *info-environment* *cached-info-environment*)
471     (;; In the target Lisp, this should be done without interrupts,
472      ;; but in the host Lisp when cross-compiling, we don't need to
473      ;; sweat it, since no affected-by-GC hashes should be used when
474      ;; running under the host Lisp (since that's non-portable) and
475      ;; since only one thread should be used when running under the
476      ;; host Lisp (because multiple threads are non-portable too).
477      #-sb-xc-host without-interrupts
478      #+sb-xc-host progn
479       (info-cache-clear)
480       (setq *cached-info-environment* *info-environment*))))
481 \f
482 ;;;; compact info environments
483
484 ;;; The upper limit on the size of the ENTRIES vector in a COMPACT-INFO-ENV.
485 ;;; 
486 ;;; "Why (U-B 28)?", you might wonder. Originally this was (U-B 16),
487 ;;; presumably to ensure that the arrays of :ELEMENT-TYPE 
488 ;;; COMPACT-INFO-ENTRIES-INDEX could use a more space-efficient representation.
489 ;;; It turns out that a environment of of only 65536 entries is insufficient in
490 ;;; the modern world (see message from Cyrus Harmon to sbcl-devel, "Subject:
491 ;;; purify failure when compact-info-env-entries-bits is too small"). Using
492 ;;; (U-B 28) instead of (U-B 29) is to avoid the need for bignum overflow 
493 ;;; checks, a probably pointless micro-optimization. Hardcoding the amount of
494 ;;; bits instead of deriving it from SB!VM::N-WORD-BITS is done to allow
495 ;;; use of a more efficient array representation on 64-bit platforms.
496 ;;;   -- JES, 2005-04-06
497 (def!constant compact-info-env-entries-bits 28)
498 (deftype compact-info-entries-index () `(unsigned-byte ,compact-info-env-entries-bits))
499
500 ;;; the type of the values in COMPACT-INFO-ENTRIES-INFO
501 (deftype compact-info-entry () `(unsigned-byte ,(1+ type-number-bits)))
502
503 ;;; This is an open hashtable with rehashing. Since modification is
504 ;;; not allowed, we don't have to worry about deleted entries. We
505 ;;; indirect through a parallel vector to find the index in the
506 ;;; ENTRIES at which the entries for a given name starts.
507 (defstruct (compact-info-env (:include info-env)
508                              #-sb-xc-host (:pure :substructure)
509                              (:copier nil))
510   ;; If this value is EQ to the name we want to look up, then the
511   ;; cache hit function can be called instead of the lookup function.
512   (cache-name 0)
513   ;; The index in ENTRIES for the CACHE-NAME, or NIL if that name has
514   ;; no entries.
515   (cache-index nil :type (or compact-info-entries-index null))
516   ;; hashtable of the names in this environment. If a bucket is
517   ;; unused, it is 0.
518   (table (missing-arg) :type simple-vector)
519   ;; an indirection vector parallel to TABLE, translating indices in
520   ;; TABLE to the start of the ENTRIES for that name. Unused entries
521   ;; are undefined.
522   (index (missing-arg) :type (simple-array compact-info-entries-index (*)))
523   ;; a vector contining in contiguous ranges the values of for all the
524   ;; types of info for each name.
525   (entries (missing-arg) :type simple-vector)
526   ;; a vector parallel to ENTRIES, indicating the type number for the
527   ;; value stored in that location and whether this location is the
528   ;; last type of info stored for this name. The type number is in the
529   ;; low TYPE-NUMBER-BITS bits, and the next bit is set if this is the
530   ;; last entry.
531   (entries-info (missing-arg) :type (simple-array compact-info-entry (*))))
532
533 (def!constant compact-info-entry-type-mask (ldb (byte type-number-bits 0) -1))
534 (def!constant compact-info-entry-last (ash 1 type-number-bits))
535
536 ;;; Return the value of the type corresponding to NUMBER for the
537 ;;; currently cached name in ENV.
538 #!-sb-fluid (declaim (inline compact-info-cache-hit))
539 (defun compact-info-cache-hit (env number)
540   (declare (type compact-info-env env) (type type-number number))
541   (let ((entries-info (compact-info-env-entries-info env))
542         (index (compact-info-env-cache-index env)))
543     (if index
544         (do ((index index (1+ index)))
545             (nil)
546           (declare (type index index))
547           (let ((info (aref entries-info index)))
548             (when (= (logand info compact-info-entry-type-mask) number)
549               (return (values (svref (compact-info-env-entries env) index)
550                               t)))
551             (unless (zerop (logand compact-info-entry-last info))
552               (return (values nil nil)))))
553         (values nil nil))))
554
555 ;;; Encache NAME in the compact environment ENV. HASH is the
556 ;;; GLOBALDB-SXHASHOID of NAME.
557 (defun compact-info-lookup (env name hash)
558   (declare (type compact-info-env env)
559            (type (integer 0 #.sb!xc:most-positive-fixnum) hash))
560   (let* ((table (compact-info-env-table env))
561          (len (length table))
562          (len-2 (- len 2))
563          (hash2 (- len-2 (rem hash len-2))))
564     (declare (type index len-2 hash2))
565     (macrolet ((lookup (test)
566                  `(do ((probe (rem hash len)
567                               (let ((new (+ probe hash2)))
568                                 (declare (type index new))
569                                 ;; same as (MOD NEW LEN), but faster.
570                                 (if (>= new len)
571                                     (the index (- new len))
572                                     new))))
573                       (nil)
574                     (let ((entry (svref table probe)))
575                       (when (eql entry 0)
576                         (return nil))
577                       (when (,test entry name)
578                         (return (aref (compact-info-env-index env)
579                                       probe)))))))
580       (setf (compact-info-env-cache-index env)
581             (if (symbolp name)
582                 (lookup eq)
583                 (lookup equal)))
584       (setf (compact-info-env-cache-name env) name)))
585
586   (values))
587
588 ;;; the exact density (modulo rounding) of the hashtable in a compact
589 ;;; info environment in names/bucket
590 (def!constant compact-info-environment-density 65)
591
592 ;;; Return a new compact info environment that holds the same
593 ;;; information as ENV.
594 (defun compact-info-environment (env &key (name (info-env-name env)))
595   (let ((name-count 0)
596         (prev-name 0)
597         (entry-count 0))
598     (/show0 "before COLLECT in COMPACT-INFO-ENVIRONMENT")
599
600     ;; Iterate over the environment once to find out how many names
601     ;; and entries it has, then build the result. This code assumes
602     ;; that all the entries for a name well be iterated over
603     ;; contiguously, which holds true for the implementation of
604     ;; iteration over both kinds of environments.
605     (collect ((names))
606
607       (/show0 "at head of COLLECT in COMPACT-INFO-ENVIRONMENT")
608       (let ((types ()))
609         (do-info (env :name name :type-number num :value value)
610           (/noshow0 "at head of DO-INFO in COMPACT-INFO-ENVIRONMENT")
611           (unless (eq name prev-name)
612             (/noshow0 "not (EQ NAME PREV-NAME) case")
613             (incf name-count)
614             (unless (eql prev-name 0)
615               (names (cons prev-name types)))
616             (setq prev-name name)
617             (setq types ()))
618           (incf entry-count)
619           (push (cons num value) types))
620         (unless (eql prev-name 0)
621           (/show0 "not (EQL PREV-NAME 0) case")
622           (names (cons prev-name types))))
623
624       ;; Now that we know how big the environment is, we can build
625       ;; a table to represent it.
626       ;; 
627       ;; When building the table, we sort the entries by pointer
628       ;; comparison in an attempt to preserve any VM locality present
629       ;; in the original load order, rather than randomizing with the
630       ;; original hash function.
631       (/show0 "about to make/sort vectors in COMPACT-INFO-ENVIRONMENT")
632       (let* ((table-size (primify
633                           (+ (truncate (* name-count 100)
634                                        compact-info-environment-density)
635                              3)))
636              (table (make-array table-size :initial-element 0))
637              (index (make-array table-size
638                                 :element-type 'compact-info-entries-index))
639              (entries (make-array entry-count))
640              (entries-info (make-array entry-count
641                                        :element-type 'compact-info-entry))
642              (sorted (sort (names)
643                            #+sb-xc-host #'<
644                            ;; (This MAKE-FIXNUM hack implements
645                            ;; pointer comparison, as explained above.)
646                            #-sb-xc-host (lambda (x y)
647                                           (< (%primitive make-fixnum x)
648                                              (%primitive make-fixnum y))))))
649         (/show0 "done making/sorting vectors in COMPACT-INFO-ENVIRONMENT")
650         (let ((entries-idx 0))
651           (dolist (types sorted)
652             (let* ((name (first types))
653                    (hash (globaldb-sxhashoid name))
654                    (len-2 (- table-size 2))
655                    (hash2 (- len-2 (rem hash len-2))))
656               (do ((probe (rem hash table-size)
657                           (rem (+ probe hash2) table-size)))
658                   (nil)
659                 (let ((entry (svref table probe)))
660                   (when (eql entry 0)
661                     (setf (svref table probe) name)
662                     (setf (aref index probe) entries-idx)
663                     (return))
664                   (aver (not (equal entry name))))))
665
666             (unless (zerop entries-idx)
667               (setf (aref entries-info (1- entries-idx))
668                     (logior (aref entries-info (1- entries-idx))
669                             compact-info-entry-last)))
670
671             (loop for (num . value) in (rest types) do
672               (setf (aref entries-info entries-idx) num)
673               (setf (aref entries entries-idx) value)
674               (incf entries-idx)))
675           (/show0 "done w/ DOLIST (TYPES SORTED) in COMPACT-INFO-ENVIRONMENT")
676
677           (unless (zerop entry-count)
678             (/show0 "nonZEROP ENTRY-COUNT")
679             (setf (aref entries-info (1- entry-count))
680                   (logior (aref entries-info (1- entry-count))
681                           compact-info-entry-last)))
682
683           (/show0 "falling through to MAKE-COMPACT-INFO-ENV")
684           (make-compact-info-env :name name
685                                  :table table
686                                  :index index
687                                  :entries entries
688                                  :entries-info entries-info))))))
689 \f
690 ;;;; volatile environments
691
692 ;;; This is a closed hashtable, with the bucket being computed by
693 ;;; taking the GLOBALDB-SXHASHOID of the NAME modulo the table size.
694 (defstruct (volatile-info-env (:include info-env)
695                               (:copier nil))
696   ;; If this value is EQ to the name we want to look up, then the
697   ;; cache hit function can be called instead of the lookup function.
698   (cache-name 0)
699   ;; the alist translating type numbers to values for the currently
700   ;; cached name
701   (cache-types nil :type list)
702   ;; vector of alists of alists of the form:
703   ;;    ((Name . ((Type-Number . Value) ...) ...)
704   (table (missing-arg) :type simple-vector)
705   ;; the number of distinct names currently in this table. Each name
706   ;; may have multiple entries, since there can be many types of info.
707   (count 0 :type index)
708   ;; the number of names at which we should grow the table and rehash
709   (threshold 0 :type index))
710
711 ;;; Just like COMPACT-INFO-CACHE-HIT, only do it on a volatile environment.
712 #!-sb-fluid (declaim (inline volatile-info-cache-hit))
713 (defun volatile-info-cache-hit (env number)
714   (declare (type volatile-info-env env) (type type-number number))
715   (dolist (type (volatile-info-env-cache-types env) (values nil nil))
716     (when (eql (car type) number)
717       (return (values (cdr type) t)))))
718
719 ;;; Just like COMPACT-INFO-LOOKUP, only do it on a volatile environment.
720 (defun volatile-info-lookup (env name hash)
721   (declare (type volatile-info-env env)
722            (type (integer 0 #.sb!xc:most-positive-fixnum) hash))
723   (let ((table (volatile-info-env-table env)))
724     (macrolet ((lookup (test)
725                  `(dolist (entry (svref table (mod hash (length table))) ())
726                     (when (,test (car entry) name)
727                       (return (cdr entry))))))
728       (setf (volatile-info-env-cache-types env)
729             (if (symbolp name)
730                 (lookup eq)
731                 (lookup equal)))
732       (setf (volatile-info-env-cache-name env) name)))
733   (values))
734
735 ;;; Given a volatile environment ENV, bind TABLE-VAR the environment's table
736 ;;; and INDEX-VAR to the index of NAME's bucket in the table. We also flush
737 ;;; the cache so that things will be consistent if body modifies something.
738 (eval-when (:compile-toplevel :execute)
739   (#+sb-xc-host cl:defmacro
740    #-sb-xc-host sb!xc:defmacro
741       with-info-bucket ((table-var index-var name env) &body body)
742     (once-only ((n-name name)
743                 (n-env env))
744       `(progn
745          (setf (volatile-info-env-cache-name ,n-env) 0)
746          (let* ((,table-var (volatile-info-env-table ,n-env))
747                 (,index-var (mod (globaldb-sxhashoid ,n-name)
748                                  (length ,table-var))))
749            ,@body)))))
750
751 ;;; Get the info environment that we use for write/modification operations.
752 ;;; This is always the first environment in the list, and must be a
753 ;;; VOLATILE-INFO-ENV.
754 #!-sb-fluid (declaim (inline get-write-info-env))
755 (defun get-write-info-env (&optional (env-list *info-environment*))
756   (let ((env (car env-list)))
757     (unless env
758       (error "no info environment?"))
759     (unless (typep env 'volatile-info-env)
760       (error "cannot modify this environment: ~S" env))
761     (the volatile-info-env env)))
762
763 ;;; If Name is already present in the table, then just create or
764 ;;; modify the specified type. Otherwise, add the new name and type,
765 ;;; checking for rehashing.
766 ;;;
767 ;;; We rehash by making a new larger environment, copying all of the
768 ;;; entries into it, then clobbering the old environment with the new
769 ;;; environment's table. We clear the old table to prevent it from
770 ;;; holding onto garbage if it is statically allocated.
771 ;;;
772 ;;; We return the new value so that this can be conveniently used in a
773 ;;; SETF function.
774 (defun set-info-value (name0 type new-value
775                              &optional (env (get-write-info-env)))
776   (declare (type type-number type) (type volatile-info-env env)
777            (inline assoc))
778   (let ((name (uncross name0)))
779     (when (eql name 0)
780       (error "0 is not a legal INFO name."))
781     ;; We don't enter the value in the cache because we don't know that this
782     ;; info-environment is part of *cached-info-environment*.
783     (info-cache-enter name type nil :empty)
784     (with-info-bucket (table index name env)
785       (let ((types (if (symbolp name)
786                        (assoc name (svref table index) :test #'eq)
787                        (assoc name (svref table index) :test #'equal))))
788         (cond
789          (types
790           (let ((value (assoc type (cdr types))))
791             (if value
792                 (setf (cdr value) new-value)
793                 (push (cons type new-value) (cdr types)))))
794          (t
795           (push (cons name (list (cons type new-value)))
796                 (svref table index))
797
798           (let ((count (incf (volatile-info-env-count env))))
799             (when (>= count (volatile-info-env-threshold env))
800               (let ((new (make-info-environment :size (* count 2))))
801                 (do-info (env :name entry-name :type-number entry-num
802                               :value entry-val :known-volatile t)
803                          (set-info-value entry-name entry-num entry-val new))
804                 (fill (volatile-info-env-table env) nil)
805                 (setf (volatile-info-env-table env)
806                       (volatile-info-env-table new))
807                 (setf (volatile-info-env-threshold env)
808                       (volatile-info-env-threshold new)))))))))
809     new-value))
810
811 ;;; FIXME: It should be possible to eliminate the hairy compiler macros below
812 ;;; by declaring INFO and (SETF INFO) inline and making a simple compiler macro
813 ;;; for TYPE-INFO-OR-LOSE. (If we didn't worry about efficiency of the
814 ;;; cross-compiler, we could even do it by just making TYPE-INFO-OR-LOSE
815 ;;; foldable.)
816
817 ;;; INFO is the standard way to access the database. It's settable.
818 ;;;
819 ;;; Return the information of the specified TYPE and CLASS for NAME.
820 ;;; The second value returned is true if there is any such information
821 ;;; recorded. If there is no information, the first value returned is
822 ;;; the default and the second value returned is NIL.
823 (defun info (class type name &optional (env-list nil env-list-p))
824   ;; FIXME: At some point check systematically to make sure that the
825   ;; system doesn't do any full calls to INFO or (SETF INFO), or at
826   ;; least none in any inner loops.
827   (let ((info (type-info-or-lose class type)))
828     (if env-list-p
829         (get-info-value name (type-info-number info) env-list)
830         (get-info-value name (type-info-number info)))))
831 #!-sb-fluid
832 (define-compiler-macro info
833   (&whole whole class type name &optional (env-list nil env-list-p))
834   ;; Constant CLASS and TYPE is an overwhelmingly common special case,
835   ;; and we can implement it much more efficiently than the general case.
836   (if (and (constantp class) (constantp type))
837       (let ((info (type-info-or-lose class type)))
838         (with-unique-names (value foundp)
839           `(multiple-value-bind (,value ,foundp)
840                (get-info-value ,name
841                                ,(type-info-number info)
842                                ,@(when env-list-p `(,env-list))) 
843              (declare (type ,(type-info-type info) ,value))
844              (values ,value ,foundp))))
845       whole))
846 (defun (setf info) (new-value
847                     class
848                     type
849                     name
850                     &optional (env-list nil env-list-p))
851   (let* ((info (type-info-or-lose class type))
852          (tin (type-info-number info)))
853     (when (type-info-validate-function info)
854       (funcall (type-info-validate-function info) name new-value))
855     (if env-list-p
856         (set-info-value name
857                         tin
858                         new-value
859                         (get-write-info-env env-list))
860         (set-info-value name
861                         tin
862                         new-value)))
863   new-value)
864 ;;; FIXME: We'd like to do this, but Python doesn't support
865 ;;; compiler macros and it's hard to change it so that it does.
866 ;;; It might make more sense to just convert INFO :FOO :BAR into
867 ;;; an ordinary function, so that instead of calling INFO :FOO :BAR
868 ;;; you call e.g. INFO%FOO%BAR. Then dynamic linking could be handled
869 ;;; by the ordinary Lisp mechanisms and we wouldn't have to maintain
870 ;;; all this cruft..
871 #|
872 #!-sb-fluid
873 (progn
874   (define-compiler-macro (setf info) (&whole whole
875                                       new-value
876                                       class
877                                       type
878                                       name
879                                       &optional (env-list nil env-list-p))
880     ;; Constant CLASS and TYPE is an overwhelmingly common special case, and we
881     ;; can resolve it much more efficiently than the general case.
882     (if (and (constantp class) (constantp type))
883         (let* ((info (type-info-or-lose class type))
884                (tin (type-info-number info)))
885           (if env-list-p
886               `(set-info-value ,name
887                                ,tin
888                                ,new-value
889                                (get-write-info-env ,env-list))
890               `(set-info-value ,name
891                                ,tin
892                                ,new-value)))
893         whole)))
894 |#
895
896 ;;; the maximum density of the hashtable in a volatile env (in
897 ;;; names/bucket)
898 ;;;
899 ;;; FIXME: actually seems to be measured in percent, should be
900 ;;; converted to be measured in names/bucket
901 (def!constant volatile-info-environment-density 50)
902
903 ;;; Make a new volatile environment of the specified size.
904 (defun make-info-environment (&key (size 42) (name "Unknown"))
905   (declare (type (integer 1) size))
906   (let ((table-size (primify (truncate (* size 100)
907                                        volatile-info-environment-density))))
908     (make-volatile-info-env :name name
909                             :table (make-array table-size :initial-element nil)
910                             :threshold size)))
911
912 ;;; Clear the information of the specified TYPE and CLASS for NAME in
913 ;;; the current environment, allowing any inherited info to become
914 ;;; visible. We return true if there was any info.
915 (defun clear-info (class type name)
916   (let ((info (type-info-or-lose class type)))
917     (clear-info-value name (type-info-number info))))
918 #!-sb-fluid
919 (define-compiler-macro clear-info (&whole whole class type name)
920   ;; Constant CLASS and TYPE is an overwhelmingly common special case, and
921   ;; we can resolve it much more efficiently than the general case.
922   (if (and (keywordp class) (keywordp type))
923     (let ((info (type-info-or-lose class type)))
924       `(clear-info-value ,name ,(type-info-number info)))
925     whole))
926 (defun clear-info-value (name type)
927   (declare (type type-number type) (inline assoc))
928   (clear-invalid-info-cache)
929   (info-cache-enter name type nil :empty)
930   (with-info-bucket (table index name (get-write-info-env))
931     (let ((types (assoc name (svref table index) :test #'equal)))
932       (when (and types
933                  (assoc type (cdr types)))
934         (setf (cdr types)
935               (delete type (cdr types) :key #'car))
936         t))))
937 \f
938 ;;;; *INFO-ENVIRONMENT*
939
940 ;;; We do info access relative to the current *INFO-ENVIRONMENT*, a
941 ;;; list of INFO-ENVIRONMENT structures.
942 (defvar *info-environment*)
943 (declaim (type list *info-environment*))
944 (!cold-init-forms
945   (setq *info-environment*
946         (list (make-info-environment :name "initial global")))
947   (/show0 "done setting *INFO-ENVIRONMENT*"))
948 ;;; FIXME: should perhaps be *INFO-ENV-LIST*. And rename
949 ;;; all FOO-INFO-ENVIRONMENT-BAR stuff to FOO-INFO-ENV-BAR.
950 \f
951 ;;;; GET-INFO-VALUE
952
953 ;;; Check whether the name and type is in our cache, if so return it.
954 ;;; Otherwise, search for the value and encache it.
955 ;;;
956 ;;; Return the value from the first environment which has it defined,
957 ;;; or return the default if none does. We have a cache for the last
958 ;;; name looked up in each environment. We don't compute the hash
959 ;;; until the first time the cache misses. When the cache does miss,
960 ;;; we invalidate it before calling the lookup routine to eliminate
961 ;;; the possibility of the cache being partially updated if the lookup
962 ;;; is interrupted.
963 (defun get-info-value (name0 type &optional (env-list nil env-list-p))
964   (declare (type type-number type))
965   ;; sanity check: If we have screwed up initialization somehow, then
966   ;; *INFO-TYPES* could still be uninitialized at the time we try to
967   ;; get an info value, and then we'd be out of luck. (This happened,
968   ;; and was confusing to debug, when rewriting EVAL-WHEN in
969   ;; sbcl-0.pre7.x.)
970   (aver (aref *info-types* type))
971   (let ((name (uncross name0)))
972     (flet ((lookup-ignoring-global-cache (env-list)
973              (let ((hash nil))
974                (dolist (env env-list
975                             (multiple-value-bind (val winp)
976                                 (funcall (type-info-default
977                                           (svref *info-types* type))
978                                          name)
979                               (values val winp)))
980                  (macrolet ((frob (lookup cache slot)
981                               `(progn
982                                  (unless (eq name (,slot env))
983                                    (unless hash
984                                      (setq hash (globaldb-sxhashoid name)))
985                                    (setf (,slot env) 0)
986                                    (,lookup env name hash))
987                                  (multiple-value-bind (value winp)
988                                      (,cache env type)
989                                    (when winp (return (values value t)))))))
990                    (etypecase env
991                      (volatile-info-env (frob
992                                          volatile-info-lookup
993                                          volatile-info-cache-hit
994                                          volatile-info-env-cache-name))
995                      (compact-info-env (frob
996                                         compact-info-lookup
997                                         compact-info-cache-hit
998                                         compact-info-env-cache-name))))))))
999       (cond (env-list-p
1000              (lookup-ignoring-global-cache env-list))
1001             (t
1002              (clear-invalid-info-cache)
1003              (multiple-value-bind (val winp) (info-cache-lookup name type)
1004                (if (eq winp :empty)
1005                    (multiple-value-bind (val winp)
1006                        (lookup-ignoring-global-cache *info-environment*)
1007                      (info-cache-enter name type val winp)
1008                      (values val winp))
1009                    (values val winp))))))))
1010 \f
1011 ;;;; definitions for function information
1012
1013 (define-info-class :function)
1014
1015 ;;; the kind of functional object being described. If null, NAME isn't
1016 ;;; a known functional object.
1017 (define-info-type
1018   :class :function
1019   :type :kind
1020   :type-spec (member nil :function :macro :special-form)
1021   ;; I'm a little confused what the correct behavior of this default
1022   ;; is. It's not clear how to generalize the FBOUNDP expression to
1023   ;; the cross-compiler. As far as I can tell, NIL is a safe default
1024   ;; -- it might keep the compiler from making some valid
1025   ;; optimization, but it shouldn't produce incorrect code. -- WHN
1026   ;; 19990330
1027   :default
1028   #+sb-xc-host nil
1029   #-sb-xc-host (if (fboundp name) :function nil))
1030
1031 ;;; The type specifier for this function.
1032 (define-info-type
1033   :class :function
1034   :type :type
1035   :type-spec ctype
1036   ;; Again (as in DEFINE-INFO-TYPE :CLASS :FUNCTION :TYPE :KIND) it's
1037   ;; not clear how to generalize the FBOUNDP expression to the
1038   ;; cross-compiler. -- WHN 19990330
1039   :default
1040   #+sb-xc-host (specifier-type 'function)
1041   #-sb-xc-host (if (fboundp name)
1042                    (extract-fun-type (fdefinition name))
1043                    (specifier-type 'function)))
1044
1045 ;;; the ASSUMED-TYPE for this function, if we have to infer the type
1046 ;;; due to not having a declaration or definition
1047 (define-info-type
1048   :class :function
1049   :type :assumed-type
1050   ;; FIXME: The type-spec really should be
1051   ;;   (or approximate-fun-type null)).
1052   ;; It was changed to T as a hopefully-temporary hack while getting
1053   ;; cold init problems untangled.
1054   :type-spec t)
1055
1056 ;;; where this information came from:
1057 ;;;    :ASSUMED  = from uses of the object
1058 ;;;    :DEFINED  = from examination of the definition
1059 ;;;    :DECLARED = from a declaration
1060 ;;; :DEFINED trumps :ASSUMED, and :DECLARED trumps :DEFINED.
1061 ;;; :DEFINED and :ASSUMED are useful for issuing compile-time warnings,
1062 ;;; and :DECLARED is useful for ANSIly specializing code which
1063 ;;; implements the function, or which uses the function's return values.
1064 (define-info-type
1065   :class :function
1066   :type :where-from
1067   :type-spec (member :declared :assumed :defined)
1068   :default
1069   ;; Again (as in DEFINE-INFO-TYPE :CLASS :FUNCTION :TYPE :KIND) it's
1070   ;; not clear how to generalize the FBOUNDP expression to the
1071   ;; cross-compiler. -- WHN 19990606
1072   #+sb-xc-host :assumed
1073   #-sb-xc-host (if (fboundp name) :defined :assumed))
1074
1075 ;;; something which can be decoded into the inline expansion of the
1076 ;;; function, or NIL if there is none
1077 ;;;
1078 ;;; To inline a function, we want a lambda expression, e.g.
1079 ;;; '(LAMBDA (X) (+ X 1)). That can be encoded here in one of two
1080 ;;; ways.
1081 ;;;   * The value in INFO can be the lambda expression itself, e.g. 
1082 ;;;       (SETF (INFO :FUNCTION :INLINE-EXPANSION-DESIGNATOR 'FOO)
1083 ;;;             '(LAMBDA (X) (+ X 1)))
1084 ;;;     This is the ordinary way, the natural way of representing e.g.
1085 ;;;       (DECLAIM (INLINE FOO))
1086 ;;;       (DEFUN FOO (X) (+ X 1))
1087 ;;;   * The value in INFO can be a closure which returns the lambda
1088 ;;;     expression, e.g.
1089 ;;;       (SETF (INFO :FUNCTION :INLINE-EXPANSION-DESIGNATOR 'BAR-LEFT-CHILD)
1090 ;;;             (LAMBDA ()
1091 ;;;               '(LAMBDA (BAR) (BAR-REF BAR 3))))
1092 ;;;     This twisty way of storing values is supported in order to
1093 ;;;     allow structure slot accessors, and perhaps later other
1094 ;;;     stereotyped functions, to be represented compactly.
1095 (define-info-type
1096   :class :function
1097   :type :inline-expansion-designator
1098   :type-spec (or list function)
1099   :default nil)
1100
1101 ;;; This specifies whether this function may be expanded inline. If
1102 ;;; null, we don't care.
1103 (define-info-type
1104   :class :function
1105   :type :inlinep
1106   :type-spec inlinep
1107   :default nil)
1108
1109 ;;; a macro-like function which transforms a call to this function
1110 ;;; into some other Lisp form. This expansion is inhibited if inline
1111 ;;; expansion is inhibited
1112 (define-info-type
1113   :class :function
1114   :type :source-transform
1115   :type-spec (or function null))
1116
1117 ;;; the macroexpansion function for this macro
1118 (define-info-type
1119   :class :function
1120   :type :macro-function
1121   :type-spec (or function null)
1122   :default nil)
1123
1124 ;;; the compiler-macroexpansion function for this macro
1125 (define-info-type
1126   :class :function
1127   :type :compiler-macro-function
1128   :type-spec (or function null)
1129   :default nil)
1130
1131 ;;; a function which converts this special form into IR1
1132 (define-info-type
1133   :class :function
1134   :type :ir1-convert
1135   :type-spec (or function null))
1136
1137 ;;; If a function is "known" to the compiler, then this is a FUN-INFO
1138 ;;; structure containing the info used to special-case compilation.
1139 (define-info-type
1140   :class :function
1141   :type :info
1142   :type-spec (or fun-info null)
1143   :default nil)
1144
1145 (define-info-type
1146   :class :function
1147   :type :documentation
1148   :type-spec (or string null)
1149   :default nil)
1150
1151 (define-info-type
1152   :class :function
1153   :type :definition
1154   :type-spec (or fdefn null)
1155   :default nil)
1156 \f
1157 ;;;; definitions for other miscellaneous information
1158
1159 (define-info-class :variable)
1160
1161 ;;; the kind of variable-like thing described
1162 (define-info-type
1163   :class :variable
1164   :type :kind
1165   :type-spec (member :special :constant :macro :global :alien)
1166   :default (if (symbol-self-evaluating-p name)
1167                :constant
1168                :global))
1169
1170 ;;; the declared type for this variable
1171 (define-info-type
1172   :class :variable
1173   :type :type
1174   :type-spec ctype
1175   :default *universal-type*)
1176
1177 ;;; where this type and kind information came from
1178 (define-info-type
1179   :class :variable
1180   :type :where-from
1181   :type-spec (member :declared :assumed :defined)
1182   :default :assumed)
1183
1184 ;;; the Lisp object which is the value of this constant, if known
1185 (define-info-type
1186   :class :variable
1187   :type :constant-value
1188   :type-spec t
1189   ;; CMU CL used to return two values for (INFO :VARIABLE :CONSTANT-VALUE ..).
1190   ;; Now we don't: it was the last remaining multiple-value return from
1191   ;; the INFO system, and bringing it down to one value lets us simplify
1192   ;; things, especially simplifying the declaration of return types.
1193   ;; Software which used to check the second value (for "is it defined
1194   ;; as a constant?") should check (EQL (INFO :VARIABLE :KIND ..) :CONSTANT)
1195   ;; instead.
1196   :default (if (symbol-self-evaluating-p name)
1197                name
1198                (bug "constant lookup of nonconstant ~S" name)))
1199
1200 ;;; the macro-expansion for symbol-macros
1201 (define-info-type
1202   :class :variable
1203   :type :macro-expansion
1204   :type-spec t
1205   :default nil)
1206
1207 (define-info-type
1208   :class :variable
1209   :type :alien-info
1210   :type-spec (or heap-alien-info null)
1211   :default nil)
1212
1213 (define-info-type
1214   :class :variable
1215   :type :documentation
1216   :type-spec (or string null)
1217   :default nil)
1218
1219 (define-info-class :type)
1220
1221 ;;; the kind of type described. We return :INSTANCE for standard types
1222 ;;; that are implemented as structures. For PCL classes, that have
1223 ;;; only been compiled, but not loaded yet, we return
1224 ;;; :FORTHCOMING-DEFCLASS-TYPE.
1225 (define-info-type
1226   :class :type
1227   :type :kind
1228   :type-spec (member :primitive :defined :instance
1229                      :forthcoming-defclass-type nil)
1230   :default nil
1231   :validate-function (lambda (name new-value)
1232                        (declare (ignore new-value)
1233                                 (notinline info))
1234                        (when (info :declaration :recognized name)
1235                          (error 'declaration-type-conflict-error
1236                                 :format-arguments (list name)))))
1237
1238 ;;; the expander function for a defined type
1239 (define-info-type
1240   :class :type
1241   :type :expander
1242   :type-spec (or function null)
1243   :default nil)
1244
1245 (define-info-type
1246   :class :type
1247   :type :documentation
1248   :type-spec (or string null))
1249
1250 ;;; function that parses type specifiers into CTYPE structures
1251 (define-info-type
1252   :class :type
1253   :type :translator
1254   :type-spec (or function null)
1255   :default nil)
1256
1257 ;;; If true, then the type coresponding to this name. Note that if
1258 ;;; this is a built-in class with a translation, then this is the
1259 ;;; translation, not the class object. This info type keeps track of
1260 ;;; various atomic types (NIL etc.) and also serves as a cache to
1261 ;;; ensure that common standard types (atomic and otherwise) are only
1262 ;;; consed once.
1263 (define-info-type
1264   :class :type
1265   :type :builtin
1266   :type-spec (or ctype null)
1267   :default nil)
1268
1269 ;;; If this is a class name, then the value is a cons (NAME . CLASS),
1270 ;;; where CLASS may be null if the class hasn't been defined yet. Note
1271 ;;; that for built-in classes, the kind may be :PRIMITIVE and not
1272 ;;; :INSTANCE. The name is in the cons so that we can signal a
1273 ;;; meaningful error if we only have the cons.
1274 (define-info-type
1275   :class :type
1276   :type :classoid
1277   :type-spec (or sb!kernel::classoid-cell null)
1278   :default nil)
1279
1280 ;;; layout for this type being used by the compiler
1281 (define-info-type
1282   :class :type
1283   :type :compiler-layout
1284   :type-spec (or layout null)
1285   :default (let ((class (find-classoid name nil)))
1286              (when class (classoid-layout class))))
1287
1288 (define-info-class :typed-structure)
1289 (define-info-type
1290   :class :typed-structure
1291   :type :info
1292   :type-spec t
1293   :default nil)
1294 (define-info-type
1295   :class :typed-structure 
1296   :type :documentation
1297   :type-spec (or string null)
1298   :default nil)
1299
1300 (define-info-class :declaration)
1301 (define-info-type
1302   :class :declaration
1303   :type :recognized
1304   :type-spec boolean
1305   :validate-function (lambda (name new-value)
1306                        (declare (ignore new-value)
1307                                 (notinline info))
1308                        (when (info :type :kind name)
1309                          (error 'declaration-type-conflict-error
1310                                 :format-arguments (list name)))))
1311
1312 (define-info-class :alien-type)
1313 (define-info-type
1314   :class :alien-type
1315   :type :kind
1316   :type-spec (member :primitive :defined :unknown)
1317   :default :unknown)
1318 (define-info-type
1319   :class :alien-type
1320   :type :translator
1321   :type-spec (or function null)
1322   :default nil)
1323 (define-info-type
1324   :class :alien-type
1325   :type :definition
1326   :type-spec (or alien-type null)
1327   :default nil)
1328 (define-info-type
1329   :class :alien-type
1330   :type :struct
1331   :type-spec (or alien-type null)
1332   :default nil)
1333 (define-info-type
1334   :class :alien-type
1335   :type :union
1336   :type-spec (or alien-type null)
1337   :default nil)
1338 (define-info-type
1339   :class :alien-type
1340   :type :enum
1341   :type-spec (or alien-type null)
1342   :default nil)
1343
1344 (define-info-class :setf)
1345
1346 (define-info-type
1347   :class :setf
1348   :type :inverse
1349   :type-spec (or symbol null)
1350   :default nil)
1351
1352 (define-info-type
1353   :class :setf
1354   :type :documentation
1355   :type-spec (or string null)
1356   :default nil)
1357
1358 (define-info-type
1359   :class :setf
1360   :type :expander
1361   :type-spec (or function null)
1362   :default nil)
1363
1364 ;;; This is used for storing miscellaneous documentation types. The
1365 ;;; stuff is an alist translating documentation kinds to values.
1366 (define-info-class :random-documentation)
1367 (define-info-type
1368   :class :random-documentation
1369   :type :stuff
1370   :type-spec list
1371   :default ())
1372
1373 #!-sb-fluid (declaim (freeze-type info-env))
1374 \f
1375 ;;; Now that we have finished initializing *INFO-CLASSES* and
1376 ;;; *INFO-TYPES* (at compile time), generate code to set them at cold
1377 ;;; load time to the same state they have currently.
1378 (!cold-init-forms
1379   (/show0 "beginning *INFO-CLASSES* init, calling MAKE-HASH-TABLE")
1380   (setf *info-classes*
1381         (make-hash-table :size #.(hash-table-size *info-classes*)))
1382   (/show0 "done with MAKE-HASH-TABLE in *INFO-CLASSES* init")
1383   (dolist (class-info-name '#.(let ((result nil))
1384                                 (maphash (lambda (key value)
1385                                            (declare (ignore value))
1386                                            (push key result))
1387                                          *info-classes*)
1388                                 result))
1389     (let ((class-info (make-class-info class-info-name)))
1390       (setf (gethash class-info-name *info-classes*)
1391             class-info)))
1392   (/show0 "done with *INFO-CLASSES* initialization")
1393   (/show0 "beginning *INFO-TYPES* initialization")
1394   (setf *info-types*
1395         (map 'vector
1396              (lambda (x)
1397                (/show0 "in LAMBDA (X), X=..")
1398                (/hexstr x)
1399                (when x
1400                  (let* ((class-info (class-info-or-lose (second x)))
1401                         (type-info (make-type-info :name (first x)
1402                                                    :class class-info
1403                                                    :number (third x)
1404                                                    :type (fourth x))))
1405                    (/show0 "got CLASS-INFO in LAMBDA (X)")
1406                    (push type-info (class-info-types class-info))
1407                    type-info)))
1408              '#.(map 'list
1409                      (lambda (info-type)
1410                        (when info-type
1411                          (list (type-info-name info-type)
1412                                (class-info-name (type-info-class info-type))
1413                                (type-info-number info-type)
1414                                (type-info-type info-type))))
1415                      *info-types*)))
1416   (/show0 "done with *INFO-TYPES* initialization"))
1417
1418 ;;; At cold load time, after the INFO-TYPE objects have been created,
1419 ;;; we can set their DEFAULT and TYPE slots.
1420 (macrolet ((frob ()
1421              `(!cold-init-forms
1422                 ,@(reverse *!reversed-type-info-init-forms*))))
1423   (frob))
1424 \f
1425 ;;;; a hack for detecting
1426 ;;;;   (DEFUN FOO (X Y)
1427 ;;;;     ..
1428 ;;;;     (SETF (BAR A FFH) 12) ; compiles to a call to #'(SETF BAR)
1429 ;;;;     ..)
1430 ;;;;   (DEFSETF BAR SET-BAR) ; can't influence previous compilation
1431 ;;;;
1432 ;;;; KLUDGE: Arguably it should be another class/type combination in
1433 ;;;; the globaldb. However, IMHO the whole globaldb/fdefinition
1434 ;;;; treatment of SETF functions is a mess which ought to be
1435 ;;;; rewritten, and I'm not inclined to mess with it short of that. So
1436 ;;;; I just put this bag on the side of it instead..
1437
1438 ;;; true for symbols FOO which have been assumed to have '(SETF FOO)
1439 ;;; bound to a function
1440 (defvar *setf-assumed-fboundp*)
1441 (!cold-init-forms (setf *setf-assumed-fboundp* (make-hash-table)))
1442 \f
1443 (!defun-from-collected-cold-init-forms !globaldb-cold-init)