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