0.6.12.22:
[sbcl.git] / src / compiler / generic / genesis.lisp
1 ;;;; "cold" core image builder: This is how we create a target Lisp
2 ;;;; system from scratch, by converting from fasl files to an image
3 ;;;; file in the cross-compilation host, without the help of the
4 ;;;; target Lisp system.
5 ;;;;
6 ;;;; As explained by Rob MacLachlan on the CMU CL mailing list Wed, 06
7 ;;;; Jan 1999 11:05:02 -0500, this cold load generator more or less
8 ;;;; fakes up static function linking. I.e. it makes sure that all the
9 ;;;; DEFUN-defined functions in the fasl files it reads are bound to the
10 ;;;; corresponding symbols before execution starts. It doesn't do
11 ;;;; anything to initialize variable values; instead it just arranges
12 ;;;; for !COLD-INIT to be called at cold load time. !COLD-INIT is
13 ;;;; responsible for explicitly initializing anything which has to be
14 ;;;; initialized early before it transfers control to the ordinary
15 ;;;; top-level forms.
16 ;;;;
17 ;;;; (In CMU CL, and in SBCL as of 0.6.9 anyway, functions not defined
18 ;;;; by DEFUN aren't set up specially by GENESIS. In particular,
19 ;;;; structure slot accessors are not set up. Slot accessors are
20 ;;;; available at cold init time because they're usually compiled
21 ;;;; inline. They're not available as out-of-line functions until the
22 ;;;; toplevel forms installing them have run.)
23
24 ;;;; This software is part of the SBCL system. See the README file for
25 ;;;; more information.
26 ;;;;
27 ;;;; This software is derived from the CMU CL system, which was
28 ;;;; written at Carnegie Mellon University and released into the
29 ;;;; public domain. The software is in the public domain and is
30 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
31 ;;;; files for more information.
32
33 (in-package "SB!FASL")
34
35 ;;; a magic number used to identify our core files
36 (defconstant core-magic
37   (logior (ash (char-code #\S) 24)
38           (ash (char-code #\B) 16)
39           (ash (char-code #\C) 8)
40           (char-code #\L)))
41
42 ;;; the current version of SBCL core files
43 ;;;
44 ;;; FIXME: This is left over from CMU CL, and not well thought out.
45 ;;; It's good to make sure that the runtime doesn't try to run core
46 ;;; files from the wrong version, but a single number is not the ideal
47 ;;; way to do this in high level data like this (as opposed to e.g. in
48 ;;; IP packets), and in fact the CMU CL version number never ended up
49 ;;; being incremented past 0. A better approach might be to use a
50 ;;; string which is set from CVS data.
51 ;;;
52 ;;; 0: inherited from CMU CL
53 ;;; 1: rearranged static symbols for sbcl-0.6.8
54 ;;; 2: eliminated non-ANSI %DEFCONSTANT/%%DEFCONSTANT support,
55 ;;;    deleted a slot from DEBUG-SOURCE structure
56 (defconstant sbcl-core-version-integer 2)
57
58 (defun round-up (number size)
59   #!+sb-doc
60   "Round NUMBER up to be an integral multiple of SIZE."
61   (* size (ceiling number size)))
62 \f
63 ;;;; representation of spaces in the core
64
65 (defvar *dynamic*)
66 (defconstant dynamic-space-id 1)
67
68 (defvar *static*)
69 (defconstant static-space-id 2)
70
71 (defvar *read-only*)
72 (defconstant read-only-space-id 3)
73
74 (defconstant descriptor-low-bits 16
75   "the number of bits in the low half of the descriptor")
76 (defconstant target-space-alignment (ash 1 descriptor-low-bits)
77   "the alignment requirement for spaces in the target.
78   Must be at least (ASH 1 DESCRIPTOR-LOW-BITS)")
79
80 ;;; a GENESIS-time representation of a memory space (e.g. read-only space,
81 ;;; dynamic space, or static space)
82 (defstruct (gspace (:constructor %make-gspace)
83                    (:copier nil))
84   ;; name and identifier for this GSPACE
85   (name (required-argument) :type symbol :read-only t)
86   (identifier (required-argument) :type fixnum :read-only t)
87   ;; the word address where the data will be loaded
88   (word-address (required-argument) :type unsigned-byte :read-only t)
89   ;; the data themselves. (Note that in CMU CL this was a pair
90   ;; of fields SAP and WORDS-ALLOCATED, but that wasn't very portable.)
91   (bytes (make-array target-space-alignment :element-type '(unsigned-byte 8))
92          :type (simple-array (unsigned-byte 8) 1))
93   ;; the index of the next unwritten word (i.e. chunk of
94   ;; SB!VM:WORD-BYTES bytes) in BYTES, or equivalently the number of
95   ;; words actually written in BYTES. In order to convert to an actual
96   ;; index into BYTES, thus must be multiplied by SB!VM:WORD-BYTES.
97   (free-word-index 0))
98
99 (defun gspace-byte-address (gspace)
100   (ash (gspace-word-address gspace) sb!vm:word-shift))
101
102 (def!method print-object ((gspace gspace) stream)
103   (print-unreadable-object (gspace stream :type t)
104     (format stream "~S" (gspace-name gspace))))
105
106 (defun make-gspace (name identifier byte-address)
107   (unless (zerop (rem byte-address target-space-alignment))
108     (error "The byte address #X~X is not aligned on a #X~X-byte boundary."
109            byte-address
110            target-space-alignment))
111   (%make-gspace :name name
112                 :identifier identifier
113                 :word-address (ash byte-address (- sb!vm:word-shift))))
114
115 ;;; KLUDGE: Doing it this way seems to partly replicate the
116 ;;; functionality of Common Lisp adjustable arrays. Is there any way
117 ;;; to do this stuff in one line of code by using standard Common Lisp
118 ;;; stuff? -- WHN 19990816
119 (defun expand-gspace-bytes (gspace)
120   (let* ((old-bytes (gspace-bytes gspace))
121          (old-length (length old-bytes))
122          (new-length (* 2 old-length))
123          (new-bytes (make-array new-length :element-type '(unsigned-byte 8))))
124     (replace new-bytes old-bytes :end1 old-length)
125     (setf (gspace-bytes gspace)
126           new-bytes))
127   (values))
128 \f
129 ;;;; representation of descriptors
130
131 (defstruct (descriptor
132             (:constructor make-descriptor
133                           (high low &optional gspace word-offset))
134             (:copier nil))
135   ;; the GSPACE that this descriptor is allocated in, or NIL if not set yet.
136   (gspace nil :type (or gspace null))
137   ;; the offset in words from the start of GSPACE, or NIL if not set yet
138   (word-offset nil :type (or (unsigned-byte #.sb!vm:word-bits) null))
139   ;; the high and low halves of the descriptor KLUDGE: Judging from
140   ;; the comments in genesis.lisp of the CMU CL old-rt compiler, this
141   ;; split dates back from a very early version of genesis where
142   ;; 32-bit integers were represented as conses of two 16-bit
143   ;; integers. In any system with nice (UNSIGNED-BYTE 32) structure
144   ;; slots, like CMU CL >= 17 or any version of SBCL, there seems to
145   ;; be no reason to persist in this. -- WHN 19990917
146   high low)
147 (def!method print-object ((des descriptor) stream)
148   (let ((lowtag (descriptor-lowtag des)))
149     (print-unreadable-object (des stream :type t)
150       (cond ((or (= lowtag sb!vm:even-fixnum-type)
151                  (= lowtag sb!vm:odd-fixnum-type))
152              (let ((unsigned (logior (ash (descriptor-high des)
153                                           (1+ (- descriptor-low-bits
154                                                  sb!vm:lowtag-bits)))
155                                      (ash (descriptor-low des)
156                                           (- 1 sb!vm:lowtag-bits)))))
157                (format stream
158                        "for fixnum: ~D"
159                        (if (> unsigned #x1FFFFFFF)
160                            (- unsigned #x40000000)
161                            unsigned))))
162             ((or (= lowtag sb!vm:other-immediate-0-type)
163                  (= lowtag sb!vm:other-immediate-1-type))
164              (format stream
165                      "for other immediate: #X~X, type #b~8,'0B"
166                      (ash (descriptor-bits des) (- sb!vm:type-bits))
167                      (logand (descriptor-low des) sb!vm:type-mask)))
168             (t
169              (format stream
170                      "for pointer: #X~X, lowtag #b~3,'0B, ~A"
171                      (logior (ash (descriptor-high des) descriptor-low-bits)
172                              (logandc2 (descriptor-low des) sb!vm:lowtag-mask))
173                      lowtag
174                      (let ((gspace (descriptor-gspace des)))
175                        (if gspace
176                            (gspace-name gspace)
177                            "unknown"))))))))
178
179 (defun allocate-descriptor (gspace length lowtag)
180   #!+sb-doc
181   "Return a descriptor for a block of LENGTH bytes out of GSPACE. The free
182   word index is boosted as necessary, and if additional memory is needed, we
183   grow the GSPACE. The descriptor returned is a pointer of type LOWTAG."
184   (let* ((bytes (round-up length (ash 1 sb!vm:lowtag-bits)))
185          (old-free-word-index (gspace-free-word-index gspace))
186          (new-free-word-index (+ old-free-word-index
187                                  (ash bytes (- sb!vm:word-shift)))))
188     ;; Grow GSPACE as necessary until it's big enough to handle
189     ;; NEW-FREE-WORD-INDEX.
190     (do ()
191         ((>= (length (gspace-bytes gspace))
192              (* new-free-word-index sb!vm:word-bytes)))
193       (expand-gspace-bytes gspace))
194     ;; Now that GSPACE is big enough, we can meaningfully grab a chunk of it.
195     (setf (gspace-free-word-index gspace) new-free-word-index)
196     (let ((ptr (+ (gspace-word-address gspace) old-free-word-index)))
197       (make-descriptor (ash ptr (- sb!vm:word-shift descriptor-low-bits))
198                        (logior (ash (logand ptr
199                                             (1- (ash 1
200                                                      (- descriptor-low-bits
201                                                         sb!vm:word-shift))))
202                                     sb!vm:word-shift)
203                                lowtag)
204                        gspace
205                        old-free-word-index))))
206
207 (defun descriptor-lowtag (des)
208   #!+sb-doc
209   "the lowtag bits for DES"
210   (logand (descriptor-low des) sb!vm:lowtag-mask))
211
212 (defun descriptor-bits (des)
213   (logior (ash (descriptor-high des) descriptor-low-bits)
214           (descriptor-low des)))
215
216 (defun descriptor-fixnum (des)
217   (let ((bits (descriptor-bits des)))
218     (if (logbitp (1- sb!vm:word-bits) bits)
219       ;; KLUDGE: The (- SB!VM:WORD-BITS 2) term here looks right to
220       ;; me, and it works, but in CMU CL it was (1- SB!VM:WORD-BITS),
221       ;; and although that doesn't make sense for me, or work for me,
222       ;; it's hard to see how it could have been wrong, since CMU CL
223       ;; genesis worked. It would be nice to understand how this came
224       ;; to be.. -- WHN 19990901
225       (logior (ash bits -2) (ash -1 (- sb!vm:word-bits 2)))
226       (ash bits -2))))
227
228 ;;; common idioms
229 (defun descriptor-bytes (des)
230   (gspace-bytes (descriptor-intuit-gspace des)))
231 (defun descriptor-byte-offset (des)
232   (ash (descriptor-word-offset des) sb!vm:word-shift))
233
234 ;;; If DESCRIPTOR-GSPACE is already set, just return that. Otherwise,
235 ;;; figure out a GSPACE which corresponds to DES, set it into
236 ;;; (DESCRIPTOR-GSPACE DES), set a consistent value into
237 ;;; (DESCRIPTOR-WORD-OFFSET DES), and return the GSPACE.
238 (declaim (ftype (function (descriptor) gspace) descriptor-intuit-gspace))
239 (defun descriptor-intuit-gspace (des)
240   (if (descriptor-gspace des)
241     (descriptor-gspace des)
242     ;; KLUDGE: It's not completely clear to me what's going on here;
243     ;; this is a literal translation from of some rather mysterious
244     ;; code from CMU CL's DESCRIPTOR-SAP function. Some explanation
245     ;; would be nice. -- WHN 19990817
246     (let ((lowtag (descriptor-lowtag des))
247           (high (descriptor-high des))
248           (low (descriptor-low des)))
249       (if (or (eql lowtag sb!vm:function-pointer-type)
250               (eql lowtag sb!vm:instance-pointer-type)
251               (eql lowtag sb!vm:list-pointer-type)
252               (eql lowtag sb!vm:other-pointer-type))
253         (dolist (gspace (list *dynamic* *static* *read-only*)
254                         (error "couldn't find a GSPACE for ~S" des))
255           ;; This code relies on the fact that GSPACEs are aligned such that
256           ;; the descriptor-low-bits low bits are zero.
257           (when (and (>= high (ash (gspace-word-address gspace)
258                                    (- sb!vm:word-shift descriptor-low-bits)))
259                      (<= high (ash (+ (gspace-word-address gspace)
260                                       (gspace-free-word-index gspace))
261                                    (- sb!vm:word-shift descriptor-low-bits))))
262             (setf (descriptor-gspace des) gspace)
263             (setf (descriptor-word-offset des)
264                   (+ (ash (- high (ash (gspace-word-address gspace)
265                                        (- sb!vm:word-shift
266                                           descriptor-low-bits)))
267                           (- descriptor-low-bits sb!vm:word-shift))
268                      (ash (logandc2 low sb!vm:lowtag-mask)
269                           (- sb!vm:word-shift))))
270             (return gspace)))
271         (error "don't even know how to look for a GSPACE for ~S" des)))))
272
273 (defun make-random-descriptor (value)
274   (make-descriptor (logand (ash value (- descriptor-low-bits))
275                            (1- (ash 1
276                                     (- sb!vm:word-bits descriptor-low-bits))))
277                    (logand value (1- (ash 1 descriptor-low-bits)))))
278
279 (defun make-fixnum-descriptor (num)
280   (when (>= (integer-length num)
281             (1+ (- sb!vm:word-bits sb!vm:lowtag-bits)))
282     (error "~D is too big for a fixnum." num))
283   (make-random-descriptor (ash num (1- sb!vm:lowtag-bits))))
284
285 (defun make-other-immediate-descriptor (data type)
286   (make-descriptor (ash data (- sb!vm:type-bits descriptor-low-bits))
287                    (logior (logand (ash data (- descriptor-low-bits
288                                                 sb!vm:type-bits))
289                                    (1- (ash 1 descriptor-low-bits)))
290                            type)))
291
292 (defun make-character-descriptor (data)
293   (make-other-immediate-descriptor data sb!vm:base-char-type))
294
295 (defun descriptor-beyond (des offset type)
296   (let* ((low (logior (+ (logandc2 (descriptor-low des) sb!vm:lowtag-mask)
297                          offset)
298                       type))
299          (high (+ (descriptor-high des)
300                   (ash low (- descriptor-low-bits)))))
301     (make-descriptor high (logand low (1- (ash 1 descriptor-low-bits))))))
302 \f
303 ;;;; miscellaneous variables and other noise
304
305 ;;; a numeric value to be returned for undefined foreign symbols, or NIL if
306 ;;; undefined foreign symbols are to be treated as an error.
307 ;;; (In the first pass of GENESIS, needed to create a header file before
308 ;;; the C runtime can be built, various foreign symbols will necessarily
309 ;;; be undefined, but we don't need actual values for them anyway, and
310 ;;; we can just use 0 or some other placeholder. In the second pass of
311 ;;; GENESIS, all foreign symbols should be defined, so any undefined
312 ;;; foreign symbol is a problem.)
313 ;;;
314 ;;; KLUDGE: It would probably be cleaner to rewrite GENESIS so that it
315 ;;; never tries to look up foreign symbols in the first place unless
316 ;;; it's actually creating a core file (as in the second pass) instead
317 ;;; of using this hack to allow it to go through the motions without
318 ;;; causing an error. -- WHN 20000825
319 (defvar *foreign-symbol-placeholder-value*)
320
321 ;;; a handle on the trap object
322 (defvar *unbound-marker*)
323 ;; was:  (make-other-immediate-descriptor 0 sb!vm:unbound-marker-type)
324
325 ;;; a handle on the NIL object
326 (defvar *nil-descriptor*)
327
328 ;;; the head of a list of TOPLEVEL-THINGs describing stuff to be done
329 ;;; when the target Lisp starts up
330 ;;;
331 ;;; Each TOPLEVEL-THING can be a function to be executed or a fixup or
332 ;;; loadtime value, represented by (CONS KEYWORD ..). The FILENAME
333 ;;; tells which fasl file each list element came from, for debugging
334 ;;; purposes.
335 (defvar *current-reversed-cold-toplevels*)
336
337 ;;; the name of the object file currently being cold loaded (as a string, not a
338 ;;; pathname), or NIL if we're not currently cold loading any object file
339 (defvar *cold-load-filename* nil)
340 (declaim (type (or string null) *cold-load-filename*))
341
342 ;;; This is vestigial support for the CMU CL byte-swapping code. CMU
343 ;;; CL code tested for whether it needed to swap bytes in GENESIS by
344 ;;; comparing the byte order of *BACKEND* to the byte order of
345 ;;; *NATIVE-BACKEND*, a concept which doesn't exist in SBCL. Instead,
346 ;;; in SBCL byte order swapping would need to be explicitly requested
347 ;;; with a &KEY argument to GENESIS.
348 ;;;
349 ;;; I'm not sure whether this is a problem or not, and I don't have a
350 ;;; machine with different byte order to test to find out for sure.
351 ;;; The version of the system which is fed to the cross-compiler is
352 ;;; now written in a subset of Common Lisp which doesn't require
353 ;;; dumping a lot of things in such a way that machine byte order
354 ;;; matters. (Mostly this is a matter of not using any specialized
355 ;;; array type unless there's portable, high-level code to dump it.)
356 ;;; If it *is* a problem, and you're trying to resurrect this code,
357 ;;; please test particularly carefully, since I haven't had a chance
358 ;;; to test the byte-swapping code at all. -- WHN 19990816
359 ;;;
360 ;;; When this variable is non-NIL, byte-swapping is enabled wherever
361 ;;; classic GENESIS would have done it. I.e. the value of this variable
362 ;;; is the logical complement of
363 ;;;    (EQ (SB!C:BACKEND-BYTE-ORDER SB!C:*NATIVE-BACKEND*)
364 ;;;     (SB!C:BACKEND-BYTE-ORDER SB!C:*BACKEND*))
365 ;;; from CMU CL.
366 (defvar *genesis-byte-order-swap-p*)
367 \f
368 ;;;; miscellaneous stuff to read and write the core memory
369
370 ;;; FIXME: should be DEFINE-MODIFY-MACRO
371 (defmacro cold-push (thing list)
372   #!+sb-doc
373   "Push THING onto the given cold-load LIST."
374   `(setq ,list (cold-cons ,thing ,list)))
375
376 (defun maybe-byte-swap (word)
377   (declare (type (unsigned-byte 32) word))
378   (aver (= sb!vm:word-bits 32))
379   (aver (= sb!vm:byte-bits 8))
380   (if (not *genesis-byte-order-swap-p*)
381       word
382       (logior (ash (ldb (byte 8 0) word) 24)
383               (ash (ldb (byte 8 8) word) 16)
384               (ash (ldb (byte 8 16) word) 8)
385               (ldb (byte 8 24) word))))
386
387 (defun maybe-byte-swap-short (short)
388   (declare (type (unsigned-byte 16) short))
389   (aver (= sb!vm:word-bits 32))
390   (aver (= sb!vm:byte-bits 8))
391   (if (not *genesis-byte-order-swap-p*)
392       short
393       (logior (ash (ldb (byte 8 0) short) 8)
394               (ldb (byte 8 8) short))))
395
396 ;;; BYTE-VECTOR-REF-32 and friends.  These are like SAP-REF-n, except
397 ;;; that instead of a SAP we use a byte vector
398 (macrolet ((make-byte-vector-ref-n
399             (n)
400             (let* ((name (intern (format nil "BYTE-VECTOR-REF-~A" n)))
401                    (number-octets (/ n 8))
402                    (ash-list
403                     (loop for i from 0 to (1- number-octets)
404                           collect `(ash (aref byte-vector (+ byte-index ,i))
405                                         ,(* i 8))))
406                    (setf-list
407                     (loop for i from 0 to (1- number-octets)
408                           append
409                           `((aref byte-vector (+ byte-index ,i))
410                             (ldb (byte 8 ,(* i 8)) new-value)))))
411               `(progn
412                  (defun ,name (byte-vector byte-index)
413   (aver (= sb!vm:word-bits 32))
414   (aver (= sb!vm:byte-bits 8))
415   (ecase sb!c:*backend-byte-order*
416     (:little-endian
417                       (logior ,@ash-list))
418     (:big-endian
419      (error "stub: no big-endian ports of SBCL (yet?)"))))
420                  (defun (setf ,name) (new-value byte-vector byte-index)
421   (aver (= sb!vm:word-bits 32))
422   (aver (= sb!vm:byte-bits 8))
423   (ecase sb!c:*backend-byte-order*
424     (:little-endian
425                       (setf ,@setf-list))
426     (:big-endian
427                       (error "stub: no big-endian ports of SBCL (yet?)"))))))))
428   (make-byte-vector-ref-n 8)
429   (make-byte-vector-ref-n 16)
430   (make-byte-vector-ref-n 32))
431
432 (declaim (ftype (function (descriptor sb!vm:word) descriptor) read-wordindexed))
433 (defun read-wordindexed (address index)
434   #!+sb-doc
435   "Return the value which is displaced by INDEX words from ADDRESS."
436   (let* ((gspace (descriptor-intuit-gspace address))
437          (bytes (gspace-bytes gspace))
438          (byte-index (ash (+ index (descriptor-word-offset address))
439                           sb!vm:word-shift))
440          ;; KLUDGE: Do we really need to do byte swap here? It seems
441          ;; as though we shouldn't.. (This attempts to be a literal
442          ;; translation of CMU CL code, and I don't have a big-endian
443          ;; machine to test it.) -- WHN 19990817
444          (value (maybe-byte-swap (byte-vector-ref-32 bytes byte-index))))
445     (make-random-descriptor value)))
446
447 (declaim (ftype (function (descriptor) descriptor) read-memory))
448 (defun read-memory (address)
449   #!+sb-doc
450   "Return the value at ADDRESS."
451   (read-wordindexed address 0))
452
453 ;;; (Note: In CMU CL, this function expected a SAP-typed ADDRESS
454 ;;; value, instead of the SAPINT we use here.)
455 (declaim (ftype (function (sb!vm:word descriptor) (values)) note-load-time-value-reference))
456 (defun note-load-time-value-reference (address marker)
457   (cold-push (cold-cons
458               (cold-intern :load-time-value-fixup)
459               (cold-cons (sapint-to-core address)
460                          (cold-cons
461                           (number-to-core (descriptor-word-offset marker))
462                           *nil-descriptor*)))
463              *current-reversed-cold-toplevels*)
464   (values))
465
466 (declaim (ftype (function (descriptor sb!vm:word descriptor)) write-wordindexed))
467 (defun write-wordindexed (address index value)
468   #!+sb-doc
469   "Write VALUE displaced INDEX words from ADDRESS."
470   ;; KLUDGE: There is an algorithm (used in DESCRIPTOR-INTUIT-GSPACE)
471   ;; for calculating the value of the GSPACE slot from scratch. It
472   ;; doesn't work for all values, only some of them, but mightn't it
473   ;; be reasonable to see whether it works on VALUE before we give up
474   ;; because (DESCRIPTOR-GSPACE VALUE) isn't set? (Or failing that,
475   ;; perhaps write a comment somewhere explaining why it's not a good
476   ;; idea?) -- WHN 19990817
477   (if (and (null (descriptor-gspace value))
478            (not (null (descriptor-word-offset value))))
479     (note-load-time-value-reference (+ (logandc2 (descriptor-bits address)
480                                                  sb!vm:lowtag-mask)
481                                        (ash index sb!vm:word-shift))
482                                     value)
483     ;; Note: There's a MAYBE-BYTE-SWAP in here in CMU CL, which I
484     ;; think is unnecessary now that we're doing the write
485     ;; byte-by-byte at high level. (I can't test this, though..) --
486     ;; WHN 19990817
487     (let* ((bytes (gspace-bytes (descriptor-intuit-gspace address)))
488            (byte-index (ash (+ index (descriptor-word-offset address))
489                                sb!vm:word-shift)))
490       (setf (byte-vector-ref-32 bytes byte-index)
491             (maybe-byte-swap (descriptor-bits value))))))
492
493 (declaim (ftype (function (descriptor descriptor)) write-memory))
494 (defun write-memory (address value)
495   #!+sb-doc
496   "Write VALUE (a DESCRIPTOR) at ADDRESS (also a DESCRIPTOR)."
497   (write-wordindexed address 0 value))
498 \f
499 ;;;; allocating images of primitive objects in the cold core
500
501 ;;; There are three kinds of blocks of memory in the type system:
502 ;;; * Boxed objects (cons cells, structures, etc): These objects have no
503 ;;;   header as all slots are descriptors.
504 ;;; * Unboxed objects (bignums): There is a single header word that contains
505 ;;;   the length.
506 ;;; * Vector objects: There is a header word with the type, then a word for
507 ;;;   the length, then the data.
508 (defun allocate-boxed-object (gspace length lowtag)
509   #!+sb-doc
510   "Allocate LENGTH words in GSPACE and return a new descriptor of type LOWTAG
511   pointing to them."
512   (allocate-descriptor gspace (ash length sb!vm:word-shift) lowtag))
513 (defun allocate-unboxed-object (gspace element-bits length type)
514   #!+sb-doc
515   "Allocate LENGTH units of ELEMENT-BITS bits plus a header word in GSPACE and
516   return an ``other-pointer'' descriptor to them. Initialize the header word
517   with the resultant length and TYPE."
518   (let* ((bytes (/ (* element-bits length) sb!vm:byte-bits))
519          (des (allocate-descriptor gspace
520                                    (+ bytes sb!vm:word-bytes)
521                                    sb!vm:other-pointer-type)))
522     (write-memory des
523                   (make-other-immediate-descriptor (ash bytes
524                                                         (- sb!vm:word-shift))
525                                                    type))
526     des))
527 (defun allocate-vector-object (gspace element-bits length type)
528   #!+sb-doc
529   "Allocate LENGTH units of ELEMENT-BITS size plus a header plus a length slot in
530   GSPACE and return an ``other-pointer'' descriptor to them. Initialize the
531   header word with TYPE and the length slot with LENGTH."
532   ;; FIXME: Here and in ALLOCATE-UNBOXED-OBJECT, BYTES is calculated using
533   ;; #'/ instead of #'CEILING, which seems wrong.
534   (let* ((bytes (/ (* element-bits length) sb!vm:byte-bits))
535          (des (allocate-descriptor gspace (+ bytes (* 2 sb!vm:word-bytes))
536                                           sb!vm:other-pointer-type)))
537     (write-memory des (make-other-immediate-descriptor 0 type))
538     (write-wordindexed des
539                        sb!vm:vector-length-slot
540                        (make-fixnum-descriptor length))
541     des))
542 \f
543 ;;;; copying simple objects into the cold core
544
545 (defun string-to-core (string &optional (gspace *dynamic*))
546   #!+sb-doc
547   "Copy string into the cold core and return a descriptor to it."
548   ;; (Remember that the system convention for storage of strings leaves an
549   ;; extra null byte at the end to aid in call-out to C.)
550   (let* ((length (length string))
551          (des (allocate-vector-object gspace
552                                       sb!vm:byte-bits
553                                       (1+ length)
554                                       sb!vm:simple-string-type))
555          (bytes (gspace-bytes gspace))
556          (offset (+ (* sb!vm:vector-data-offset sb!vm:word-bytes)
557                     (descriptor-byte-offset des))))
558     (write-wordindexed des
559                        sb!vm:vector-length-slot
560                        (make-fixnum-descriptor length))
561     (dotimes (i length)
562       (setf (aref bytes (+ offset i))
563             ;; KLUDGE: There's no guarantee that the character
564             ;; encoding here will be the same as the character
565             ;; encoding on the target machine, so using CHAR-CODE as
566             ;; we do, or a bitwise copy as CMU CL code did, is sleazy.
567             ;; (To make this more portable, perhaps we could use
568             ;; indices into the sequence which is used to test whether
569             ;; a character is a STANDARD-CHAR?) -- WHN 19990817
570             (char-code (aref string i))))
571     (setf (aref bytes (+ offset length))
572           0) ; null string-termination character for C
573     des))
574
575 (defun bignum-to-core (n)
576   #!+sb-doc
577   "Copy a bignum to the cold core."
578   (let* ((words (ceiling (1+ (integer-length n)) sb!vm:word-bits))
579          (handle (allocate-unboxed-object *dynamic*
580                                           sb!vm:word-bits
581                                           words
582                                           sb!vm:bignum-type)))
583     (declare (fixnum words))
584     (do ((index 1 (1+ index))
585          (remainder n (ash remainder (- sb!vm:word-bits))))
586         ((> index words)
587          (unless (zerop (integer-length remainder))
588            ;; FIXME: Shouldn't this be a fatal error?
589            (warn "~D words of ~D were written, but ~D bits were left over."
590                  words n remainder)))
591       (let ((word (ldb (byte sb!vm:word-bits 0) remainder)))
592         (write-wordindexed handle index
593                            (make-descriptor (ash word (- descriptor-low-bits))
594                                             (ldb (byte descriptor-low-bits 0)
595                                                  word)))))
596     handle))
597
598 (defun number-pair-to-core (first second type)
599   #!+sb-doc
600   "Makes a number pair of TYPE (ratio or complex) and fills it in."
601   (let ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits 2 type)))
602     (write-wordindexed des 1 first)
603     (write-wordindexed des 2 second)
604     des))
605
606 (defun float-to-core (x)
607   (etypecase x
608     (single-float
609      (let ((des (allocate-unboxed-object *dynamic*
610                                          sb!vm:word-bits
611                                          (1- sb!vm:single-float-size)
612                                          sb!vm:single-float-type)))
613        (write-wordindexed des
614                           sb!vm:single-float-value-slot
615                           (make-random-descriptor (single-float-bits x)))
616        des))
617     (double-float
618      (let ((des (allocate-unboxed-object *dynamic*
619                                          sb!vm:word-bits
620                                          (1- sb!vm:double-float-size)
621                                          sb!vm:double-float-type))
622            (high-bits (make-random-descriptor (double-float-high-bits x)))
623            (low-bits (make-random-descriptor (double-float-low-bits x))))
624        (ecase sb!c:*backend-byte-order*
625          (:little-endian
626           (write-wordindexed des sb!vm:double-float-value-slot low-bits)
627           (write-wordindexed des (1+ sb!vm:double-float-value-slot) high-bits))
628          (:big-endian
629           (write-wordindexed des sb!vm:double-float-value-slot high-bits)
630           (write-wordindexed des (1+ sb!vm:double-float-value-slot) low-bits)))
631        des))
632     #!+(and long-float x86)
633     (long-float
634      (let ((des (allocate-unboxed-object *dynamic*
635                                          sb!vm:word-bits
636                                          (1- sb!vm:long-float-size)
637                                          sb!vm:long-float-type))
638            (exp-bits (make-random-descriptor (long-float-exp-bits x)))
639            (high-bits (make-random-descriptor (long-float-high-bits x)))
640            (low-bits (make-random-descriptor (long-float-low-bits x))))
641        (ecase sb!c:*backend-byte-order*
642          (:little-endian
643           (write-wordindexed des sb!vm:long-float-value-slot low-bits)
644           (write-wordindexed des (1+ sb!vm:long-float-value-slot) high-bits)
645           (write-wordindexed des (+ 2 sb!vm:long-float-value-slot) exp-bits))
646          (:big-endian
647           (error "LONG-FLOAT is not supported for big-endian byte order.")))
648        des))))
649
650 (defun complex-single-float-to-core (num)
651   (declare (type (complex single-float) num))
652   (let ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
653                                       (1- sb!vm:complex-single-float-size)
654                                       sb!vm:complex-single-float-type)))
655     (write-wordindexed des sb!vm:complex-single-float-real-slot
656                    (make-random-descriptor (single-float-bits (realpart num))))
657     (write-wordindexed des sb!vm:complex-single-float-imag-slot
658                    (make-random-descriptor (single-float-bits (imagpart num))))
659     des))
660
661 (defun complex-double-float-to-core (num)
662   (declare (type (complex double-float) num))
663   (let ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
664                                       (1- sb!vm:complex-double-float-size)
665                                       sb!vm:complex-double-float-type)))
666     (let* ((real (realpart num))
667            (high-bits (make-random-descriptor (double-float-high-bits real)))
668            (low-bits (make-random-descriptor (double-float-low-bits real))))
669       (ecase sb!c:*backend-byte-order*
670         (:little-endian
671          (write-wordindexed des sb!vm:complex-double-float-real-slot low-bits)
672          (write-wordindexed des (1+ sb!vm:complex-double-float-real-slot) high-bits))
673         (:big-endian
674          (write-wordindexed des sb!vm:complex-double-float-real-slot high-bits)
675          (write-wordindexed des (1+ sb!vm:complex-double-float-real-slot) low-bits))))
676     (let* ((imag (imagpart num))
677            (high-bits (make-random-descriptor (double-float-high-bits imag)))
678            (low-bits (make-random-descriptor (double-float-low-bits imag))))
679       (ecase sb!c:*backend-byte-order*
680         (:little-endian
681          (write-wordindexed des sb!vm:complex-double-float-imag-slot low-bits)
682          (write-wordindexed des (1+ sb!vm:complex-double-float-imag-slot) high-bits))
683         (:big-endian
684          (write-wordindexed des sb!vm:complex-double-float-imag-slot high-bits)
685          (write-wordindexed des (1+ sb!vm:complex-double-float-imag-slot) low-bits))))
686     des))
687
688 (defun number-to-core (number)
689   #!+sb-doc
690   "Copy the given number to the core, or flame out if we can't deal with it."
691   (typecase number
692     (integer (if (< (integer-length number) 30)
693                  (make-fixnum-descriptor number)
694                  (bignum-to-core number)))
695     (ratio (number-pair-to-core (number-to-core (numerator number))
696                                 (number-to-core (denominator number))
697                                 sb!vm:ratio-type))
698     ((complex single-float) (complex-single-float-to-core number))
699     ((complex double-float) (complex-double-float-to-core number))
700     #!+long-float
701     ((complex long-float)
702      (error "~S isn't a cold-loadable number at all!" number))
703     (complex (number-pair-to-core (number-to-core (realpart number))
704                                   (number-to-core (imagpart number))
705                                   sb!vm:complex-type))
706     (float (float-to-core number))
707     (t (error "~S isn't a cold-loadable number at all!" number))))
708
709 (declaim (ftype (function (sb!vm:word) descriptor) sap-to-core))
710 (defun sapint-to-core (sapint)
711   (let ((des (allocate-unboxed-object *dynamic*
712                                       sb!vm:word-bits
713                                       (1- sb!vm:sap-size)
714                                       sb!vm:sap-type)))
715     (write-wordindexed des
716                        sb!vm:sap-pointer-slot
717                        (make-random-descriptor sapint))
718     des))
719
720 ;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR.
721 (defun cold-cons (car cdr &optional (gspace *dynamic*))
722   (let ((dest (allocate-boxed-object gspace 2 sb!vm:list-pointer-type)))
723     (write-memory dest car)
724     (write-wordindexed dest 1 cdr)
725     dest))
726
727 ;;; Make a simple-vector that holds the specified OBJECTS, and return its
728 ;;; descriptor.
729 (defun vector-in-core (&rest objects)
730   (let* ((size (length objects))
731          (result (allocate-vector-object *dynamic* sb!vm:word-bits size
732                                          sb!vm:simple-vector-type)))
733     (dotimes (index size)
734       (write-wordindexed result (+ index sb!vm:vector-data-offset)
735                          (pop objects)))
736     result))
737 \f
738 ;;;; symbol magic
739
740 ;;; FIXME: This should be a &KEY argument of ALLOCATE-SYMBOL.
741 (defvar *cold-symbol-allocation-gspace* nil)
742
743 ;;; Allocate (and initialize) a symbol.
744 (defun allocate-symbol (name)
745   (declare (simple-string name))
746   (let ((symbol (allocate-unboxed-object (or *cold-symbol-allocation-gspace*
747                                              *dynamic*)
748                                          sb!vm:word-bits
749                                          (1- sb!vm:symbol-size)
750                                          sb!vm:symbol-header-type)))
751     (write-wordindexed symbol sb!vm:symbol-value-slot *unbound-marker*)
752     #!+x86
753     (write-wordindexed symbol
754                        sb!vm:symbol-hash-slot
755                        (make-fixnum-descriptor
756                         (1+ (random sb!vm:*target-most-positive-fixnum*))))
757     (write-wordindexed symbol sb!vm:symbol-plist-slot *nil-descriptor*)
758     (write-wordindexed symbol sb!vm:symbol-name-slot
759                        (string-to-core name *dynamic*))
760     (write-wordindexed symbol sb!vm:symbol-package-slot *nil-descriptor*)
761     symbol))
762
763 ;;; Set the cold symbol value of SYMBOL-OR-SYMBOL-DES, which can be either a
764 ;;; descriptor of a cold symbol or (in an abbreviation for the
765 ;;; most common usage pattern) an ordinary symbol, which will be
766 ;;; automatically cold-interned.
767 (declaim (ftype (function ((or descriptor symbol) descriptor)) cold-set))
768 (defun cold-set (symbol-or-symbol-des value)
769   (let ((symbol-des (etypecase symbol-or-symbol-des
770                       (descriptor symbol-or-symbol-des)
771                       (symbol (cold-intern symbol-or-symbol-des)))))
772     (write-wordindexed symbol-des sb!vm:symbol-value-slot value)))
773 \f
774 ;;;; layouts and type system pre-initialization
775
776 ;;; Since we want to be able to dump structure constants and
777 ;;; predicates with reference layouts, we need to create layouts at
778 ;;; cold-load time. We use the name to intern layouts by, and dump a
779 ;;; list of all cold layouts in *!INITIAL-LAYOUTS* so that type system
780 ;;; initialization can find them. The only thing that's tricky [sic --
781 ;;; WHN 19990816] is initializing layout's layout, which must point to
782 ;;; itself.
783
784 ;;; a map from class names to lists of
785 ;;;    `(,descriptor ,name ,length ,inherits ,depth)
786 ;;; KLUDGE: It would be more understandable and maintainable to use
787 ;;; DEFSTRUCT (:TYPE LIST) here. -- WHN 19990823
788 (defvar *cold-layouts* (make-hash-table :test 'equal))
789
790 ;;; a map from DESCRIPTOR-BITS of cold layouts to the name, for inverting
791 ;;; mapping
792 (defvar *cold-layout-names* (make-hash-table :test 'eql))
793
794 ;;; FIXME: *COLD-LAYOUTS* and *COLD-LAYOUT-NAMES* should be
795 ;;; initialized by binding in GENESIS.
796
797 ;;; the descriptor for layout's layout (needed when making layouts)
798 (defvar *layout-layout*)
799
800 ;;; FIXME: This information should probably be pulled out of the
801 ;;; cross-compiler's tables at genesis time instead of inserted by
802 ;;; hand here as a bare numeric constant.
803 (defconstant target-layout-length 16)
804
805 ;;; Return a list of names created from the cold layout INHERITS data
806 ;;; in X.
807 (defun listify-cold-inherits (x)
808   (let ((len (descriptor-fixnum (read-wordindexed x
809                                                   sb!vm:vector-length-slot))))
810     (collect ((res))
811       (dotimes (index len)
812         (let* ((des (read-wordindexed x (+ sb!vm:vector-data-offset index)))
813                (found (gethash (descriptor-bits des) *cold-layout-names*)))
814           (if found
815             (res found)
816             (error "unknown descriptor at index ~S (bits = ~8,'0X)"
817                    index
818                    (descriptor-bits des)))))
819       (res))))
820
821 (declaim (ftype (function (symbol descriptor descriptor descriptor) descriptor)
822                 make-cold-layout))
823 (defun make-cold-layout (name length inherits depthoid)
824   (let ((result (allocate-boxed-object *dynamic*
825                                        ;; KLUDGE: Why 1+? -- WHN 19990901
826                                        (1+ target-layout-length)
827                                        sb!vm:instance-pointer-type)))
828     (write-memory result
829                   (make-other-immediate-descriptor target-layout-length
830                                                    sb!vm:instance-header-type))
831
832     ;; KLUDGE: The offsets into LAYOUT below should probably be pulled out
833     ;; of the cross-compiler's tables at genesis time instead of inserted
834     ;; by hand as bare numeric constants. -- WHN ca. 19990901
835
836     ;; Set slot 0 = the layout of the layout.
837     (write-wordindexed result sb!vm:instance-slots-offset *layout-layout*)
838
839     ;; Set the immediately following slots = CLOS hash values.
840     ;;
841     ;; Note: CMU CL didn't set these in genesis, but instead arranged
842     ;; for them to be set at cold init time. That resulted in slightly
843     ;; kludgy-looking code, but there were at least two things to be
844     ;; said for it:
845     ;;   1. It put the hash values under the control of the target Lisp's
846     ;;      RANDOM function, so that CLOS behavior would be nearly
847     ;;      deterministic (instead of depending on the implementation of
848     ;;      RANDOM in the cross-compilation host, and the state of its
849     ;;      RNG when genesis begins).
850     ;;   2. It automatically ensured that all hash values in the target Lisp
851     ;;      were part of the same sequence, so that we didn't have to worry
852     ;;      about the possibility of the first hash value set in genesis
853     ;;      being precisely equal to the some hash value set in cold init time
854     ;;      (because the target Lisp RNG has advanced to precisely the same
855     ;;      state that the host Lisp RNG was in earlier).
856     ;; Point 1 should not be an issue in practice because of the way we do our
857     ;; build procedure in two steps, so that the SBCL that we end up with has
858     ;; been created by another SBCL (whose RNG is under our control).
859     ;; Point 2 is more of an issue. If ANSI had provided a way to feed
860     ;; entropy into an RNG, we would have no problem: we'd just feed
861     ;; some specialized genesis-time-only pattern into the RNG state
862     ;; before using it. However, they didn't, so we have a slight
863     ;; problem. We address it by generating the hash values using a
864     ;; different algorithm than we use in ordinary operation.
865     (dotimes (i sb!kernel:layout-clos-hash-length)
866       (let (;; The expression here is pretty arbitrary, we just want
867             ;; to make sure that it's not something which is (1)
868             ;; evenly distributed and (2) not foreordained to arise in
869             ;; the target Lisp's (RANDOM-LAYOUT-CLOS-HASH) sequence
870             ;; and show up as the CLOS-HASH value of some other
871             ;; LAYOUT.
872             ;;
873             ;; FIXME: This expression here can generate a zero value,
874             ;; and the CMU CL code goes out of its way to generate
875             ;; strictly positive values (even though the field is
876             ;; declared as an INDEX). Check that it's really OK to
877             ;; have zero values in the CLOS-HASH slots.
878             (hash-value (mod (logxor (logand   (random-layout-clos-hash) 15253)
879                                      (logandc2 (random-layout-clos-hash) 15253)
880                                      1)
881                              ;; (The MOD here is defensive programming
882                              ;; to make sure we never write an
883                              ;; out-of-range value even if some joker
884                              ;; sets LAYOUT-CLOS-HASH-MAX to other
885                              ;; than 2^n-1 at some time in the
886                              ;; future.)
887                              (1+ sb!kernel:layout-clos-hash-max))))
888         (write-wordindexed result
889                            (+ i sb!vm:instance-slots-offset 1)
890                            (make-fixnum-descriptor hash-value))))
891
892     ;; Set other slot values.
893     (let ((base (+ sb!vm:instance-slots-offset
894                    sb!kernel:layout-clos-hash-length
895                    1)))
896       ;; (Offset 0 is CLASS, "the class this is a layout for", which
897       ;; is uninitialized at this point.)
898       (write-wordindexed result (+ base 1) *nil-descriptor*) ; marked invalid
899       (write-wordindexed result (+ base 2) inherits)
900       (write-wordindexed result (+ base 3) depthoid)
901       (write-wordindexed result (+ base 4) length)
902       (write-wordindexed result (+ base 5) *nil-descriptor*) ; info
903       (write-wordindexed result (+ base 6) *nil-descriptor*)) ; pure
904
905     (setf (gethash name *cold-layouts*)
906           (list result
907                 name
908                 (descriptor-fixnum length)
909                 (listify-cold-inherits inherits)
910                 (descriptor-fixnum depthoid)))
911     (setf (gethash (descriptor-bits result) *cold-layout-names*) name)
912
913     result))
914
915 (defun initialize-layouts ()
916
917   (clrhash *cold-layouts*)
918
919   ;; We initially create the layout of LAYOUT itself with NIL as the LAYOUT and
920   ;; #() as INHERITS,
921   (setq *layout-layout* *nil-descriptor*)
922   (setq *layout-layout*
923         (make-cold-layout 'layout
924                           (number-to-core target-layout-length)
925                           (vector-in-core)
926                           ;; FIXME: hard-coded LAYOUT-DEPTHOID of LAYOUT..
927                           (number-to-core 4)))
928   (write-wordindexed *layout-layout*
929                      sb!vm:instance-slots-offset
930                      *layout-layout*)
931
932   ;; Then we create the layouts that we'll need to make a correct INHERITS
933   ;; vector for the layout of LAYOUT itself..
934   ;;
935   ;; FIXME: The various LENGTH and DEPTHOID numbers should be taken from
936   ;; the compiler's tables, not set by hand.
937   (let* ((t-layout
938           (make-cold-layout 't
939                             (number-to-core 0)
940                             (vector-in-core)
941                             (number-to-core 0)))
942          (i-layout
943           (make-cold-layout 'instance
944                             (number-to-core 0)
945                             (vector-in-core t-layout)
946                             (number-to-core 1)))
947          (so-layout
948           (make-cold-layout 'structure-object
949                             (number-to-core 1)
950                             (vector-in-core t-layout i-layout)
951                             (number-to-core 2)))
952          (bso-layout
953           (make-cold-layout 'structure!object
954                             (number-to-core 1)
955                             (vector-in-core t-layout i-layout so-layout)
956                             (number-to-core 3)))
957          (layout-inherits (vector-in-core t-layout
958                                           i-layout
959                                           so-layout
960                                           bso-layout)))
961
962     ;; ..and return to backpatch the layout of LAYOUT.
963     (setf (fourth (gethash 'layout *cold-layouts*))
964           (listify-cold-inherits layout-inherits))
965     (write-wordindexed *layout-layout*
966                        ;; FIXME: hardcoded offset into layout struct
967                        (+ sb!vm:instance-slots-offset
968                           layout-clos-hash-length
969                           1
970                           2)
971                        layout-inherits)))
972 \f
973 ;;;; interning symbols in the cold image
974
975 ;;; In order to avoid having to know about the package format, we
976 ;;; build a data structure in *COLD-PACKAGE-SYMBOLS* that holds all
977 ;;; interned symbols along with info about their packages. The data
978 ;;; structure is a list of sublists, where the sublists have the
979 ;;; following format:
980 ;;;   (<make-package-arglist>
981 ;;;    <internal-symbols>
982 ;;;    <external-symbols>
983 ;;;    <imported-internal-symbols>
984 ;;;    <imported-external-symbols>
985 ;;;    <shadowing-symbols>)
986 ;;;
987 ;;; KLUDGE: It would be nice to implement the sublists as instances of
988 ;;; a DEFSTRUCT (:TYPE LIST). (They'd still be lists, but at least we'd be
989 ;;; using mnemonically-named operators to access them, instead of trying
990 ;;; to remember what THIRD and FIFTH mean, and hoping that we never
991 ;;; need to change the list layout..) -- WHN 19990825
992
993 ;;; an alist from packages to lists of that package's symbols to be dumped
994 (defvar *cold-package-symbols*)
995 (declaim (type list *cold-package-symbols*))
996
997 ;;; a map from descriptors to symbols, so that we can back up. The key is the
998 ;;; address in the target core.
999 (defvar *cold-symbols*)
1000 (declaim (type hash-table *cold-symbols*))
1001
1002 ;;; Return a handle on an interned symbol. If necessary allocate the
1003 ;;; symbol and record which package the symbol was referenced in. When
1004 ;;; we allocate the symbol, make sure we record a reference to the
1005 ;;; symbol in the home package so that the package gets set.
1006 (defun cold-intern (symbol &optional (package (symbol-package symbol)))
1007
1008   ;; Anything on the cross-compilation host which refers to the target
1009   ;; machinery through the host SB-XC package can be translated to
1010   ;; something on the target which refers to the same machinery
1011   ;; through the target COMMON-LISP package.
1012   (let ((p (find-package "SB-XC")))
1013     (when (eq package p)
1014       (setf package *cl-package*))
1015     (when (eq (symbol-package symbol) p)
1016       (setf symbol (intern (symbol-name symbol) *cl-package*))))
1017
1018   (let (;; Information about each cold-interned symbol is stored
1019         ;; in COLD-INTERN-INFO.
1020         ;;   (CAR COLD-INTERN-INFO) = descriptor of symbol
1021         ;;   (CDR COLD-INTERN-INFO) = list of packages, other than symbol's
1022         ;;                          own package, referring to symbol
1023         ;; (*COLD-PACKAGE-SYMBOLS* and *COLD-SYMBOLS* store basically the same
1024         ;; information, but with the mapping running the opposite way.)
1025         (cold-intern-info (get symbol 'cold-intern-info)))
1026     (unless cold-intern-info
1027       (cond ((eq (symbol-package symbol) package)
1028              (let ((handle (allocate-symbol (symbol-name symbol))))
1029                (setf (gethash (descriptor-bits handle) *cold-symbols*) symbol)
1030                (when (eq package *keyword-package*)
1031                  (cold-set handle handle))
1032                (setq cold-intern-info
1033                      (setf (get symbol 'cold-intern-info) (cons handle nil)))))
1034             (t
1035              (cold-intern symbol)
1036              (setq cold-intern-info (get symbol 'cold-intern-info)))))
1037     (unless (or (null package)
1038                 (member package (cdr cold-intern-info)))
1039       (push package (cdr cold-intern-info))
1040       (let* ((old-cps-entry (assoc package *cold-package-symbols*))
1041              (cps-entry (or old-cps-entry
1042                             (car (push (list package)
1043                                        *cold-package-symbols*)))))
1044         (unless old-cps-entry
1045           (/show "created *COLD-PACKAGE-SYMBOLS* entry for" package symbol))
1046         (push symbol (rest cps-entry))))
1047     (car cold-intern-info)))
1048
1049 ;;; Construct and return a value for use as *NIL-DESCRIPTOR*.
1050 (defun make-nil-descriptor ()
1051   (let* ((des (allocate-unboxed-object
1052                *static*
1053                sb!vm:word-bits
1054                sb!vm:symbol-size
1055                0))
1056          (result (make-descriptor (descriptor-high des)
1057                                   (+ (descriptor-low des)
1058                                      (* 2 sb!vm:word-bytes)
1059                                      (- sb!vm:list-pointer-type
1060                                         sb!vm:other-pointer-type)))))
1061     (write-wordindexed des
1062                        1
1063                        (make-other-immediate-descriptor
1064                         0
1065                         sb!vm:symbol-header-type))
1066     (write-wordindexed des
1067                        (+ 1 sb!vm:symbol-value-slot)
1068                        result)
1069     (write-wordindexed des
1070                        (+ 2 sb!vm:symbol-value-slot)
1071                        result)
1072     (write-wordindexed des
1073                        (+ 1 sb!vm:symbol-plist-slot)
1074                        result)
1075     (write-wordindexed des
1076                        (+ 1 sb!vm:symbol-name-slot)
1077                        ;; This is *DYNAMIC*, and DES is *STATIC*,
1078                        ;; because that's the way CMU CL did it; I'm
1079                        ;; not sure whether there's an underlying
1080                        ;; reason. -- WHN 1990826
1081                        (string-to-core "NIL" *dynamic*))
1082     (write-wordindexed des
1083                        (+ 1 sb!vm:symbol-package-slot)
1084                        result)
1085     (setf (get nil 'cold-intern-info)
1086           (cons result nil))
1087     (cold-intern nil)
1088     result))
1089
1090 ;;; Since the initial symbols must be allocated before we can intern
1091 ;;; anything else, we intern those here. We also set the value of T.
1092 (defun initialize-non-nil-symbols ()
1093   #!+sb-doc
1094   "Initialize the cold load symbol-hacking data structures."
1095   (let ((*cold-symbol-allocation-gspace* *static*))
1096     ;; Intern the others.
1097     (dolist (symbol sb!vm:*static-symbols*)
1098       (let* ((des (cold-intern symbol))
1099              (offset-wanted (sb!vm:static-symbol-offset symbol))
1100              (offset-found (- (descriptor-low des)
1101                               (descriptor-low *nil-descriptor*))))
1102         (unless (= offset-wanted offset-found)
1103           ;; FIXME: should be fatal
1104           (warn "Offset from ~S to ~S is ~D, not ~D"
1105                 symbol
1106                 nil
1107                 offset-found
1108                 offset-wanted))))
1109     ;; Establish the value of T.
1110     (let ((t-symbol (cold-intern t)))
1111       (cold-set t-symbol t-symbol))))
1112
1113 ;;; a helper function for FINISH-SYMBOLS: Return a cold alist suitable
1114 ;;; to be stored in *!INITIAL-LAYOUTS*.
1115 (defun cold-list-all-layouts ()
1116   (let ((result *nil-descriptor*))
1117     (maphash (lambda (key stuff)
1118                (cold-push (cold-cons (cold-intern key)
1119                                      (first stuff))
1120                           result))
1121              *cold-layouts*)
1122     result))
1123
1124 ;;; Establish initial values for magic symbols.
1125 ;;;
1126 ;;; Scan over all the symbols referenced in each package in
1127 ;;; *COLD-PACKAGE-SYMBOLS* making that for each one there's an
1128 ;;; appropriate entry in the *!INITIAL-SYMBOLS* data structure to
1129 ;;; intern it.
1130 (defun finish-symbols ()
1131
1132   ;; FIXME: Why use SETQ (setting symbol value) instead of just using
1133   ;; the function values for these things?? I.e. why do we need this
1134   ;; section at all? Is it because all the FDEFINITION stuff gets in
1135   ;; the way of reading function values and is too hairy to rely on at
1136   ;; cold boot? FIXME: 5/6 of these are in *STATIC-SYMBOLS* in
1137   ;; parms.lisp, but %HANDLE-FUNCTION-END-BREAKPOINT is not. Why?
1138   ;; Explain.
1139   (macrolet ((frob (symbol)
1140                `(cold-set ',symbol
1141                           (cold-fdefinition-object (cold-intern ',symbol)))))
1142     (frob !cold-init)
1143     (frob maybe-gc)
1144     (frob internal-error)
1145     (frob sb!di::handle-breakpoint)
1146     (frob sb!di::handle-function-end-breakpoint)
1147     (frob fdefinition-object))
1148
1149   (cold-set '*current-catch-block*          (make-fixnum-descriptor 0))
1150   (cold-set '*current-unwind-protect-block* (make-fixnum-descriptor 0))
1151   (cold-set '*eval-stack-top*               (make-fixnum-descriptor 0))
1152
1153   (cold-set '*free-interrupt-context-index* (make-fixnum-descriptor 0))
1154
1155   (cold-set '*!initial-layouts* (cold-list-all-layouts))
1156
1157   (/show "dumping packages" (mapcar #'car *cold-package-symbols*))
1158   (let ((initial-symbols *nil-descriptor*))
1159     (dolist (cold-package-symbols-entry *cold-package-symbols*)
1160       (let* ((cold-package (car cold-package-symbols-entry))
1161              (symbols (cdr cold-package-symbols-entry))
1162              (shadows (package-shadowing-symbols cold-package))
1163              (internal *nil-descriptor*)
1164              (external *nil-descriptor*)
1165              (imported-internal *nil-descriptor*)
1166              (imported-external *nil-descriptor*)
1167              (shadowing *nil-descriptor*))
1168         (/show "dumping" cold-package symbols)
1169
1170         ;; FIXME: Add assertions here to make sure that inappropriate stuff
1171         ;; isn't being dumped:
1172         ;;   * the CL-USER package
1173         ;;   * the SB-COLD package
1174         ;;   * any internal symbols in the CL package
1175         ;;   * basically any package other than CL, KEYWORD, or the packages
1176         ;;     in package-data-list.lisp-expr
1177         ;; and that the structure of the KEYWORD package (e.g. whether
1178         ;; any symbols are internal to it) matches what we want in the
1179         ;; target SBCL.
1180
1181         ;; FIXME: It seems possible that by looking at the contents of
1182         ;; packages in the target SBCL we could find which symbols in
1183         ;; package-data-lisp.lisp-expr are now obsolete. (If I
1184         ;; understand correctly, only symbols which actually have
1185         ;; definitions or which are otherwise referred to actually end
1186         ;; up in the target packages.)
1187
1188         (dolist (symbol symbols)
1189           (let ((handle (car (get symbol 'cold-intern-info)))
1190                 (imported-p (not (eq (symbol-package symbol) cold-package))))
1191             (multiple-value-bind (found where)
1192                 (find-symbol (symbol-name symbol) cold-package)
1193               (unless (and where (eq found symbol))
1194                 (error "The symbol ~S is not available in ~S."
1195                        symbol
1196                        cold-package))
1197               (when (memq symbol shadows)
1198                 (cold-push handle shadowing))
1199               (case where
1200                 (:internal (if imported-p
1201                                (cold-push handle imported-internal)
1202                                (cold-push handle internal)))
1203                 (:external (if imported-p
1204                                (cold-push handle imported-external)
1205                                (cold-push handle external)))))))
1206         (let ((r *nil-descriptor*))
1207           (cold-push shadowing r)
1208           (cold-push imported-external r)
1209           (cold-push imported-internal r)
1210           (cold-push external r)
1211           (cold-push internal r)
1212           (cold-push (make-make-package-args cold-package) r)
1213           ;; FIXME: It would be more space-efficient to use vectors
1214           ;; instead of lists here, and space-efficiency here would be
1215           ;; nice, since it would reduce the peak memory usage in
1216           ;; genesis and cold init.
1217           (cold-push r initial-symbols))))
1218     (cold-set '*!initial-symbols* initial-symbols))
1219
1220   (cold-set '*!initial-fdefn-objects* (list-all-fdefn-objects))
1221
1222   (cold-set '*!reversed-cold-toplevels* *current-reversed-cold-toplevels*)
1223
1224   #!+x86
1225   (progn
1226     (cold-set 'sb!vm::*fp-constant-0d0* (number-to-core 0d0))
1227     (cold-set 'sb!vm::*fp-constant-1d0* (number-to-core 1d0))
1228     (cold-set 'sb!vm::*fp-constant-0s0* (number-to-core 0s0))
1229     (cold-set 'sb!vm::*fp-constant-1s0* (number-to-core 1s0))
1230     #!+long-float
1231     (progn
1232       (cold-set 'sb!vm::*fp-constant-0l0* (number-to-core 0L0))
1233       (cold-set 'sb!vm::*fp-constant-1l0* (number-to-core 1L0))
1234       ;; FIXME: Why is initialization of PI conditional on LONG-FLOAT?
1235       ;; (ditto LG2, LN2, L2E, etc.)
1236       (cold-set 'sb!vm::*fp-constant-pi* (number-to-core pi))
1237       (cold-set 'sb!vm::*fp-constant-l2t* (number-to-core (log 10L0 2L0)))
1238       (cold-set 'sb!vm::*fp-constant-l2e*
1239             (number-to-core (log 2.718281828459045235360287471352662L0 2L0)))
1240       (cold-set 'sb!vm::*fp-constant-lg2* (number-to-core (log 2L0 10L0)))
1241       (cold-set 'sb!vm::*fp-constant-ln2*
1242             (number-to-core
1243              (log 2L0 2.718281828459045235360287471352662L0))))
1244     #!+gencgc
1245     (cold-set 'sb!vm::*SCAVENGE-READ-ONLY-GSPACE* *nil-descriptor*)))
1246
1247 ;;; Make a cold list that can be used as the arg list to MAKE-PACKAGE in order
1248 ;;; to make a package that is similar to PKG.
1249 (defun make-make-package-args (pkg)
1250   (let* ((use *nil-descriptor*)
1251          (cold-nicknames *nil-descriptor*)
1252          (res *nil-descriptor*))
1253     (dolist (u (package-use-list pkg))
1254       (when (assoc u *cold-package-symbols*)
1255         (cold-push (string-to-core (package-name u)) use)))
1256     (let* ((pkg-name (package-name pkg))
1257            ;; Make the package nickname lists for the standard packages
1258            ;; be the minimum specified by ANSI, regardless of what value
1259            ;; the cross-compilation host happens to use.
1260            (warm-nicknames (cond ((string= pkg-name "COMMON-LISP")
1261                                   '("CL"))
1262                                  ((string= pkg-name "COMMON-LISP-USER")
1263                                   '("CL-USER"))
1264                                  ((string= pkg-name "KEYWORD")
1265                                   '())
1266                                  ;; For packages other than the
1267                                  ;; standard packages, the nickname
1268                                  ;; list was specified by our package
1269                                  ;; setup code, not by properties of
1270                                  ;; what cross-compilation host we
1271                                  ;; happened to use, and we can just
1272                                  ;; propagate it into the target.
1273                                  (t
1274                                   (package-nicknames pkg)))))
1275       (dolist (warm-nickname warm-nicknames)
1276         (cold-push (string-to-core warm-nickname) cold-nicknames)))
1277
1278     (cold-push (number-to-core (truncate (package-internal-symbol-count pkg)
1279                                          0.8))
1280                res)
1281     (cold-push (cold-intern :internal-symbols) res)
1282     (cold-push (number-to-core (truncate (package-external-symbol-count pkg)
1283                                          0.8))
1284                res)
1285     (cold-push (cold-intern :external-symbols) res)
1286
1287     (cold-push cold-nicknames res)
1288     (cold-push (cold-intern :nicknames) res)
1289
1290     (cold-push use res)
1291     (cold-push (cold-intern :use) res)
1292
1293     (cold-push (string-to-core (package-name pkg)) res)
1294     res))
1295 \f
1296 ;;;; fdefinition objects
1297
1298 ;;; a hash table mapping from fdefinition names to descriptors of cold
1299 ;;; objects. Note: Since fdefinition names can be lists like '(SETF
1300 ;;; FOO), and we want to have only one entry per name, this must be an
1301 ;;; 'EQUAL hash table, not the default 'EQL.
1302 (defvar *cold-fdefn-objects*)
1303
1304 (defvar *cold-fdefn-gspace* nil)
1305
1306 ;;; Given a cold representation of an FDEFN name, return a warm representation.
1307 ;;;
1308 ;;; Note: Despite the name, this actually has little to do with
1309 ;;; FDEFNs, it's just a function for warming up values, and the only
1310 ;;; values it knows how to warm up are symbols and lists. (The
1311 ;;; connection to FDEFNs is that symbols and lists are the only
1312 ;;; possible names for functions.)
1313 (declaim (ftype (function (descriptor) (or symbol list)) warm-fdefn-name))
1314 (defun warm-fdefn-name (des)
1315   (ecase (descriptor-lowtag des)
1316     (#.sb!vm:list-pointer-type ; FIXME: no #.
1317      (if (= (descriptor-bits des) (descriptor-bits *nil-descriptor*))
1318          nil
1319          ;; FIXME: If we cold-intern this again, we might get a different
1320          ;; name. Check to make sure that any hash tables along the way
1321          ;; are 'EQUAL not 'EQL.
1322          (cons (warm-fdefn-name (read-wordindexed des sb!vm:cons-car-slot))
1323                (warm-fdefn-name (read-wordindexed des sb!vm:cons-cdr-slot)))))
1324     (#.sb!vm:other-pointer-type ; FIXME: no #.
1325      (or (gethash (descriptor-bits des) *cold-symbols*)
1326          (descriptor-bits des)))))
1327
1328 (defun cold-fdefinition-object (cold-name &optional leave-fn-raw)
1329   (declare (type descriptor cold-name))
1330   (let ((warm-name (warm-fdefn-name cold-name)))
1331     (or (gethash warm-name *cold-fdefn-objects*)
1332         (let ((fdefn (allocate-boxed-object (or *cold-fdefn-gspace* *dynamic*)
1333                                             (1- sb!vm:fdefn-size)
1334                                             sb!vm:other-pointer-type)))
1335
1336           (setf (gethash warm-name *cold-fdefn-objects*) fdefn)
1337           (write-memory fdefn (make-other-immediate-descriptor
1338                                (1- sb!vm:fdefn-size) sb!vm:fdefn-type))
1339           (write-wordindexed fdefn sb!vm:fdefn-name-slot cold-name)
1340           (unless leave-fn-raw
1341             (write-wordindexed fdefn sb!vm:fdefn-function-slot
1342                                *nil-descriptor*)
1343             (write-wordindexed fdefn
1344                                sb!vm:fdefn-raw-addr-slot
1345                                (make-random-descriptor
1346                                 (lookup-foreign-symbol "undefined_tramp"))))
1347           fdefn))))
1348
1349 (defun cold-fset (cold-name defn)
1350   (declare (type descriptor cold-name))
1351   (let ((fdefn (cold-fdefinition-object cold-name t))
1352         (type (logand (descriptor-low (read-memory defn)) sb!vm:type-mask)))
1353     (write-wordindexed fdefn sb!vm:fdefn-function-slot defn)
1354     (write-wordindexed fdefn
1355                        sb!vm:fdefn-raw-addr-slot
1356                        (ecase type
1357                          (#.sb!vm:function-header-type
1358                           #!+sparc
1359                           defn
1360                           #!-sparc
1361                           (make-random-descriptor
1362                            (+ (logandc2 (descriptor-bits defn)
1363                                         sb!vm:lowtag-mask)
1364                               (ash sb!vm:function-code-offset
1365                                    sb!vm:word-shift))))
1366                          (#.sb!vm:closure-header-type
1367                           (make-random-descriptor
1368                            (lookup-foreign-symbol "closure_tramp")))))
1369     fdefn))
1370
1371 (defun initialize-static-fns ()
1372   (let ((*cold-fdefn-gspace* *static*))
1373     (dolist (sym sb!vm:*static-functions*)
1374       (let* ((fdefn (cold-fdefinition-object (cold-intern sym)))
1375              (offset (- (+ (- (descriptor-low fdefn)
1376                               sb!vm:other-pointer-type)
1377                            (* sb!vm:fdefn-raw-addr-slot sb!vm:word-bytes))
1378                         (descriptor-low *nil-descriptor*)))
1379              (desired (sb!vm:static-function-offset sym)))
1380         (unless (= offset desired)
1381           ;; FIXME: should be fatal
1382           (warn "Offset from FDEFN ~S to ~S is ~D, not ~D."
1383                 sym nil offset desired))))))
1384
1385 (defun list-all-fdefn-objects ()
1386   (let ((result *nil-descriptor*))
1387     (maphash #'(lambda (key value)
1388                  (declare (ignore key))
1389                  (cold-push value result))
1390              *cold-fdefn-objects*)
1391     result))
1392 \f
1393 ;;;; fixups and related stuff
1394
1395 ;;; an EQUAL hash table
1396 (defvar *cold-foreign-symbol-table*)
1397 (declaim (type hash-table *cold-foreign-symbol-table*))
1398
1399 (defun load-foreign-symbol-table (filename)
1400   (with-open-file (file filename)
1401     (loop
1402       (let ((line (read-line file nil nil)))
1403         (unless line
1404           (return))
1405         ;; UNIX symbol tables might have tabs in them, and tabs are
1406         ;; not in Common Lisp STANDARD-CHAR, so there seems to be no
1407         ;; nice portable way to deal with them within Lisp, alas.
1408         ;; Fortunately, it's easy to use UNIX command line tools like
1409         ;; sed to remove the problem, so it's not too painful for us
1410         ;; to push responsibility for converting tabs to spaces out to
1411         ;; the caller.
1412         ;;
1413         ;; Other non-STANDARD-CHARs are problematic for the same reason.
1414         ;; Make sure that there aren't any..
1415         (let ((ch (find-if (lambda (char)
1416                              (not (typep char 'standard-char)))
1417                           line)))
1418           (when ch
1419             (error "non-STANDARD-CHAR ~S found in foreign symbol table:~%~S"
1420                    ch
1421                    line)))
1422         (setf line (string-trim '(#\space) line))
1423         (let ((p1 (position #\space line :from-end nil))
1424               (p2 (position #\space line :from-end t)))
1425           (if (not (and p1 p2 (< p1 p2)))
1426               ;; KLUDGE: It's too messy to try to understand all
1427               ;; possible output from nm, so we just punt the lines we
1428               ;; don't recognize. We realize that there's some chance
1429               ;; that might get us in trouble someday, so we warn
1430               ;; about it.
1431               (warn "ignoring unrecognized line ~S in ~A" line filename)
1432               (multiple-value-bind (value name)
1433                   (if (string= "0x" line :end2 2)
1434                       (values (parse-integer line :start 2 :end p1 :radix 16)
1435                               (subseq line (1+ p2)))
1436                       (values (parse-integer line :end p1 :radix 16)
1437                               (subseq line (1+ p2))))
1438                 (multiple-value-bind (old-value found)
1439                     (gethash name *cold-foreign-symbol-table*)
1440                   (when (and found
1441                              (not (= old-value value)))
1442                     (warn "redefining ~S from #X~X to #X~X"
1443                           name old-value value)))
1444                 (setf (gethash name *cold-foreign-symbol-table*) value))))))
1445     (values)))
1446
1447 ;;; FIXME: the relation between #'lookup-foreign-symbol and
1448 ;;; #'lookup-maybe-prefix-foreign-symbol seems more than slightly
1449 ;;; illdefined
1450
1451 (defun lookup-foreign-symbol (name)
1452   #!+(or alpha x86)
1453   (let ((prefixes
1454          #!+linux #(;; FIXME: How many of these are actually
1455                     ;; needed? The first four are taken from rather
1456                     ;; disorganized CMU CL code, which could easily
1457                     ;; have had redundant values in it..
1458                     "_"
1459                     "__"
1460                     "__libc_"
1461                     "ldso_stub__"
1462                     ;; ..and the fifth seems to match most
1463                     ;; actual symbols, at least in RedHat 6.2.
1464                     "")
1465          #!+freebsd #("" "ldso_stub__")
1466          #!+openbsd #("_")))
1467     (or (some (lambda (prefix)
1468                 (gethash (concatenate 'string prefix name)
1469                          *cold-foreign-symbol-table*
1470                          nil))
1471               prefixes)
1472         *foreign-symbol-placeholder-value*
1473         (progn
1474           (format *error-output* "~&The foreign symbol table is:~%")
1475           (maphash (lambda (k v)
1476                      (format *error-output* "~&~S = #X~8X~%" k v))
1477                    *cold-foreign-symbol-table*)
1478           (format *error-output* "~&The prefix table is: ~S~%" prefixes)
1479           (error "The foreign symbol ~S is undefined." name))))
1480   #!-(or x86 alpha) (error "non-x86/alpha unsupported in SBCL (but see old CMU CL code)"))
1481
1482 (defvar *cold-assembler-routines*)
1483
1484 (defvar *cold-assembler-fixups*)
1485
1486 (defun record-cold-assembler-routine (name address)
1487   (/xhow "in RECORD-COLD-ASSEMBLER-ROUTINE" name address)
1488   (push (cons name address)
1489         *cold-assembler-routines*))
1490
1491 (defun record-cold-assembler-fixup (routine
1492                                     code-object
1493                                     offset
1494                                     &optional
1495                                     (kind :both))
1496   (push (list routine code-object offset kind)
1497         *cold-assembler-fixups*))
1498
1499 (defun lookup-assembler-reference (symbol)
1500   (let ((value (cdr (assoc symbol *cold-assembler-routines*))))
1501     ;; FIXME: Should this be ERROR instead of WARN?
1502     (unless value
1503       (warn "Assembler routine ~S not defined." symbol))
1504     value))
1505
1506 ;;; The x86 port needs to store code fixups along with code objects if
1507 ;;; they are to be moved, so fixups for code objects in the dynamic
1508 ;;; heap need to be noted.
1509 #!+x86
1510 (defvar *load-time-code-fixups*)
1511
1512 #!+x86
1513 (defun note-load-time-code-fixup (code-object offset value kind)
1514   ;; If CODE-OBJECT might be moved
1515   (when (= (gspace-identifier (descriptor-intuit-gspace code-object))
1516            dynamic-space-id)
1517     ;; FIXME: pushed thing should be a structure, not just a list
1518     (push (list code-object offset value kind) *load-time-code-fixups*))
1519   (values))
1520
1521 #!+x86
1522 (defun output-load-time-code-fixups ()
1523   (dolist (fixups *load-time-code-fixups*)
1524     (let ((code-object (first fixups))
1525           (offset (second fixups))
1526           (value (third fixups))
1527           (kind (fourth fixups)))
1528       (cold-push (cold-cons
1529                   (cold-intern :load-time-code-fixup)
1530                   (cold-cons
1531                    code-object
1532                    (cold-cons
1533                     (number-to-core offset)
1534                     (cold-cons
1535                      (number-to-core value)
1536                      (cold-cons
1537                       (cold-intern kind)
1538                       *nil-descriptor*)))))
1539                  *current-reversed-cold-toplevels*))))
1540
1541 ;;; Given a pointer to a code object and an offset relative to the
1542 ;;; tail of the code object's header, return an offset relative to the
1543 ;;; (beginning of the) code object.
1544 ;;;
1545 ;;; FIXME: It might be clearer to reexpress
1546 ;;;    (LET ((X (CALC-OFFSET CODE-OBJECT OFFSET0))) ..)
1547 ;;; as
1548 ;;;    (LET ((X (+ OFFSET0 (CODE-OBJECT-HEADER-N-BYTES CODE-OBJECT)))) ..).
1549 (declaim (ftype (function (descriptor sb!vm:word)) calc-offset))
1550 (defun calc-offset (code-object offset-from-tail-of-header)
1551   (let* ((header (read-memory code-object))
1552          (header-n-words (ash (descriptor-bits header) (- sb!vm:type-bits)))
1553          (header-n-bytes (ash header-n-words sb!vm:word-shift))
1554          (result (+ offset-from-tail-of-header header-n-bytes)))
1555     result))
1556
1557 (declaim (ftype (function (descriptor sb!vm:word sb!vm:word keyword))
1558                 do-cold-fixup))
1559 (defun do-cold-fixup (code-object after-header value kind)
1560   (let* ((offset-within-code-object (calc-offset code-object after-header))
1561          (gspace-bytes (descriptor-bytes code-object))
1562          (gspace-byte-offset (+ (descriptor-byte-offset code-object)
1563                                 offset-within-code-object))
1564          (gspace-byte-address (gspace-byte-address
1565                                (descriptor-gspace code-object))))
1566     (ecase +backend-fasl-file-implementation+
1567       ;; See CMU CL source for other formerly-supported architectures
1568       ;; (and note that you have to rewrite them to use VECTOR-REF
1569       ;; unstead of SAP-REF).
1570       (:alpha
1571          (ecase kind
1572          (:jmp-hint
1573           (assert (zerop (ldb (byte 2 0) value)))
1574           #+nil ;; was commented out in cmucl source too.  Don't know what
1575           ;; it does   -dan 2001.05.03
1576             (setf (sap-ref-16 sap 0)
1577                 (logior (sap-ref-16 sap 0) (ldb (byte 14 0) (ash value -2)))))
1578          (:bits-63-48
1579           (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
1580                  (value (if (logbitp 31 value) (+ value (ash 1 32)) value))
1581                  (value (if (logbitp 47 value) (+ value (ash 1 48)) value)))
1582             (setf (byte-vector-ref-8 gspace-bytes gspace-byte-offset)
1583                   (ldb (byte 8 48) value)
1584                   (byte-vector-ref-8 gspace-bytes (1+ gspace-byte-offset))
1585                   (ldb (byte 8 56) value))))
1586          (:bits-47-32
1587           (let* ((value (if (logbitp 15 value) (+ value (ash 1 16)) value))
1588                  (value (if (logbitp 31 value) (+ value (ash 1 32)) value)))
1589             (setf (byte-vector-ref-8 gspace-bytes gspace-byte-offset)
1590                   (ldb (byte 8 32) value)
1591                   (byte-vector-ref-8 gspace-bytes (1+ gspace-byte-offset))
1592                   (ldb (byte 8 40) value))))
1593          (:ldah
1594           (let ((value (if (logbitp 15 value) (+ value (ash 1 16)) value)))
1595             (setf (byte-vector-ref-8 gspace-bytes gspace-byte-offset)
1596                   (ldb (byte 8 16) value)
1597                   (byte-vector-ref-8 gspace-bytes (1+ gspace-byte-offset))
1598                   (ldb (byte 8 24) value))))
1599          (:lda
1600           (setf (byte-vector-ref-8 gspace-bytes gspace-byte-offset)
1601                 (ldb (byte 8 0) value)
1602                 (byte-vector-ref-8 gspace-bytes (1+ gspace-byte-offset))
1603                 (ldb (byte 8 8) value)))))
1604       (:x86
1605        (let* ((un-fixed-up (byte-vector-ref-32 gspace-bytes
1606                                                gspace-byte-offset))
1607               (code-object-start-addr (logandc2 (descriptor-bits code-object)
1608                                                 sb!vm:lowtag-mask)))
1609          (assert (= code-object-start-addr
1610                   (+ gspace-byte-address
1611                      (descriptor-byte-offset code-object))))
1612          (ecase kind
1613            (:absolute
1614             (let ((fixed-up (+ value un-fixed-up)))
1615               (setf (byte-vector-ref-32 gspace-bytes gspace-byte-offset)
1616                     fixed-up)
1617               ;; comment from CMU CL sources:
1618               ;;
1619               ;; Note absolute fixups that point within the object.
1620               ;; KLUDGE: There seems to be an implicit assumption in
1621               ;; the old CMU CL code here, that if it doesn't point
1622               ;; before the object, it must point within the object
1623               ;; (not beyond it). It would be good to add an
1624               ;; explanation of why that's true, or an assertion that
1625               ;; it's really true, or both.
1626               (unless (< fixed-up code-object-start-addr)
1627                 (note-load-time-code-fixup code-object
1628                                            after-header
1629                                            value
1630                                            kind))))
1631            (:relative ; (used for arguments to X86 relative CALL instruction)
1632             (let ((fixed-up (- (+ value un-fixed-up)
1633                                gspace-byte-address
1634                                gspace-byte-offset
1635                                sb!vm:word-bytes))) ; length of CALL argument
1636               (setf (byte-vector-ref-32 gspace-bytes gspace-byte-offset)
1637                     fixed-up)
1638               ;; Note relative fixups that point outside the code
1639               ;; object, which is to say all relative fixups, since
1640               ;; relative addressing within a code object never needs
1641               ;; a fixup.
1642               (note-load-time-code-fixup code-object
1643                                          after-header
1644                                          value
1645                                          kind)))))) ))
1646   (values))
1647
1648 (defun resolve-assembler-fixups ()
1649   (dolist (fixup *cold-assembler-fixups*)
1650     (let* ((routine (car fixup))
1651            (value (lookup-assembler-reference routine)))
1652       (when value
1653         (do-cold-fixup (second fixup) (third fixup) value (fourth fixup))))))
1654
1655 (defun linkage-info-to-core ()
1656   (let ((result *nil-descriptor*))
1657     (maphash #'(lambda (symbol value)
1658                  (cold-push (cold-cons (string-to-core symbol)
1659                                        (number-to-core value))
1660                             result))
1661              *cold-foreign-symbol-table*)
1662     (cold-set (cold-intern '*!initial-foreign-symbols*) result))
1663   (let ((result *nil-descriptor*))
1664     (dolist (rtn *cold-assembler-routines*)
1665       (cold-push (cold-cons (cold-intern (car rtn))
1666                             (number-to-core (cdr rtn)))
1667                  result))
1668     (cold-set (cold-intern '*!initial-assembler-routines*) result)))
1669 \f
1670 ;;;; general machinery for cold-loading FASL files
1671
1672 (defvar *cold-fop-functions* (replace (make-array 256) *fop-functions*)
1673   #!+sb-doc
1674   "FOP functions for cold loading")
1675
1676 (defvar *normal-fop-functions*)
1677
1678 ;;; Cause a fop to have a special definition for cold load.
1679 ;;; 
1680 ;;; This is similar to DEFINE-FOP, but unlike DEFINE-FOP, this version
1681 ;;;   (1) looks up the code for this name (created by a previous
1682 ;;        DEFINE-FOP) instead of creating a code, and
1683 ;;;   (2) stores its definition in the *COLD-FOP-FUNCTIONS* vector,
1684 ;;;       instead of storing in the *FOP-FUNCTIONS* vector.
1685 (defmacro define-cold-fop ((name &optional (pushp t)) &rest forms)
1686   (aver (member pushp '(nil t :nope)))
1687   (let ((code (get name 'fop-code))
1688         (fname (symbolicate "COLD-" name)))
1689     (unless code
1690       (error "~S is not a defined FOP." name))
1691     `(progn
1692        (defun ,fname ()
1693          ,@(if (eq pushp :nope)
1694              forms
1695              `((with-fop-stack ,pushp ,@forms))))
1696        (setf (svref *cold-fop-functions* ,code) #',fname))))
1697
1698 (defmacro clone-cold-fop ((name &optional (pushp t)) (small-name) &rest forms)
1699   (aver (member pushp '(nil t :nope)))
1700   `(progn
1701     (macrolet ((clone-arg () '(read-arg 4)))
1702       (define-cold-fop (,name ,pushp) ,@forms))
1703     (macrolet ((clone-arg () '(read-arg 1)))
1704       (define-cold-fop (,small-name ,pushp) ,@forms))))
1705
1706 ;;; Cause a fop to be undefined in cold load.
1707 (defmacro not-cold-fop (name)
1708   `(define-cold-fop (,name)
1709      (error "The fop ~S is not supported in cold load." ',name)))
1710
1711 ;;; COLD-LOAD loads stuff into the core image being built by calling
1712 ;;; LOAD-AS-FASL with the fop function table rebound to a table of cold
1713 ;;; loading functions.
1714 (defun cold-load (filename)
1715   #!+sb-doc
1716   "Load the file named by FILENAME into the cold load image being built."
1717   (let* ((*normal-fop-functions* *fop-functions*)
1718          (*fop-functions* *cold-fop-functions*)
1719          (*cold-load-filename* (etypecase filename
1720                                  (string filename)
1721                                  (pathname (namestring filename)))))
1722     (with-open-file (s filename :element-type '(unsigned-byte 8))
1723       (load-as-fasl s nil nil))))
1724 \f
1725 ;;;; miscellaneous cold fops
1726
1727 (define-cold-fop (fop-misc-trap) *unbound-marker*)
1728
1729 (define-cold-fop (fop-character)
1730   (make-character-descriptor (read-arg 3)))
1731 (define-cold-fop (fop-short-character)
1732   (make-character-descriptor (read-arg 1)))
1733
1734 (define-cold-fop (fop-empty-list) *nil-descriptor*)
1735 (define-cold-fop (fop-truth) (cold-intern t))
1736
1737 (define-cold-fop (fop-normal-load :nope)
1738   (setq *fop-functions* *normal-fop-functions*))
1739
1740 (define-fop (fop-maybe-cold-load 82 :nope)
1741   (when *cold-load-filename*
1742     (setq *fop-functions* *cold-fop-functions*)))
1743
1744 (define-cold-fop (fop-maybe-cold-load :nope))
1745
1746 (clone-cold-fop (fop-struct)
1747                 (fop-small-struct)
1748   (let* ((size (clone-arg))
1749          (result (allocate-boxed-object *dynamic*
1750                                         (1+ size)
1751                                         sb!vm:instance-pointer-type)))
1752     (write-memory result (make-other-immediate-descriptor
1753                           size
1754                           sb!vm:instance-header-type))
1755     (do ((index (1- size) (1- index)))
1756         ((minusp index))
1757       (declare (fixnum index))
1758       (write-wordindexed result
1759                          (+ index sb!vm:instance-slots-offset)
1760                          (pop-stack)))
1761     result))
1762
1763 (define-cold-fop (fop-layout)
1764   (let* ((length-des (pop-stack))
1765          (depthoid-des (pop-stack))
1766          (cold-inherits (pop-stack))
1767          (name (pop-stack))
1768          (old (gethash name *cold-layouts*)))
1769     (declare (type descriptor length-des depthoid-des cold-inherits))
1770     (declare (type symbol name))
1771     ;; If a layout of this name has been defined already
1772     (if old
1773       ;; Enforce consistency between the previous definition and the
1774       ;; current definition, then return the previous definition.
1775       (destructuring-bind
1776           ;; FIXME: This would be more maintainable if we used
1777           ;; DEFSTRUCT (:TYPE LIST) to define COLD-LAYOUT. -- WHN 19990825
1778           (old-layout-descriptor
1779            old-name
1780            old-length
1781            old-inherits-list
1782            old-depthoid)
1783           old
1784         (declare (type descriptor old-layout-descriptor))
1785         (declare (type index old-length))
1786         (declare (type fixnum old-depthoid))
1787         (declare (type list old-inherits-list))
1788         (aver (eq name old-name))
1789         (let ((length (descriptor-fixnum length-des))
1790               (inherits-list (listify-cold-inherits cold-inherits))
1791               (depthoid (descriptor-fixnum depthoid-des)))
1792           (unless (= length old-length)
1793             (error "cold loading a reference to class ~S when the compile~%~
1794                    time length was ~S and current length is ~S"
1795                    name
1796                    length
1797                    old-length))
1798           (unless (equal inherits-list old-inherits-list)
1799             (error "cold loading a reference to class ~S when the compile~%~
1800                    time inherits were ~S~%~
1801                    and current inherits are ~S"
1802                    name
1803                    inherits-list
1804                    old-inherits-list))
1805           (unless (= depthoid old-depthoid)
1806             (error "cold loading a reference to class ~S when the compile~%~
1807                    time inheritance depthoid was ~S and current inheritance~%~
1808                    depthoid is ~S"
1809                    name
1810                    depthoid
1811                    old-depthoid)))
1812         old-layout-descriptor)
1813       ;; Make a new definition from scratch.
1814       (make-cold-layout name length-des cold-inherits depthoid-des))))
1815 \f
1816 ;;;; cold fops for loading symbols
1817
1818 ;;; Load a symbol SIZE characters long from *FASL-INPUT-STREAM* and intern
1819 ;;; that symbol in PACKAGE.
1820 (defun cold-load-symbol (size package)
1821   (let ((string (make-string size)))
1822     (read-string-as-bytes *fasl-input-stream* string)
1823     (cold-intern (intern string package) package)))
1824
1825 (macrolet ((frob (name pname-len package-len)
1826              `(define-cold-fop (,name)
1827                 (let ((index (read-arg ,package-len)))
1828                   (push-fop-table
1829                    (cold-load-symbol (read-arg ,pname-len)
1830                                      (svref *current-fop-table* index)))))))
1831   (frob fop-symbol-in-package-save 4 4)
1832   (frob fop-small-symbol-in-package-save 1 4)
1833   (frob fop-symbol-in-byte-package-save 4 1)
1834   (frob fop-small-symbol-in-byte-package-save 1 1))
1835
1836 (clone-cold-fop (fop-lisp-symbol-save)
1837                 (fop-lisp-small-symbol-save)
1838   (push-fop-table (cold-load-symbol (clone-arg) *cl-package*)))
1839
1840 (clone-cold-fop (fop-keyword-symbol-save)
1841                 (fop-keyword-small-symbol-save)
1842   (push-fop-table (cold-load-symbol (clone-arg) *keyword-package*)))
1843
1844 (clone-cold-fop (fop-uninterned-symbol-save)
1845                 (fop-uninterned-small-symbol-save)
1846   (let* ((size (clone-arg))
1847          (name (make-string size)))
1848     (read-string-as-bytes *fasl-input-stream* name)
1849     (let ((symbol (allocate-symbol name)))
1850       (push-fop-table symbol))))
1851 \f
1852 ;;;; cold fops for loading lists
1853
1854 ;;; Make a list of the top LENGTH things on the fop stack. The last
1855 ;;; cdr of the list is set to LAST.
1856 (defmacro cold-stack-list (length last)
1857   `(do* ((index ,length (1- index))
1858          (result ,last (cold-cons (pop-stack) result)))
1859         ((= index 0) result)
1860      (declare (fixnum index))))
1861
1862 (define-cold-fop (fop-list)
1863   (cold-stack-list (read-arg 1) *nil-descriptor*))
1864 (define-cold-fop (fop-list*)
1865   (cold-stack-list (read-arg 1) (pop-stack)))
1866 (define-cold-fop (fop-list-1)
1867   (cold-stack-list 1 *nil-descriptor*))
1868 (define-cold-fop (fop-list-2)
1869   (cold-stack-list 2 *nil-descriptor*))
1870 (define-cold-fop (fop-list-3)
1871   (cold-stack-list 3 *nil-descriptor*))
1872 (define-cold-fop (fop-list-4)
1873   (cold-stack-list 4 *nil-descriptor*))
1874 (define-cold-fop (fop-list-5)
1875   (cold-stack-list 5 *nil-descriptor*))
1876 (define-cold-fop (fop-list-6)
1877   (cold-stack-list 6 *nil-descriptor*))
1878 (define-cold-fop (fop-list-7)
1879   (cold-stack-list 7 *nil-descriptor*))
1880 (define-cold-fop (fop-list-8)
1881   (cold-stack-list 8 *nil-descriptor*))
1882 (define-cold-fop (fop-list*-1)
1883   (cold-stack-list 1 (pop-stack)))
1884 (define-cold-fop (fop-list*-2)
1885   (cold-stack-list 2 (pop-stack)))
1886 (define-cold-fop (fop-list*-3)
1887   (cold-stack-list 3 (pop-stack)))
1888 (define-cold-fop (fop-list*-4)
1889   (cold-stack-list 4 (pop-stack)))
1890 (define-cold-fop (fop-list*-5)
1891   (cold-stack-list 5 (pop-stack)))
1892 (define-cold-fop (fop-list*-6)
1893   (cold-stack-list 6 (pop-stack)))
1894 (define-cold-fop (fop-list*-7)
1895   (cold-stack-list 7 (pop-stack)))
1896 (define-cold-fop (fop-list*-8)
1897   (cold-stack-list 8 (pop-stack)))
1898 \f
1899 ;;;; cold fops for loading vectors
1900
1901 (clone-cold-fop (fop-string)
1902                 (fop-small-string)
1903   (let* ((len (clone-arg))
1904          (string (make-string len)))
1905     (read-string-as-bytes *fasl-input-stream* string)
1906     (string-to-core string)))
1907
1908 (clone-cold-fop (fop-vector)
1909                 (fop-small-vector)
1910   (let* ((size (clone-arg))
1911          (result (allocate-vector-object *dynamic*
1912                                          sb!vm:word-bits
1913                                          size
1914                                          sb!vm:simple-vector-type)))
1915     (do ((index (1- size) (1- index)))
1916         ((minusp index))
1917       (declare (fixnum index))
1918       (write-wordindexed result
1919                          (+ index sb!vm:vector-data-offset)
1920                          (pop-stack)))
1921     result))
1922
1923 (define-cold-fop (fop-int-vector)
1924   (let* ((len (read-arg 4))
1925          (sizebits (read-arg 1))
1926          (type (case sizebits
1927                  (1 sb!vm:simple-bit-vector-type)
1928                  (2 sb!vm:simple-array-unsigned-byte-2-type)
1929                  (4 sb!vm:simple-array-unsigned-byte-4-type)
1930                  (8 sb!vm:simple-array-unsigned-byte-8-type)
1931                  (16 sb!vm:simple-array-unsigned-byte-16-type)
1932                  (32 sb!vm:simple-array-unsigned-byte-32-type)
1933                  (t (error "losing element size: ~D" sizebits))))
1934          (result (allocate-vector-object *dynamic* sizebits len type))
1935          (start (+ (descriptor-byte-offset result)
1936                    (ash sb!vm:vector-data-offset sb!vm:word-shift)))
1937          (end (+ start
1938                  (ceiling (* len sizebits)
1939                           sb!vm:byte-bits))))
1940     (read-sequence-or-die (descriptor-bytes result)
1941                           *fasl-input-stream*
1942                           :start start
1943                           :end end)
1944     result))
1945
1946 (define-cold-fop (fop-single-float-vector)
1947   (let* ((len (read-arg 4))
1948          (result (allocate-vector-object *dynamic*
1949                                          sb!vm:word-bits
1950                                          len
1951                                          sb!vm:simple-array-single-float-type))
1952          (start (+ (descriptor-byte-offset result)
1953                    (ash sb!vm:vector-data-offset sb!vm:word-shift)))
1954          (end (+ start (* len sb!vm:word-bytes))))
1955     (read-sequence-or-die (descriptor-bytes result)
1956                           *fasl-input-stream*
1957                           :start start
1958                           :end end)
1959     result))
1960
1961 (not-cold-fop fop-double-float-vector)
1962 #!+long-float (not-cold-fop fop-long-float-vector)
1963 (not-cold-fop fop-complex-single-float-vector)
1964 (not-cold-fop fop-complex-double-float-vector)
1965 #!+long-float (not-cold-fop fop-complex-long-float-vector)
1966
1967 (define-cold-fop (fop-array)
1968   (let* ((rank (read-arg 4))
1969          (data-vector (pop-stack))
1970          (result (allocate-boxed-object *dynamic*
1971                                         (+ sb!vm:array-dimensions-offset rank)
1972                                         sb!vm:other-pointer-type)))
1973     (write-memory result
1974                   (make-other-immediate-descriptor rank
1975                                                    sb!vm:simple-array-type))
1976     (write-wordindexed result sb!vm:array-fill-pointer-slot *nil-descriptor*)
1977     (write-wordindexed result sb!vm:array-data-slot data-vector)
1978     (write-wordindexed result sb!vm:array-displacement-slot *nil-descriptor*)
1979     (write-wordindexed result sb!vm:array-displaced-p-slot *nil-descriptor*)
1980     (let ((total-elements 1))
1981       (dotimes (axis rank)
1982         (let ((dim (pop-stack)))
1983           (unless (or (= (descriptor-lowtag dim) sb!vm:even-fixnum-type)
1984                       (= (descriptor-lowtag dim) sb!vm:odd-fixnum-type))
1985             (error "non-fixnum dimension? (~S)" dim))
1986           (setf total-elements
1987                 (* total-elements
1988                    (logior (ash (descriptor-high dim)
1989                                 (- descriptor-low-bits (1- sb!vm:lowtag-bits)))
1990                            (ash (descriptor-low dim)
1991                                 (- 1 sb!vm:lowtag-bits)))))
1992           (write-wordindexed result
1993                              (+ sb!vm:array-dimensions-offset axis)
1994                              dim)))
1995       (write-wordindexed result
1996                          sb!vm:array-elements-slot
1997                          (make-fixnum-descriptor total-elements)))
1998     result))
1999 \f
2000 ;;;; cold fops for loading numbers
2001
2002 (defmacro define-cold-number-fop (fop)
2003   `(define-cold-fop (,fop :nope)
2004      ;; Invoke the ordinary warm version of this fop to push the
2005      ;; number.
2006      (,fop)
2007      ;; Replace the warm fop result with the cold image of the warm
2008      ;; fop result.
2009      (with-fop-stack t
2010        (let ((number (pop-stack)))
2011          (number-to-core number)))))
2012
2013 (define-cold-number-fop fop-single-float)
2014 (define-cold-number-fop fop-double-float)
2015 (define-cold-number-fop fop-integer)
2016 (define-cold-number-fop fop-small-integer)
2017 (define-cold-number-fop fop-word-integer)
2018 (define-cold-number-fop fop-byte-integer)
2019 (define-cold-number-fop fop-complex-single-float)
2020 (define-cold-number-fop fop-complex-double-float)
2021
2022 #!+long-float
2023 (define-cold-fop (fop-long-float)
2024   (ecase +backend-fasl-file-implementation+
2025     (:x86 ; (which has 80-bit long-float format)
2026      (prepare-for-fast-read-byte *fasl-input-stream*
2027        (let* ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
2028                                             (1- sb!vm:long-float-size)
2029                                             sb!vm:long-float-type))
2030               (low-bits (make-random-descriptor (fast-read-u-integer 4)))
2031               (high-bits (make-random-descriptor (fast-read-u-integer 4)))
2032               (exp-bits (make-random-descriptor (fast-read-s-integer 2))))
2033          (done-with-fast-read-byte)
2034          (write-wordindexed des sb!vm:long-float-value-slot low-bits)
2035          (write-wordindexed des (1+ sb!vm:long-float-value-slot) high-bits)
2036          (write-wordindexed des (+ 2 sb!vm:long-float-value-slot) exp-bits)
2037          des)))
2038     ;; This was supported in CMU CL, but isn't currently supported in
2039     ;; SBCL.
2040     #+nil
2041     (#.sb!c:sparc-fasl-file-implementation ; 128 bit long-float format
2042      (prepare-for-fast-read-byte *fasl-input-stream*
2043        (let* ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
2044                                             (1- sb!vm:long-float-size)
2045                                             sb!vm:long-float-type))
2046               (low-bits (make-random-descriptor (fast-read-u-integer 4)))
2047               (mid-bits (make-random-descriptor (fast-read-u-integer 4)))
2048               (high-bits (make-random-descriptor (fast-read-u-integer 4)))
2049               (exp-bits (make-random-descriptor (fast-read-s-integer 4))))
2050          (done-with-fast-read-byte)
2051          (write-wordindexed des sb!vm:long-float-value-slot exp-bits)
2052          (write-wordindexed des (1+ sb!vm:long-float-value-slot) high-bits)
2053          (write-wordindexed des (+ 2 sb!vm:long-float-value-slot) mid-bits)
2054          (write-wordindexed des (+ 3 sb!vm:long-float-value-slot) low-bits)
2055          des)))))
2056
2057 #!+long-float
2058 (define-cold-fop (fop-complex-long-float)
2059   (ecase +backend-fasl-file-implementation+
2060     (:x86 ; (which has 80-bit long-float format)
2061      (prepare-for-fast-read-byte *fasl-input-stream*
2062        (let* ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
2063                                             (1- sb!vm:complex-long-float-size)
2064                                             sb!vm:complex-long-float-type))
2065               (real-low-bits (make-random-descriptor (fast-read-u-integer 4)))
2066               (real-high-bits (make-random-descriptor (fast-read-u-integer 4)))
2067               (real-exp-bits (make-random-descriptor (fast-read-s-integer 2)))
2068               (imag-low-bits (make-random-descriptor (fast-read-u-integer 4)))
2069               (imag-high-bits (make-random-descriptor (fast-read-u-integer 4)))
2070               (imag-exp-bits (make-random-descriptor (fast-read-s-integer 2))))
2071          (done-with-fast-read-byte)
2072          (write-wordindexed des
2073                             sb!vm:complex-long-float-real-slot
2074                             real-low-bits)
2075          (write-wordindexed des
2076                             (1+ sb!vm:complex-long-float-real-slot)
2077                             real-high-bits)
2078          (write-wordindexed des
2079                             (+ 2 sb!vm:complex-long-float-real-slot)
2080                             real-exp-bits)
2081          (write-wordindexed des
2082                             sb!vm:complex-long-float-imag-slot
2083                             imag-low-bits)
2084          (write-wordindexed des
2085                             (1+ sb!vm:complex-long-float-imag-slot)
2086                             imag-high-bits)
2087          (write-wordindexed des
2088                             (+ 2 sb!vm:complex-long-float-imag-slot)
2089                             imag-exp-bits)
2090          des)))
2091     ;; This was supported in CMU CL, but isn't currently supported in SBCL.
2092     #+nil
2093     (#.sb!c:sparc-fasl-file-implementation ; 128 bit long-float format
2094      (prepare-for-fast-read-byte *fasl-input-stream*
2095        (let* ((des (allocate-unboxed-object *dynamic* sb!vm:word-bits
2096                                             (1- sb!vm:complex-long-float-size)
2097                                             sb!vm:complex-long-float-type))
2098               (real-low-bits (make-random-descriptor (fast-read-u-integer 4)))
2099               (real-mid-bits (make-random-descriptor (fast-read-u-integer 4)))
2100               (real-high-bits (make-random-descriptor (fast-read-u-integer 4)))
2101               (real-exp-bits (make-random-descriptor (fast-read-s-integer 4)))
2102               (imag-low-bits (make-random-descriptor (fast-read-u-integer 4)))
2103               (imag-mid-bits (make-random-descriptor (fast-read-u-integer 4)))
2104               (imag-high-bits (make-random-descriptor (fast-read-u-integer 4)))
2105               (imag-exp-bits (make-random-descriptor (fast-read-s-integer 4))))
2106          (done-with-fast-read-byte)
2107          (write-wordindexed des
2108                             sb!vm:complex-long-float-real-slot
2109                             real-exp-bits)
2110          (write-wordindexed des
2111                             (1+ sb!vm:complex-long-float-real-slot)
2112                             real-high-bits)
2113          (write-wordindexed des
2114                             (+ 2 sb!vm:complex-long-float-real-slot)
2115                             real-mid-bits)
2116          (write-wordindexed des
2117                             (+ 3 sb!vm:complex-long-float-real-slot)
2118                             real-low-bits)
2119          (write-wordindexed des
2120                             sb!vm:complex-long-float-real-slot
2121                             imag-exp-bits)
2122          (write-wordindexed des
2123                             (1+ sb!vm:complex-long-float-real-slot)
2124                             imag-high-bits)
2125          (write-wordindexed des
2126                             (+ 2 sb!vm:complex-long-float-real-slot)
2127                             imag-mid-bits)
2128          (write-wordindexed des
2129                             (+ 3 sb!vm:complex-long-float-real-slot)
2130                             imag-low-bits)
2131          des)))))
2132
2133 (define-cold-fop (fop-ratio)
2134   (let ((den (pop-stack)))
2135     (number-pair-to-core (pop-stack) den sb!vm:ratio-type)))
2136
2137 (define-cold-fop (fop-complex)
2138   (let ((im (pop-stack)))
2139     (number-pair-to-core (pop-stack) im sb!vm:complex-type)))
2140 \f
2141 ;;;; cold fops for calling (or not calling)
2142
2143 (not-cold-fop fop-eval)
2144 (not-cold-fop fop-eval-for-effect)
2145
2146 (defvar *load-time-value-counter*)
2147
2148 (define-cold-fop (fop-funcall)
2149   (unless (= (read-arg 1) 0)
2150     (error "You can't FOP-FUNCALL arbitrary stuff in cold load."))
2151   (let ((counter *load-time-value-counter*))
2152     (cold-push (cold-cons
2153                 (cold-intern :load-time-value)
2154                 (cold-cons
2155                  (pop-stack)
2156                  (cold-cons
2157                   (number-to-core counter)
2158                   *nil-descriptor*)))
2159                *current-reversed-cold-toplevels*)
2160     (setf *load-time-value-counter* (1+ counter))
2161     (make-descriptor 0 0 nil counter)))
2162
2163 (defun finalize-load-time-value-noise ()
2164   (cold-set (cold-intern '*!load-time-values*)
2165             (allocate-vector-object *dynamic*
2166                                     sb!vm:word-bits
2167                                     *load-time-value-counter*
2168                                     sb!vm:simple-vector-type)))
2169
2170 (define-cold-fop (fop-funcall-for-effect nil)
2171   (if (= (read-arg 1) 0)
2172       (cold-push (pop-stack)
2173                  *current-reversed-cold-toplevels*)
2174       (error "You can't FOP-FUNCALL arbitrary stuff in cold load.")))
2175 \f
2176 ;;;; cold fops for fixing up circularities
2177
2178 (define-cold-fop (fop-rplaca nil)
2179   (let ((obj (svref *current-fop-table* (read-arg 4)))
2180         (idx (read-arg 4)))
2181     (write-memory (cold-nthcdr idx obj) (pop-stack))))
2182
2183 (define-cold-fop (fop-rplacd nil)
2184   (let ((obj (svref *current-fop-table* (read-arg 4)))
2185         (idx (read-arg 4)))
2186     (write-wordindexed (cold-nthcdr idx obj) 1 (pop-stack))))
2187
2188 (define-cold-fop (fop-svset nil)
2189   (let ((obj (svref *current-fop-table* (read-arg 4)))
2190         (idx (read-arg 4)))
2191     (write-wordindexed obj
2192                    (+ idx
2193                       (ecase (descriptor-lowtag obj)
2194                         (#.sb!vm:instance-pointer-type 1)
2195                         (#.sb!vm:other-pointer-type 2)))
2196                    (pop-stack))))
2197
2198 (define-cold-fop (fop-structset nil)
2199   (let ((obj (svref *current-fop-table* (read-arg 4)))
2200         (idx (read-arg 4)))
2201     (write-wordindexed obj (1+ idx) (pop-stack))))
2202
2203 (define-cold-fop (fop-nthcdr t)
2204   (cold-nthcdr (read-arg 4) (pop-stack)))
2205
2206 (defun cold-nthcdr (index obj)
2207   (dotimes (i index)
2208     (setq obj (read-wordindexed obj 1)))
2209   obj)
2210 \f
2211 ;;;; cold fops for loading code objects and functions
2212
2213 (define-cold-fop (fop-fset nil)
2214   (let ((fn (pop-stack))
2215         (name (pop-stack)))
2216     (cold-fset name fn)))
2217
2218 (define-cold-fop (fop-fdefinition)
2219   (cold-fdefinition-object (pop-stack)))
2220
2221 (define-cold-fop (fop-sanctify-for-execution)
2222   (pop-stack))
2223
2224 (not-cold-fop fop-make-byte-compiled-function)
2225
2226 ;;; Setting this variable shows what code looks like before any
2227 ;;; fixups (or function headers) are applied.
2228 #!+sb-show (defvar *show-pre-fixup-code-p* nil)
2229
2230 ;;; FIXME: The logic here should be converted into a function
2231 ;;; COLD-CODE-FOP-GUTS (NCONST CODE-SIZE) called by DEFINE-COLD-FOP
2232 ;;; FOP-CODE and DEFINE-COLD-FOP FOP-SMALL-CODE, so that
2233 ;;; variable-capture nastiness like (LET ((NCONST ,NCONST) ..) ..)
2234 ;;; doesn't keep me awake at night.
2235 (defmacro define-cold-code-fop (name nconst code-size)
2236   `(define-cold-fop (,name)
2237      (let* ((nconst ,nconst)
2238             (code-size ,code-size)
2239             (raw-header-n-words (+ sb!vm:code-trace-table-offset-slot nconst))
2240             (header-n-words
2241              ;; Note: we round the number of constants up to ensure
2242              ;; that the code vector will be properly aligned.
2243              (round-up raw-header-n-words 2))
2244             (des (allocate-descriptor
2245                   ;; In the X86 with CGC, code can't be relocated, so
2246                   ;; we have to put it into static space. In all other
2247                   ;; configurations, code can go into dynamic space.
2248                   #!+(and x86 cgc) *static* ; KLUDGE: Why? -- WHN 19990907
2249                   #!-(and x86 cgc) *dynamic*
2250                   (+ (ash header-n-words sb!vm:word-shift) code-size)
2251                   sb!vm:other-pointer-type)))
2252        (write-memory des
2253                      (make-other-immediate-descriptor header-n-words
2254                                                       sb!vm:code-header-type))
2255        (write-wordindexed des
2256                           sb!vm:code-code-size-slot
2257                           (make-fixnum-descriptor
2258                            (ash (+ code-size (1- (ash 1 sb!vm:word-shift)))
2259                                 (- sb!vm:word-shift))))
2260        (write-wordindexed des sb!vm:code-entry-points-slot *nil-descriptor*)
2261        (write-wordindexed des sb!vm:code-debug-info-slot (pop-stack))
2262        (when (oddp raw-header-n-words)
2263          (write-wordindexed des
2264                             raw-header-n-words
2265                             (make-random-descriptor 0)))
2266        (do ((index (1- raw-header-n-words) (1- index)))
2267            ((< index sb!vm:code-trace-table-offset-slot))
2268          (write-wordindexed des index (pop-stack)))
2269        (let* ((start (+ (descriptor-byte-offset des)
2270                         (ash header-n-words sb!vm:word-shift)))
2271               (end (+ start code-size)))
2272          (read-sequence-or-die (descriptor-bytes des)
2273                                *fasl-input-stream*
2274                                :start start
2275                                :end end)
2276          #!+sb-show
2277          (when *show-pre-fixup-code-p*
2278            (format *trace-output*
2279                    "~&/raw code from code-fop ~D ~D:~%"
2280                    nconst
2281                    code-size)
2282            (do ((i start (+ i sb!vm:word-bytes)))
2283                ((>= i end))
2284              (format *trace-output*
2285                      "/#X~8,'0x: #X~8,'0x~%"
2286                      (+ i (gspace-byte-address (descriptor-gspace des)))
2287                      (byte-vector-ref-32 (descriptor-bytes des) i)))))
2288        des)))
2289
2290 (define-cold-code-fop fop-code (read-arg 4) (read-arg 4))
2291
2292 (define-cold-code-fop fop-small-code (read-arg 1) (read-arg 2))
2293
2294 (clone-cold-fop (fop-alter-code nil)
2295                 (fop-byte-alter-code)
2296   (let ((slot (clone-arg))
2297         (value (pop-stack))
2298         (code (pop-stack)))
2299     (write-wordindexed code slot value)))
2300
2301 (define-cold-fop (fop-function-entry)
2302   (let* ((type (pop-stack))
2303          (arglist (pop-stack))
2304          (name (pop-stack))
2305          (code-object (pop-stack))
2306          (offset (calc-offset code-object (read-arg 4)))
2307          (fn (descriptor-beyond code-object
2308                                 offset
2309                                 sb!vm:function-pointer-type))
2310          (next (read-wordindexed code-object sb!vm:code-entry-points-slot)))
2311     (unless (zerop (logand offset sb!vm:lowtag-mask))
2312       ;; FIXME: This should probably become a fatal error.
2313       (warn "unaligned function entry: ~S at #X~X" name offset))
2314     (write-wordindexed code-object sb!vm:code-entry-points-slot fn)
2315     (write-memory fn
2316                   (make-other-immediate-descriptor (ash offset
2317                                                         (- sb!vm:word-shift))
2318                                                    sb!vm:function-header-type))
2319     (write-wordindexed fn
2320                        sb!vm:function-self-slot
2321                        ;; KLUDGE: Wiring decisions like this in at
2322                        ;; this level ("if it's an x86") instead of a
2323                        ;; higher level of abstraction ("if it has such
2324                        ;; and such relocation peculiarities (which
2325                        ;; happen to be confined to the x86)") is bad.
2326                        ;; It would be nice if the code were instead
2327                        ;; conditional on some more descriptive
2328                        ;; feature, :STICKY-CODE or
2329                        ;; :LOAD-GC-INTERACTION or something.
2330                        ;;
2331                        ;; FIXME: The X86 definition of the function
2332                        ;; self slot breaks everything object.tex says
2333                        ;; about it. (As far as I can tell, the X86
2334                        ;; definition makes it a pointer to the actual
2335                        ;; code instead of a pointer back to the object
2336                        ;; itself.) Ask on the mailing list whether
2337                        ;; this is documented somewhere, and if not,
2338                        ;; try to reverse engineer some documentation
2339                        ;; before release.
2340                        #!-x86
2341                        ;; a pointer back to the function object, as
2342                        ;; described in CMU CL
2343                        ;; src/docs/internals/object.tex
2344                        fn
2345                        #!+x86
2346                        ;; KLUDGE: a pointer to the actual code of the
2347                        ;; object, as described nowhere that I can find
2348                        ;; -- WHN 19990907
2349                        (make-random-descriptor
2350                         (+ (descriptor-bits fn)
2351                            (- (ash sb!vm:function-code-offset sb!vm:word-shift)
2352                               ;; FIXME: We should mask out the type
2353                               ;; bits, not assume we know what they
2354                               ;; are and subtract them out this way.
2355                               sb!vm:function-pointer-type))))
2356     (write-wordindexed fn sb!vm:function-next-slot next)
2357     (write-wordindexed fn sb!vm:function-name-slot name)
2358     (write-wordindexed fn sb!vm:function-arglist-slot arglist)
2359     (write-wordindexed fn sb!vm:function-type-slot type)
2360     fn))
2361
2362 (define-cold-fop (fop-foreign-fixup)
2363   (let* ((kind (pop-stack))
2364          (code-object (pop-stack))
2365          (len (read-arg 1))
2366          (sym (make-string len)))
2367     (read-string-as-bytes *fasl-input-stream* sym)
2368     (let ((offset (read-arg 4))
2369           (value (lookup-foreign-symbol sym)))
2370       (do-cold-fixup code-object offset value kind))
2371     code-object))
2372
2373 (define-cold-fop (fop-assembler-code)
2374   (let* ((length (read-arg 4))
2375          (header-n-words
2376           ;; Note: we round the number of constants up to ensure that
2377           ;; the code vector will be properly aligned.
2378           (round-up sb!vm:code-constants-offset 2))
2379          (des (allocate-descriptor *read-only*
2380                                    (+ (ash header-n-words sb!vm:word-shift)
2381                                       length)
2382                                    sb!vm:other-pointer-type)))
2383     (write-memory des
2384                   (make-other-immediate-descriptor header-n-words
2385                                                    sb!vm:code-header-type))
2386     (write-wordindexed des
2387                        sb!vm:code-code-size-slot
2388                        (make-fixnum-descriptor
2389                         (ash (+ length (1- (ash 1 sb!vm:word-shift)))
2390                              (- sb!vm:word-shift))))
2391     (write-wordindexed des sb!vm:code-entry-points-slot *nil-descriptor*)
2392     (write-wordindexed des sb!vm:code-debug-info-slot *nil-descriptor*)
2393
2394     (let* ((start (+ (descriptor-byte-offset des)
2395                      (ash header-n-words sb!vm:word-shift)))
2396            (end (+ start length)))
2397       (read-sequence-or-die (descriptor-bytes des)
2398                             *fasl-input-stream*
2399                             :start start
2400                             :end end))
2401     des))
2402
2403 (define-cold-fop (fop-assembler-routine)
2404   (let* ((routine (pop-stack))
2405          (des (pop-stack))
2406          (offset (calc-offset des (read-arg 4))))
2407     (record-cold-assembler-routine
2408      routine
2409      (+ (logandc2 (descriptor-bits des) sb!vm:lowtag-mask) offset))
2410     des))
2411
2412 (define-cold-fop (fop-assembler-fixup)
2413   (let* ((routine (pop-stack))
2414          (kind (pop-stack))
2415          (code-object (pop-stack))
2416          (offset (read-arg 4)))
2417     (record-cold-assembler-fixup routine code-object offset kind)
2418     code-object))
2419
2420 (define-cold-fop (fop-code-object-fixup)
2421   (let* ((kind (pop-stack))
2422          (code-object (pop-stack))
2423          (offset (read-arg 4))
2424          (value (descriptor-bits code-object)))
2425     (do-cold-fixup code-object offset value kind)
2426     code-object))
2427 \f
2428 ;;;; emitting C header file
2429
2430 (defun tail-comp (string tail)
2431   (and (>= (length string) (length tail))
2432        (string= string tail :start1 (- (length string) (length tail)))))
2433
2434 (defun head-comp (string head)
2435   (and (>= (length string) (length head))
2436        (string= string head :end1 (length head))))
2437
2438 (defun write-c-header ()
2439
2440   ;; writing beginning boilerplate
2441   (format t "/*~%")
2442   (dolist (line
2443            '("This is a machine-generated file. Do not edit it by hand."
2444              ""
2445              "This file contains low-level information about the"
2446              "internals of a particular version and configuration"
2447              "of SBCL. It is used by the C compiler to create a runtime"
2448              "support environment, an executable program in the host"
2449              "operating system's native format, which can then be used to"
2450              "load and run 'core' files, which are basically programs"
2451              "in SBCL's own format."))
2452     (format t " * ~A~%" line))
2453   (format t " */~%")
2454   (terpri)
2455   (format t "#ifndef _SBCL_H_~%#define _SBCL_H_~%")
2456   (terpri)
2457
2458   ;; writing miscellaneous constants
2459   (format t "#define SBCL_CORE_VERSION_INTEGER ~D~%" sbcl-core-version-integer)
2460   (format t
2461           "#define SBCL_VERSION_STRING ~S~%"
2462           (sb!xc:lisp-implementation-version))
2463   (format t "#define CORE_MAGIC 0x~X~%" core-magic)
2464   (terpri)
2465   ;; FIXME: Other things from core.h should be defined here too:
2466   ;; #define CORE_END 3840
2467   ;; #define CORE_NDIRECTORY 3861
2468   ;; #define CORE_VALIDATE 3845
2469   ;; #define CORE_VERSION 3860
2470   ;; #define CORE_MACHINE_STATE 3862
2471   ;; (Except that some of them are obsolete and should be deleted instead.)
2472   ;; also
2473   ;; #define DYNAMIC_SPACE_ID (1)
2474   ;; #define STATIC_SPACE_ID (2)
2475   ;; #define READ_ONLY_SPACE_ID (3)
2476
2477   ;; writing entire families of named constants from SB!VM
2478   (let ((constants nil))
2479     (do-external-symbols (symbol (find-package "SB!VM"))
2480       (when (constantp symbol)
2481         (let ((name (symbol-name symbol)))
2482           (labels (;; shared machinery
2483                    (record (string priority)
2484                      (push (list string
2485                                  priority
2486                                  (symbol-value symbol)
2487                                  (documentation symbol 'variable))
2488                            constants))
2489                    ;; machinery for old-style CMU CL Lisp-to-C naming
2490                    (record-with-munged-name (prefix string priority)
2491                      (record (concatenate
2492                               'simple-string
2493                               prefix
2494                               (delete #\- (string-capitalize string)))
2495                              priority))
2496                    (test-tail (tail prefix priority)
2497                      (when (tail-comp name tail)
2498                        (record-with-munged-name prefix
2499                                                 (subseq name 0
2500                                                         (- (length name)
2501                                                            (length tail)))
2502                                                 priority)))
2503                    (test-head (head prefix priority)
2504                      (when (head-comp name head)
2505                        (record-with-munged-name prefix
2506                                                 (subseq name (length head))
2507                                                 priority)))
2508                    ;; machinery for new-style SBCL Lisp-to-C naming
2509                    (record-with-translated-name (priority)
2510                      (record (substitute #\_ #\- name)
2511                              priority)))
2512             ;; This style of munging of names is used in the code
2513             ;; inherited from CMU CL.
2514             (test-tail "-TYPE" "type_" 0)
2515             (test-tail "-FLAG" "flag_" 1)
2516             (test-tail "-TRAP" "trap_" 2)
2517             (test-tail "-SUBTYPE" "subtype_" 3)
2518             (test-head "TRACE-TABLE-" "tracetab_" 4)
2519             (test-tail "-SC-NUMBER" "sc_" 5)
2520             ;; This simpler style of translation of names seems less
2521             ;; confusing, and is used for newer code.
2522             (when (some (lambda (suffix) (tail-comp name suffix))
2523                         #("-START" "-END"))
2524               (record-with-translated-name 6))))))
2525     (setf constants
2526           (sort constants
2527                 #'(lambda (const1 const2)
2528                     (if (= (second const1) (second const2))
2529                       (< (third const1) (third const2))
2530                       (< (second const1) (second const2))))))
2531     (let ((prev-priority (second (car constants))))
2532       (dolist (const constants)
2533         (destructuring-bind (name priority value doc) const
2534           (unless (= prev-priority priority)
2535             (terpri)
2536             (setf prev-priority priority))
2537           (format t "#define ~A " name)
2538           (format t 
2539                   ;; KLUDGE: As of sbcl-0.6.7.14, we're dumping two
2540                   ;; different kinds of values here, (1) small codes
2541                   ;; and (2) machine addresses. The small codes can be
2542                   ;; dumped as bare integer values. The large machine
2543                   ;; addresses might cause problems if they're large
2544                   ;; and represented as (signed) C integers, so we
2545                   ;; want to force them to be unsigned. We do that by
2546                   ;; wrapping them in the LISPOBJ macro. (We could do
2547                   ;; it with a bare "(unsigned)" cast, except that
2548                   ;; this header file is used not only in C files, but
2549                   ;; also in assembly files, which don't understand
2550                   ;; the cast syntax. The LISPOBJ macro goes away in
2551                   ;; assembly files, but that shouldn't matter because
2552                   ;; we don't do arithmetic on address constants in
2553                   ;; assembly files. See? It really is a kludge..) --
2554                   ;; WHN 2000-10-18
2555                   (let (;; cutoff for treatment as a small code
2556                         (cutoff (expt 2 16)))
2557                     (cond ((minusp value)
2558                            (error "stub: negative values unsupported"))
2559                           ((< value cutoff)
2560                            "~D")
2561                           (t
2562                            "LISPOBJ(~D)")))
2563                   value)
2564           (format t " /* 0x~X */~@[  /* ~A */~]~%" value doc))))
2565     (terpri))
2566
2567   ;; writing codes/strings for internal errors
2568   (format t "#define ERRORS { \\~%")
2569   ;; FIXME: Is this just DO-VECTOR?
2570   (let ((internal-errors sb!c:*backend-internal-errors*))
2571     (dotimes (i (length internal-errors))
2572       (format t "    ~S, /*~D*/ \\~%" (cdr (aref internal-errors i)) i)))
2573   (format t "    NULL \\~%}~%")
2574   (terpri)
2575
2576   ;; writing primitive object layouts
2577   (let ((structs (sort (copy-list sb!vm:*primitive-objects*) #'string<
2578                        :key #'(lambda (obj)
2579                                 (symbol-name
2580                                  (sb!vm:primitive-object-name obj))))))
2581     (format t "#ifndef LANGUAGE_ASSEMBLY~2%")
2582     (format t "#define LISPOBJ(x) ((lispobj)x)~2%")
2583     (dolist (obj structs)
2584       (format t
2585               "struct ~A {~%"
2586               (nsubstitute #\_ #\-
2587               (string-downcase (string (sb!vm:primitive-object-name obj)))))
2588       (when (sb!vm:primitive-object-header obj)
2589         (format t "    lispobj header;~%"))
2590       (dolist (slot (sb!vm:primitive-object-slots obj))
2591         (format t "    ~A ~A~@[[1]~];~%"
2592         (getf (sb!vm:slot-options slot) :c-type "lispobj")
2593         (nsubstitute #\_ #\-
2594                      (string-downcase (string (sb!vm:slot-name slot))))
2595         (sb!vm:slot-rest-p slot)))
2596       (format t "};~2%"))
2597     (format t "#else /* LANGUAGE_ASSEMBLY */~2%")
2598     (format t "#define LISPOBJ(thing) thing~2%")
2599     (dolist (obj structs)
2600       (let ((name (sb!vm:primitive-object-name obj))
2601       (lowtag (eval (sb!vm:primitive-object-lowtag obj))))
2602         (when lowtag
2603         (dolist (slot (sb!vm:primitive-object-slots obj))
2604           (format t "#define ~A_~A_OFFSET ~D~%"
2605                   (substitute #\_ #\- (string name))
2606                   (substitute #\_ #\- (string (sb!vm:slot-name slot)))
2607                   (- (* (sb!vm:slot-offset slot) sb!vm:word-bytes) lowtag)))
2608         (terpri))))
2609     (format t "#endif /* LANGUAGE_ASSEMBLY */~2%"))
2610
2611   ;; writing static symbol offsets
2612   (dolist (symbol (cons nil sb!vm:*static-symbols*))
2613     ;; FIXME: It would be nice to use longer names NIL and (particularly) T
2614     ;; in #define statements.
2615     (format t "#define ~A LISPOBJ(0x~X)~%"
2616             (nsubstitute #\_ #\-
2617                          (remove-if #'(lambda (char)
2618                                         (member char '(#\% #\* #\. #\!)))
2619                                     (symbol-name symbol)))
2620             (if *static*                ; if we ran GENESIS
2621               ;; We actually ran GENESIS, use the real value.
2622               (descriptor-bits (cold-intern symbol))
2623               ;; We didn't run GENESIS, so guess at the address.
2624               (+ sb!vm:static-space-start
2625                  sb!vm:word-bytes
2626                  sb!vm:other-pointer-type
2627                  (if symbol (sb!vm:static-symbol-offset symbol) 0)))))
2628
2629   ;; Voila.
2630   (format t "~%#endif~%"))
2631 \f
2632 ;;;; writing map file
2633
2634 ;;; Write a map file describing the cold load. Some of this
2635 ;;; information is subject to change due to relocating GC, but even so
2636 ;;; it can be very handy when attempting to troubleshoot the early
2637 ;;; stages of cold load.
2638 (defun write-map ()
2639   (let ((*print-pretty* nil)
2640         (*print-case* :upcase))
2641     (format t "assembler routines defined in core image:~2%")
2642     (dolist (routine (sort (copy-list *cold-assembler-routines*) #'<
2643                            :key #'cdr))
2644       (format t "#X~8,'0X: ~S~%" (cdr routine) (car routine)))
2645     (let ((funs nil)
2646           (undefs nil))
2647       (maphash #'(lambda (name fdefn)
2648                    (let ((fun (read-wordindexed fdefn
2649                                                 sb!vm:fdefn-function-slot)))
2650                      (if (= (descriptor-bits fun)
2651                             (descriptor-bits *nil-descriptor*))
2652                          (push name undefs)
2653                          (let ((addr (read-wordindexed fdefn
2654                                                        sb!vm:fdefn-raw-addr-slot)))
2655                            (push (cons name (descriptor-bits addr))
2656                                  funs)))))
2657                *cold-fdefn-objects*)
2658       (format t "~%~|~%initially defined functions:~2%")
2659       (dolist (info (sort funs #'< :key #'cdr))
2660         (format t "0x~8,'0X: ~S   #X~8,'0X~%" (cdr info) (car info)
2661                 (- (cdr info) #x17)))
2662       (format t
2663 "~%~|
2664 (a note about initially undefined function references: These functions
2665 are referred to by code which is installed by GENESIS, but they are not
2666 installed by GENESIS. This is not necessarily a problem; functions can
2667 be defined later, by cold init toplevel forms, or in files compiled and
2668 loaded at warm init, or elsewhere. As long as they are defined before
2669 they are called, everything should be OK. Things are also OK if the
2670 cross-compiler knew their inline definition and used that everywhere
2671 that they were called before the out-of-line definition is installed,
2672 as is fairly common for structure accessors.)
2673 initially undefined function references:~2%")
2674       (labels ((key (name)
2675                  (etypecase name
2676                    (symbol (symbol-name name))
2677                    ;; FIXME: should use standard SETF-function parsing logic
2678                    (list (key (second name))))))
2679         (dolist (name (sort undefs #'string< :key #'key))
2680           (format t "~S" name)
2681           ;; FIXME: This ACCESSOR-FOR stuff should go away when the
2682           ;; code has stabilized. (It's only here to help me
2683           ;; categorize the flood of undefined functions caused by
2684           ;; completely rewriting the bootstrap process. Hopefully any
2685           ;; future maintainers will mostly have small numbers of
2686           ;; undefined functions..)
2687           (let ((accessor-for (info :function :accessor-for name)))
2688             (when accessor-for
2689               (format t " (accessor for ~S)" accessor-for)))
2690           (format t "~%")))))
2691
2692   (format t "~%~|~%layout names:~2%")
2693   (collect ((stuff))
2694     (maphash #'(lambda (name gorp)
2695                  (declare (ignore name))
2696                  (stuff (cons (descriptor-bits (car gorp))
2697                               (cdr gorp))))
2698              *cold-layouts*)
2699     (dolist (x (sort (stuff) #'< :key #'car))
2700       (apply #'format t "~8,'0X: ~S[~D]~%~10T~S~%" x)))
2701
2702   (values))
2703 \f
2704 ;;;; writing core file
2705
2706 (defvar *core-file*)
2707 (defvar *data-page*)
2708
2709 ;;; KLUDGE: These numbers correspond to values in core.h. If they're
2710 ;;; documented anywhere, I haven't found it. (I haven't tried very
2711 ;;; hard yet.) -- WHN 19990826
2712 (defparameter version-entry-type-code 3860)
2713 (defparameter validate-entry-type-code 3845)
2714 (defparameter directory-entry-type-code 3841)
2715 (defparameter new-directory-entry-type-code 3861)
2716 (defparameter initial-function-entry-type-code 3863)
2717 (defparameter end-entry-type-code 3840)
2718
2719 (declaim (ftype (function (sb!vm:word) sb!vm:word) write-long))
2720 (defun write-long (num) ; FIXME: WRITE-WORD would be a better name.
2721   (ecase sb!c:*backend-byte-order*
2722     (:little-endian
2723      (dotimes (i 4)
2724        (write-byte (ldb (byte 8 (* i 8)) num) *core-file*)))
2725     (:big-endian
2726      (dotimes (i 4)
2727        (write-byte (ldb (byte 8 (* (- 3 i) 8)) num) *core-file*))))
2728   num)
2729
2730 (defun advance-to-page ()
2731   (force-output *core-file*)
2732   (file-position *core-file*
2733                  (round-up (file-position *core-file*)
2734                            sb!c:*backend-page-size*)))
2735
2736 (defun output-gspace (gspace)
2737   (force-output *core-file*)
2738   (let* ((posn (file-position *core-file*))
2739          (bytes (* (gspace-free-word-index gspace) sb!vm:word-bytes))
2740          (pages (ceiling bytes sb!c:*backend-page-size*))
2741          (total-bytes (* pages sb!c:*backend-page-size*)))
2742
2743     (file-position *core-file*
2744                    (* sb!c:*backend-page-size* (1+ *data-page*)))
2745     (format t
2746             "writing ~S byte~:P [~S page~:P] from ~S~%"
2747             total-bytes
2748             pages
2749             gspace)
2750     (force-output)
2751
2752     ;; Note: It is assumed that the GSPACE allocation routines always
2753     ;; allocate whole pages (of size *target-page-size*) and that any
2754     ;; empty gspace between the free pointer and the end of page will
2755     ;; be zero-filled. This will always be true under Mach on machines
2756     ;; where the page size is equal. (RT is 4K, PMAX is 4K, Sun 3 is
2757     ;; 8K).
2758     (write-sequence (gspace-bytes gspace) *core-file* :end total-bytes)
2759     (force-output *core-file*)
2760     (file-position *core-file* posn)
2761
2762     ;; Write part of a (new) directory entry which looks like this:
2763     ;;   GSPACE IDENTIFIER
2764     ;;   WORD COUNT
2765     ;;   DATA PAGE
2766     ;;   ADDRESS
2767     ;;   PAGE COUNT
2768     (write-long (gspace-identifier gspace))
2769     (write-long (gspace-free-word-index gspace))
2770     (write-long *data-page*)
2771     (multiple-value-bind (floor rem)
2772         (floor (gspace-byte-address gspace) sb!c:*backend-page-size*)
2773       (aver (zerop rem))
2774       (write-long floor))
2775     (write-long pages)
2776
2777     (incf *data-page* pages)))
2778
2779 ;;; Create a core file created from the cold loaded image. (This is
2780 ;;; the "initial core file" because core files could be created later
2781 ;;; by executing SAVE-LISP in a running system, perhaps after we've
2782 ;;; added some functionality to the system.)
2783 (declaim (ftype (function (string)) write-initial-core-file))
2784 (defun write-initial-core-file (filename)
2785
2786   (let ((filenamestring (namestring filename))
2787         (*data-page* 0))
2788
2789     (format t
2790             "[building initial core file in ~S: ~%"
2791             filenamestring)
2792     (force-output)
2793
2794     (with-open-file (*core-file* filenamestring
2795                                  :direction :output
2796                                  :element-type '(unsigned-byte 8)
2797                                  :if-exists :rename-and-delete)
2798
2799       ;; Write the magic number.
2800       (write-long core-magic)
2801
2802       ;; Write the Version entry.
2803       (write-long version-entry-type-code)
2804       (write-long 3)
2805       (write-long sbcl-core-version-integer)
2806
2807       ;; Write the New Directory entry header.
2808       (write-long new-directory-entry-type-code)
2809       (write-long 17) ; length = (5 words/space) * 3 spaces + 2 for header.
2810
2811       (output-gspace *read-only*)
2812       (output-gspace *static*)
2813       (output-gspace *dynamic*)
2814
2815       ;; Write the initial function.
2816       (write-long initial-function-entry-type-code)
2817       (write-long 3)
2818       (let* ((cold-name (cold-intern '!cold-init))
2819              (cold-fdefn (cold-fdefinition-object cold-name))
2820              (initial-function (read-wordindexed cold-fdefn
2821                                                  sb!vm:fdefn-function-slot)))
2822         (format t
2823                 "~&/(DESCRIPTOR-BITS INITIAL-FUNCTION)=#X~X~%"
2824                 (descriptor-bits initial-function))
2825         (write-long (descriptor-bits initial-function)))
2826
2827       ;; Write the End entry.
2828       (write-long end-entry-type-code)
2829       (write-long 2)))
2830
2831   (format t "done]~%")
2832   (force-output)
2833   (/show "leaving WRITE-INITIAL-CORE-FILE")
2834   (values))
2835 \f
2836 ;;;; the actual GENESIS function
2837
2838 ;;; Read the FASL files in OBJECT-FILE-NAMES and produce a Lisp core,
2839 ;;; and/or information about a Lisp core, therefrom.
2840 ;;;
2841 ;;; input file arguments:
2842 ;;;   SYMBOL-TABLE-FILE-NAME names a UNIX-style .nm file *with* *any*
2843 ;;;     *tab* *characters* *converted* *to* *spaces*. (We push
2844 ;;;     responsibility for removing tabs out to the caller it's
2845 ;;;     trivial to remove them using UNIX command line tools like
2846 ;;;     sed, whereas it's a headache to do it portably in Lisp because
2847 ;;;     #\TAB is not a STANDARD-CHAR.) If this file is not supplied,
2848 ;;;     a core file cannot be built (but a C header file can be).
2849 ;;;
2850 ;;; output files arguments (any of which may be NIL to suppress output):
2851 ;;;   CORE-FILE-NAME gets a Lisp core.
2852 ;;;   C-HEADER-FILE-NAME gets a C header file, traditionally called
2853 ;;;     internals.h, which is used by the C compiler when constructing
2854 ;;;     the executable which will load the core.
2855 ;;;   MAP-FILE-NAME gets (?) a map file. (dunno about this -- WHN 19990815)
2856 ;;;
2857 ;;; other arguments:
2858 ;;;   BYTE-ORDER-SWAP-P controls whether GENESIS tries to swap bytes
2859 ;;;     in some places in the output. It's only appropriate when
2860 ;;;     cross-compiling from a machine with one byte order to a
2861 ;;;     machine with the opposite byte order, which is irrelevant in
2862 ;;;     current (19990816) SBCL, since only the X86 architecture is
2863 ;;;     supported. If you're trying to add support for more
2864 ;;;     architectures, see the comments on DEFVAR
2865 ;;;     *GENESIS-BYTE-ORDER-SWAP-P* for more information.
2866 ;;;
2867 ;;; FIXME: GENESIS doesn't belong in SB!VM. Perhaps in %KERNEL for now,
2868 ;;; perhaps eventually in SB-LD or SB-BOOT.
2869 (defun sb!vm:genesis (&key
2870                       object-file-names
2871                       symbol-table-file-name
2872                       core-file-name
2873                       map-file-name
2874                       c-header-file-name
2875                       byte-order-swap-p)
2876
2877   (when (and core-file-name
2878              (not symbol-table-file-name))
2879     (error "can't output a core file without symbol table file input"))
2880
2881   (format t
2882           "~&beginning GENESIS, ~A~%"
2883           (if core-file-name
2884             ;; Note: This output summarizing what we're doing is
2885             ;; somewhat telegraphic in style, not meant to imply that
2886             ;; we're not e.g. also creating a header file when we
2887             ;; create a core.
2888             (format nil "creating core ~S" core-file-name)
2889             (format nil "creating header ~S" c-header-file-name)))
2890
2891   (let* ((*cold-foreign-symbol-table* (make-hash-table :test 'equal)))
2892
2893     ;; Read symbol table, if any.
2894     (when symbol-table-file-name
2895       (load-foreign-symbol-table symbol-table-file-name))
2896
2897     ;; Now that we've successfully read our only input file (by
2898     ;; loading the symbol table, if any), it's a good time to ensure
2899     ;; that there'll be someplace for our output files to go when
2900     ;; we're done.
2901     (flet ((frob (filename)
2902              (when filename
2903                (ensure-directories-exist filename :verbose t))))
2904       (frob core-file-name)
2905       (frob map-file-name)
2906       (frob c-header-file-name))
2907
2908     ;; (This shouldn't matter in normal use, since GENESIS normally
2909     ;; only runs once in any given Lisp image, but it could reduce
2910     ;; confusion if we ever experiment with running, tweaking, and
2911     ;; rerunning genesis interactively.)
2912     (do-all-symbols (sym)
2913       (remprop sym 'cold-intern-info))
2914
2915     (let* ((*foreign-symbol-placeholder-value* (if core-file-name nil 0))
2916            (*load-time-value-counter* 0)
2917            (*genesis-byte-order-swap-p* byte-order-swap-p)
2918            (*cold-fdefn-objects* (make-hash-table :test 'equal))
2919            (*cold-symbols* (make-hash-table :test 'equal))
2920            (*cold-package-symbols* nil)
2921            (*read-only* (make-gspace :read-only
2922                                      read-only-space-id
2923                                      sb!vm:read-only-space-start))
2924            (*static*    (make-gspace :static
2925                                      static-space-id
2926                                      sb!vm:static-space-start))
2927            (*dynamic*   (make-gspace :dynamic
2928                                      dynamic-space-id
2929                                      sb!vm:dynamic-space-start))
2930            (*nil-descriptor* (make-nil-descriptor))
2931            (*current-reversed-cold-toplevels* *nil-descriptor*)
2932            (*unbound-marker* (make-other-immediate-descriptor
2933                               0
2934                               sb!vm:unbound-marker-type))
2935            *cold-assembler-fixups*
2936            *cold-assembler-routines*
2937            #!+x86 *load-time-code-fixups*)
2938
2939       ;; Prepare for cold load.
2940       (initialize-non-nil-symbols)
2941       (initialize-layouts)
2942       (initialize-static-fns)
2943
2944       ;; Initialize the *COLD-SYMBOLS* system with the information
2945       ;; from package-data-list.lisp-expr and
2946       ;; common-lisp-exports.lisp-expr.
2947       ;;
2948       ;; Why do things this way? Historically, the *COLD-SYMBOLS*
2949       ;; machinery was designed and implemented in CMU CL long before
2950       ;; I (WHN) ever heard of CMU CL. It dumped symbols and packages
2951       ;; iff they were used in the cold image. When I added the
2952       ;; package-data-list.lisp-expr mechanism, the idea was to
2953       ;; centralize all information about packages and exports. Thus,
2954       ;; it was the natural place for information even about packages
2955       ;; (such as SB!PCL and SB!WALKER) which aren't used much until
2956       ;; after cold load. This didn't quite match the CMU CL approach
2957       ;; of filling *COLD-SYMBOLS* with symbols which appear in the
2958       ;; cold image and then dumping only those symbols. By explicitly
2959       ;; putting all the symbols from package-data-list.lisp-expr and
2960       ;; from common-lisp-exports.lisp-expr into *COLD-SYMBOLS* here,
2961       ;; we feed our centralized symbol information into the old CMU
2962       ;; CL code without having to change the old CMU CL code too
2963       ;; much. (And the old CMU CL code is still useful for making
2964       ;; sure that the appropriate keywords and internal symbols end
2965       ;; up interned in the target Lisp, which is good, e.g. in order
2966       ;; to make &KEY arguments work right and in order to make
2967       ;; BACKTRACEs into target Lisp system code be legible.)
2968       (dolist (exported-name
2969                (sb-cold:read-from-file "common-lisp-exports.lisp-expr"))
2970         (cold-intern (intern exported-name *cl-package*)))
2971       (dolist (pd (sb-cold:read-from-file "package-data-list.lisp-expr"))
2972         (declare (type sb-cold:package-data pd))
2973         (let ((package (find-package (sb-cold:package-data-name pd))))
2974           (labels (;; Call FN on every node of the TREE.
2975                    (mapc-on-tree (fn tree)
2976                                  (typecase tree
2977                                    (cons (mapc-on-tree fn (car tree))
2978                                          (mapc-on-tree fn (cdr tree)))
2979                                    (t (funcall fn tree)
2980                                       (values))))
2981                    ;; Make sure that information about the association
2982                    ;; between PACKAGE and the symbol named NAME gets
2983                    ;; recorded in the cold-intern system or (as a
2984                    ;; convenience when dealing with the tree structure
2985                    ;; allowed in the PACKAGE-DATA-EXPORTS slot) do
2986                    ;; nothing if NAME is NIL.
2987                    (chill (name)
2988                      (when name
2989                        (cold-intern (intern name package) package))))
2990             (mapc-on-tree #'chill (sb-cold:package-data-export pd))
2991             (mapc #'chill (sb-cold:package-data-reexport pd))
2992             (dolist (sublist (sb-cold:package-data-import-from pd))
2993               (destructuring-bind (package-name &rest symbol-names) sublist
2994                 (declare (ignore package-name))
2995                 (mapc #'chill symbol-names))))))
2996
2997       ;; Cold load.
2998       (dolist (file-name object-file-names)
2999         (write-line (namestring file-name))
3000         (cold-load file-name))
3001
3002       ;; Tidy up loose ends left by cold loading. ("Postpare from cold load?")
3003       (resolve-assembler-fixups)
3004       #!+x86 (output-load-time-code-fixups)
3005       (linkage-info-to-core)
3006       (finish-symbols)
3007       (/show "back from FINISH-SYMBOLS")
3008       (finalize-load-time-value-noise)
3009
3010       ;; Tell the target Lisp how much stuff we've allocated.
3011       (cold-set 'sb!vm:*read-only-space-free-pointer*
3012                 (allocate-descriptor *read-only* 0 sb!vm:even-fixnum-type))
3013       (cold-set 'sb!vm:*static-space-free-pointer*
3014                 (allocate-descriptor *static* 0 sb!vm:even-fixnum-type))
3015       (cold-set 'sb!vm:*initial-dynamic-space-free-pointer*
3016                 (allocate-descriptor *dynamic* 0 sb!vm:even-fixnum-type))
3017       (/show "done setting free pointers")
3018
3019       ;; Write results to files.
3020       ;;
3021       ;; FIXME: I dislike this approach of redefining
3022       ;; *STANDARD-OUTPUT* instead of putting the new stream in a
3023       ;; lexical variable, and it's annoying to have WRITE-MAP (to
3024       ;; *STANDARD-OUTPUT*) not be parallel to WRITE-INITIAL-CORE-FILE
3025       ;; (to a stream explicitly passed as an argument).
3026       (when map-file-name
3027         (with-open-file (*standard-output* map-file-name
3028                                            :direction :output
3029                                            :if-exists :supersede)
3030           (write-map)))
3031       (when c-header-file-name
3032         (with-open-file (*standard-output* c-header-file-name
3033                                            :direction :output
3034                                            :if-exists :supersede)
3035           (write-c-header)))
3036       (when core-file-name
3037         (write-initial-core-file core-file-name)))))