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