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