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