Store all assembler routines in one code object
[sbcl.git] / src / compiler / generic / genesis.lisp
blob6fcbb57f767e34c1777de3ebcd9bd9327be5006b
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.)
20 ;;;; This software is part of the SBCL system. See the README file for
21 ;;;; more information.
22 ;;;;
23 ;;;; This software is derived from the CMU CL system, which was
24 ;;;; written at Carnegie Mellon University and released into the
25 ;;;; public domain. The software is in the public domain and is
26 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
27 ;;;; files for more information.
29 (in-package "SB!FASL")
31 ;;; a magic number used to identify our core files
32 (defconstant core-magic
33 (logior (ash (sb!xc:char-code #\S) 24)
34 (ash (sb!xc:char-code #\B) 16)
35 (ash (sb!xc:char-code #\C) 8)
36 (sb!xc:char-code #\L)))
38 (defun round-up (number size)
39 "Round NUMBER up to be an integral multiple of SIZE."
40 (* size (ceiling number size)))
42 ;;;; implementing the concept of "vector" in (almost) portable
43 ;;;; Common Lisp
44 ;;;;
45 ;;;; "If you only need to do such simple things, it doesn't really
46 ;;;; matter which language you use." -- _ANSI Common Lisp_, p. 1, Paul
47 ;;;; Graham (evidently not considering the abstraction "vector" to be
48 ;;;; such a simple thing:-)
50 (eval-when (:compile-toplevel :load-toplevel :execute)
51 (defconstant +smallvec-length+
52 (expt 2 16)))
54 ;;; an element of a BIGVEC -- a vector small enough that we have
55 ;;; a good chance of it being portable to other Common Lisps
56 (deftype smallvec ()
57 `(simple-array (unsigned-byte 8) (,+smallvec-length+)))
59 (defun make-smallvec ()
60 (make-array +smallvec-length+ :element-type '(unsigned-byte 8)
61 :initial-element 0))
63 ;;; a big vector, implemented as a vector of SMALLVECs
64 ;;;
65 ;;; KLUDGE: This implementation seems portable enough for our
66 ;;; purposes, since realistically every modern implementation is
67 ;;; likely to support vectors of at least 2^16 elements. But if you're
68 ;;; masochistic enough to read this far into the contortions imposed
69 ;;; on us by ANSI and the Lisp community, for daring to use the
70 ;;; abstraction of a large linearly addressable memory space, which is
71 ;;; after all only directly supported by the underlying hardware of at
72 ;;; least 99% of the general-purpose computers in use today, then you
73 ;;; may be titillated to hear that in fact this code isn't really
74 ;;; portable, because as of sbcl-0.7.4 we need somewhat more than
75 ;;; 16Mbytes to represent a core, and ANSI only guarantees that
76 ;;; ARRAY-DIMENSION-LIMIT is not less than 1024. -- WHN 2002-06-13
77 (defstruct bigvec
78 (outer-vector (vector (make-smallvec)) :type (vector smallvec)))
80 ;;; analogous to SVREF, but into a BIGVEC
81 (defun bvref (bigvec index)
82 (multiple-value-bind (outer-index inner-index)
83 (floor index +smallvec-length+)
84 (aref (the smallvec
85 (svref (bigvec-outer-vector bigvec) outer-index))
86 inner-index)))
87 (defun (setf bvref) (new-value bigvec index)
88 (multiple-value-bind (outer-index inner-index)
89 (floor index +smallvec-length+)
90 (setf (aref (the smallvec
91 (svref (bigvec-outer-vector bigvec) outer-index))
92 inner-index)
93 new-value)))
95 ;;; analogous to LENGTH, but for a BIGVEC
96 ;;;
97 ;;; the length of BIGVEC, measured in the number of BVREFable bytes it
98 ;;; can hold
99 (defun bvlength (bigvec)
100 (* (length (bigvec-outer-vector bigvec))
101 +smallvec-length+))
103 ;;; analogous to WRITE-SEQUENCE, but for a BIGVEC
104 (defun write-bigvec-as-sequence (bigvec stream &key (start 0) end pad-with-zeros)
105 (let* ((bvlength (bvlength bigvec))
106 (data-length (min (or end bvlength) bvlength)))
107 (loop for i of-type index from start below data-length do
108 (write-byte (bvref bigvec i)
109 stream))
110 (when (and pad-with-zeros (< bvlength data-length))
111 (loop repeat (- data-length bvlength) do (write-byte 0 stream)))))
113 ;;; analogous to READ-SEQUENCE-OR-DIE, but for a BIGVEC
114 (defun read-bigvec-as-sequence-or-die (bigvec stream &key (start 0) end)
115 (loop for i of-type index from start below (or end (bvlength bigvec)) do
116 (setf (bvref bigvec i)
117 (read-byte stream))))
119 ;;; Grow BIGVEC (exponentially, so that large increases in size have
120 ;;; asymptotic logarithmic cost per byte).
121 (defun expand-bigvec (bigvec)
122 (let* ((old-outer-vector (bigvec-outer-vector bigvec))
123 (length-old-outer-vector (length old-outer-vector))
124 (new-outer-vector (make-array (* 2 length-old-outer-vector))))
125 (replace new-outer-vector old-outer-vector)
126 (loop for i from length-old-outer-vector below (length new-outer-vector) do
127 (setf (svref new-outer-vector i)
128 (make-smallvec)))
129 (setf (bigvec-outer-vector bigvec)
130 new-outer-vector))
131 bigvec)
133 ;;;; looking up bytes and multi-byte values in a BIGVEC (considering
134 ;;;; it as an image of machine memory on the cross-compilation target)
136 ;;; BVREF-32 and friends. These are like SAP-REF-n, except that
137 ;;; instead of a SAP we use a BIGVEC.
138 (macrolet ((make-bvref-n (n)
139 (let ((name (intern (format nil "BVREF-~A" n)))
140 (le-octet-indices
141 (loop with n-octets = (/ n 8)
142 for i from 0 below n-octets
143 collect `(+ byte-index #!+big-endian ,(- n-octets i 1)
144 #!-big-endian ,i))))
145 `(progn
146 (defun ,name (bigvec byte-index)
147 (logior ,@(loop for index in le-octet-indices
148 for i from 0
149 collect `(ash (bvref bigvec ,index) ,(* i 8)))))
150 (defun (setf ,name) (new-value bigvec byte-index)
151 ;; We don't carefully distinguish between signed and unsigned,
152 ;; since there's only one setter function per byte size.
153 (declare (type (or (signed-byte ,n) (unsigned-byte ,n))
154 new-value))
155 (setf ,@(loop for index in le-octet-indices
156 for i from 0
157 append `((bvref bigvec ,index)
158 (ldb (byte 8 ,(* i 8)) new-value)))))))))
159 (make-bvref-n 8)
160 (make-bvref-n 16)
161 (make-bvref-n 32)
162 (make-bvref-n 64))
164 ;; lispobj-sized word, whatever that may be
165 ;; hopefully nobody ever wants a 128-bit SBCL...
166 (macrolet ((acc (bv index) `(#!+64-bit bvref-64 #!-64-bit bvref-32 ,bv ,index)))
167 (defun (setf bvref-word) (new-val bytes index) (setf (acc bytes index) new-val))
168 (defun bvref-word (bytes index) (acc bytes index)))
170 ;;;; representation of spaces in the core
172 ;;; If there is more than one dynamic space in memory (i.e., if a
173 ;;; copying GC is in use), then only the active dynamic space gets
174 ;;; dumped to core.
175 (defvar *dynamic*)
176 (defconstant dynamic-core-space-id 1)
178 (defvar *static*)
179 (defconstant static-core-space-id 2)
181 (defvar *read-only*)
182 (defconstant read-only-core-space-id 3)
184 #!+immobile-space
185 (progn
186 (defvar *immobile-fixedobj*)
187 (defvar *immobile-varyobj*)
188 (defconstant immobile-fixedobj-core-space-id 4)
189 (defconstant immobile-varyobj-core-space-id 5)
190 (defvar *immobile-space-map* nil))
192 (defconstant max-core-space-id (+ 3 #!+immobile-space 2))
193 (defconstant deflated-core-space-id-flag 8)
195 ;;; a GENESIS-time representation of a memory space (e.g. read-only
196 ;;; space, dynamic space, or static space)
197 (defstruct (gspace (:constructor %make-gspace)
198 (:copier nil))
199 ;; name and identifier for this GSPACE
200 (name (missing-arg) :type symbol :read-only t)
201 (identifier (missing-arg) :type fixnum :read-only t)
202 ;; the word address where the data will be loaded
203 (word-address (missing-arg) :type unsigned-byte :read-only t)
204 ;; the gspace contents as a BIGVEC
205 (data (make-bigvec) :type bigvec :read-only t)
206 ;; the index of the next unwritten word (i.e. chunk of
207 ;; SB!VM:N-WORD-BYTES bytes) in DATA, or equivalently the number of
208 ;; words actually written in DATA. In order to convert to an actual
209 ;; index into DATA, thus must be multiplied by SB!VM:N-WORD-BYTES.
210 (free-word-index 0))
212 (defun gspace-byte-address (gspace)
213 (ash (gspace-word-address gspace) sb!vm:word-shift))
215 (cl:defmethod print-object ((gspace gspace) stream)
216 (print-unreadable-object (gspace stream :type t)
217 (format stream "@#x~X ~S" (gspace-byte-address gspace) (gspace-name gspace))))
219 (defun make-gspace (name identifier byte-address)
220 ;; Genesis should be agnostic of space alignment except in so far as it must
221 ;; be a multiple of the backend page size. We used to care more, in that
222 ;; descriptor-bits were composed of a high half and low half for the
223 ;; questionable motive of caring about fixnum-ness of the halves,
224 ;; despite the wonderful abstraction INTEGER that transparently becomes
225 ;; a BIGNUM if the host's fixnum is limited in size.
226 ;; So it's not clear whether this test belongs here, because if we do need it,
227 ;; then it best belongs where we assign space addresses in the first place.
228 (let ((target-space-alignment sb!c:+backend-page-bytes+))
229 (unless (zerop (rem byte-address target-space-alignment))
230 (error "The byte address #X~X is not aligned on a #X~X-byte boundary."
231 byte-address target-space-alignment)))
232 (%make-gspace :name name
233 :identifier identifier
234 :word-address (ash byte-address (- sb!vm:word-shift))))
236 ;;;; representation of descriptors
238 (declaim (inline is-fixnum-lowtag))
239 (defun is-fixnum-lowtag (lowtag)
240 (zerop (logand lowtag sb!vm:fixnum-tag-mask)))
242 (defun is-other-immediate-lowtag (lowtag)
243 ;; The other-immediate lowtags are similar to the fixnum lowtags, in
244 ;; that they have an "effective length" that is shorter than is used
245 ;; for the pointer lowtags. Unlike the fixnum lowtags, however, the
246 ;; other-immediate lowtags are always effectively two bits wide.
247 (= (logand lowtag 3) sb!vm:other-immediate-0-lowtag))
249 (defstruct (descriptor
250 (:constructor make-descriptor (bits &optional gspace word-offset))
251 (:copier nil))
252 ;; the GSPACE that this descriptor is allocated in, or NIL if not set yet.
253 (gspace nil :type (or gspace (eql :load-time-value) null))
254 ;; the offset in words from the start of GSPACE, or NIL if not set yet
255 (word-offset nil :type (or sb!vm:word null))
256 (bits 0 :read-only t :type (unsigned-byte #.sb!vm:n-machine-word-bits)))
258 (declaim (inline descriptor=))
259 (defun descriptor= (a b) (eql (descriptor-bits a) (descriptor-bits b)))
261 (defun make-random-descriptor (bits)
262 (make-descriptor (logand bits sb!ext:most-positive-word)))
264 (declaim (inline descriptor-lowtag))
265 (defun descriptor-lowtag (des)
266 "the lowtag bits for DES"
267 (logand (descriptor-bits des) sb!vm:lowtag-mask))
269 (defmethod print-object ((des descriptor) stream)
270 (let ((gspace (descriptor-gspace des))
271 (bits (descriptor-bits des))
272 (lowtag (descriptor-lowtag des)))
273 (print-unreadable-object (des stream :type t)
274 (cond ((eq gspace :load-time-value)
275 (format stream "for LTV ~D" (descriptor-word-offset des)))
276 ((is-fixnum-lowtag lowtag)
277 (format stream "for fixnum: ~W" (descriptor-fixnum des)))
278 ((is-other-immediate-lowtag lowtag)
279 (format stream
280 "for other immediate: #X~X, type #b~8,'0B"
281 (ash bits (- sb!vm:n-widetag-bits))
282 (logand bits sb!vm:widetag-mask)))
284 (format stream
285 "for pointer: #X~X, lowtag #b~v,'0B, ~A"
286 (logandc2 bits sb!vm:lowtag-mask)
287 sb!vm:n-lowtag-bits lowtag
288 (if gspace (gspace-name gspace) "unknown")))))))
290 ;;; Return a descriptor for a block of LENGTH bytes out of GSPACE. The
291 ;;; free word index is boosted as necessary, and if additional memory
292 ;;; is needed, we grow the GSPACE. The descriptor returned is a
293 ;;; pointer of type LOWTAG.
294 (defun allocate-cold-descriptor (gspace length lowtag &optional page-attributes)
295 (let* ((word-index
296 (gspace-claim-n-bytes gspace length page-attributes))
297 (ptr (+ (gspace-word-address gspace) word-index)))
298 (make-descriptor (logior (ash ptr sb!vm:word-shift) lowtag)
299 gspace
300 word-index)))
302 (defun gspace-claim-n-words (gspace n-words)
303 (let* ((old-free-word-index (gspace-free-word-index gspace))
304 (new-free-word-index (+ old-free-word-index n-words)))
305 ;; Grow GSPACE as necessary until it's big enough to handle
306 ;; NEW-FREE-WORD-INDEX.
307 (do ()
308 ((>= (bvlength (gspace-data gspace))
309 (* new-free-word-index sb!vm:n-word-bytes)))
310 (expand-bigvec (gspace-data gspace)))
311 ;; Now that GSPACE is big enough, we can meaningfully grab a chunk of it.
312 (setf (gspace-free-word-index gspace) new-free-word-index)
313 old-free-word-index))
315 ;; layoutp is true if we need to force objects on this page to LAYOUT-ALIGN
316 ;; boundaries. This doesn't need to be generalized - everything of type
317 ;; INSTANCE is either on its natural alignment, or the layout alignment.
318 ;; [See doc/internals-notes/compact-instance for why you might want it at all]
319 ;; PAGE-KIND is a heuristic for placement of symbols
320 ;; based on being interned/uninterned/likely-special-variable.
321 (defun make-page-attributes (layoutp page-kind)
322 (declare (type (or null (integer 0 3)) page-kind))
323 (logior (ash (or page-kind 0) 1) (if layoutp 1 0)))
325 (defun gspace-claim-n-bytes (gspace specified-n-bytes page-attributes)
326 (declare (ignorable page-attributes))
327 (let* ((n-bytes (round-up specified-n-bytes (ash 1 sb!vm:n-lowtag-bits)))
328 (n-words (ash n-bytes (- sb!vm:word-shift))))
329 (aver (evenp n-words))
330 (cond #!+immobile-space
331 ((eq gspace *immobile-fixedobj*)
332 (aver page-attributes)
333 ;; An immobile fixedobj page can only have one value of object-spacing
334 ;; and size for all objects on it. Different widetags are ok.
335 (let* ((key (cons specified-n-bytes page-attributes))
336 (found (cdr (assoc key *immobile-space-map* :test 'equal)))
337 (page-n-words (/ sb!vm:immobile-card-bytes sb!vm:n-word-bytes)))
338 (unless found ; grab one whole GC page from immobile space
339 (let ((free-word-index
340 (gspace-claim-n-words gspace page-n-words)))
341 (setf found (cons 0 free-word-index))
342 (push (cons key found) *immobile-space-map*)))
343 (destructuring-bind (page-word-index . page-base-index) found
344 (let ((next-word
345 (+ page-word-index
346 (if (logbitp 0 page-attributes)
347 (/ sb!vm:layout-align sb!vm:n-word-bytes)
348 n-words))))
349 (if (> next-word (- page-n-words n-words))
350 ;; no more objects fit on this page
351 (setf *immobile-space-map*
352 (delete key *immobile-space-map* :key 'car :test 'equal))
353 (setf (car found) next-word)))
354 (+ page-word-index page-base-index))))
356 (gspace-claim-n-words gspace n-words)))))
358 (defun descriptor-fixnum (des)
359 (unless (is-fixnum-lowtag (descriptor-lowtag des))
360 (error "descriptor-fixnum called on non-fixnum ~S" des))
361 (let* ((descriptor-bits (descriptor-bits des))
362 (bits (ash descriptor-bits (- sb!vm:n-fixnum-tag-bits))))
363 (if (logbitp (1- sb!vm:n-word-bits) descriptor-bits)
364 (logior bits (ash -1 (1+ sb!vm:n-positive-fixnum-bits)))
365 bits)))
367 (defun descriptor-word-sized-integer (des)
368 ;; Extract an (unsigned-byte 32), from either its fixnum or bignum
369 ;; representation.
370 (let ((lowtag (descriptor-lowtag des)))
371 (if (is-fixnum-lowtag lowtag)
372 (make-random-descriptor (descriptor-fixnum des))
373 (read-wordindexed des 1))))
375 ;;; common idioms
376 (defun descriptor-mem (des)
377 (gspace-data (descriptor-intuit-gspace des)))
378 (defun descriptor-byte-offset (des)
379 (ash (descriptor-word-offset des) sb!vm:word-shift))
381 ;;; If DESCRIPTOR-GSPACE is already set, just return that. Otherwise,
382 ;;; figure out a GSPACE which corresponds to DES, set it into
383 ;;; (DESCRIPTOR-GSPACE DES), set a consistent value into
384 ;;; (DESCRIPTOR-WORD-OFFSET DES), and return the GSPACE.
385 (declaim (ftype (function (descriptor) gspace) descriptor-intuit-gspace))
386 (defun descriptor-intuit-gspace (des)
387 (or (descriptor-gspace des)
389 ;; gspace wasn't set, now we have to search for it.
390 (let* ((lowtag (descriptor-lowtag des))
391 (abs-word-addr (ash (- (descriptor-bits des) lowtag)
392 (- sb!vm:word-shift))))
394 ;; Non-pointer objects don't have a gspace.
395 (unless (or (eql lowtag sb!vm:fun-pointer-lowtag)
396 (eql lowtag sb!vm:instance-pointer-lowtag)
397 (eql lowtag sb!vm:list-pointer-lowtag)
398 (eql lowtag sb!vm:other-pointer-lowtag))
399 (error "don't even know how to look for a GSPACE for ~S" des))
401 (dolist (gspace (list *dynamic* *static* *read-only*
402 #!+immobile-space *immobile-fixedobj*
403 #!+immobile-space *immobile-varyobj*)
404 (error "couldn't find a GSPACE for ~S" des))
405 ;; Bounds-check the descriptor against the allocated area
406 ;; within each gspace.
407 (when (and (<= (gspace-word-address gspace)
408 abs-word-addr
409 (+ (gspace-word-address gspace)
410 (gspace-free-word-index gspace))))
411 ;; Update the descriptor with the correct gspace and the
412 ;; offset within the gspace and return the gspace.
413 (setf (descriptor-word-offset des)
414 (- abs-word-addr (gspace-word-address gspace)))
415 (return (setf (descriptor-gspace des) gspace)))))))
417 (defun %fixnum-descriptor-if-possible (num)
418 (and (typep num '(signed-byte #.sb!vm:n-fixnum-bits))
419 (make-random-descriptor (ash num sb!vm:n-fixnum-tag-bits))))
421 (defun make-fixnum-descriptor (num)
422 (or (%fixnum-descriptor-if-possible num)
423 (error "~W is too big for a fixnum." num)))
425 (defun make-other-immediate-descriptor (data type)
426 (make-descriptor (logior (ash data sb!vm:n-widetag-bits) type)))
428 (defun make-character-descriptor (data)
429 (make-other-immediate-descriptor data sb!vm:character-widetag))
432 ;;;; miscellaneous variables and other noise
434 ;;; a numeric value to be returned for undefined foreign symbols, or NIL if
435 ;;; undefined foreign symbols are to be treated as an error.
436 ;;; (In the first pass of GENESIS, needed to create a header file before
437 ;;; the C runtime can be built, various foreign symbols will necessarily
438 ;;; be undefined, but we don't need actual values for them anyway, and
439 ;;; we can just use 0 or some other placeholder. In the second pass of
440 ;;; GENESIS, all foreign symbols should be defined, so any undefined
441 ;;; foreign symbol is a problem.)
443 ;;; KLUDGE: It would probably be cleaner to rewrite GENESIS so that it
444 ;;; never tries to look up foreign symbols in the first place unless
445 ;;; it's actually creating a core file (as in the second pass) instead
446 ;;; of using this hack to allow it to go through the motions without
447 ;;; causing an error. -- WHN 20000825
448 (defvar *foreign-symbol-placeholder-value*)
450 ;;; a handle on the trap object
451 (defvar *unbound-marker*
452 (make-other-immediate-descriptor 0 sb!vm:unbound-marker-widetag))
454 ;;; a handle on the NIL object
455 (defvar *nil-descriptor*)
457 ;;; the head of a list of TOPLEVEL-THINGs describing stuff to be done
458 ;;; when the target Lisp starts up
460 ;;; Each TOPLEVEL-THING can be a function to be executed or a fixup or
461 ;;; loadtime value, represented by (CONS KEYWORD ..).
462 (declaim (special *!cold-toplevels* *!cold-defconstants*
463 *!cold-defuns* *cold-methods*))
466 ;;;; miscellaneous stuff to read and write the core memory
468 ;; Like above, but the list is held in the target's image of the host symbol,
469 ;; not the host's value of the symbol.
470 (defun cold-target-push (cold-thing host-symbol)
471 (cold-set host-symbol (cold-cons cold-thing (cold-symbol-value host-symbol))))
473 (declaim (ftype (function (descriptor sb!vm:word) descriptor) read-wordindexed))
474 (macrolet ((read-bits ()
475 `(bvref-word (descriptor-mem address)
476 (ash (+ index (descriptor-word-offset address))
477 sb!vm:word-shift))))
478 (defun read-bits-wordindexed (address index)
479 (read-bits))
480 (defun read-wordindexed (address index)
481 "Return the value which is displaced by INDEX words from ADDRESS."
482 (make-random-descriptor (read-bits))))
484 (declaim (ftype (function (descriptor) descriptor) read-memory))
485 (defun read-memory (address)
486 "Return the value at ADDRESS."
487 (read-wordindexed address 0))
489 (declaim (ftype (function (descriptor
490 (integer #.(- sb!vm:list-pointer-lowtag)
491 #.sb!ext:most-positive-word)
492 descriptor)
493 (values))
494 note-load-time-value-reference))
495 (defun note-load-time-value-reference (address offset marker)
496 (push (cold-list (cold-intern :load-time-value-fixup)
497 address
498 (number-to-core offset)
499 (number-to-core (descriptor-word-offset marker)))
500 *!cold-toplevels*)
501 (values))
503 (declaim (ftype (function (descriptor sb!vm:word (or symbol descriptor))) write-wordindexed))
504 (macrolet ((write-bits (bits)
505 `(setf (bvref-word (descriptor-mem address)
506 (ash (+ index (descriptor-word-offset address))
507 sb!vm:word-shift))
508 ,bits)))
509 (defun write-wordindexed (address index value)
510 "Write VALUE displaced INDEX words from ADDRESS."
511 ;; If we're passed a symbol as a value then it needs to be interned.
512 (let ((value (cond ((symbolp value) (cold-intern value))
513 (t value))))
514 (if (eql (descriptor-gspace value) :load-time-value)
515 (note-load-time-value-reference address
516 (- (ash index sb!vm:word-shift)
517 (logand (descriptor-bits address)
518 sb!vm:lowtag-mask))
519 value)
520 (write-bits (descriptor-bits value)))))
522 (defun write-wordindexed/raw (address index bits)
523 (declare (type descriptor address) (type sb!vm:word index)
524 (type (or sb!vm:word sb!vm:signed-word) bits))
525 (write-bits (logand bits sb!ext:most-positive-word))))
527 (declaim (ftype (function (descriptor (or symbol descriptor))) write-memory))
528 (defun write-memory (address value)
529 "Write VALUE (a DESCRIPTOR) at ADDRESS (also a DESCRIPTOR)."
530 (write-wordindexed address 0 value))
532 ;;;; allocating images of primitive objects in the cold core
534 (defun write-header-word (des header-data widetag)
535 ;; In immobile space, all objects start life as pseudo-static as if by 'save'.
536 (let ((gen #!+gencgc (if (or #!+immobile-space
537 (let ((gspace (descriptor-gspace des)))
538 (or (eq gspace *immobile-fixedobj*)
539 (eq gspace *immobile-varyobj*))))
540 sb!vm:+pseudo-static-generation+
542 #!-gencgc 0))
543 (write-wordindexed/raw des 0
544 (logior (ash (logior (ash gen 16) header-data)
545 sb!vm:n-widetag-bits) widetag))))
547 (defun set-header-data (object data)
548 (write-header-word object data (ldb (byte sb!vm:n-widetag-bits 0)
549 (read-bits-wordindexed object 0)))
550 object) ; return the object itself, like SB!KERNEL:SET-HEADER-DATA
552 (defun get-header-data (object)
553 (ash (read-bits-wordindexed object 0) (- sb!vm:n-widetag-bits)))
555 ;;; There are three kinds of blocks of memory in the type system:
556 ;;; * Boxed objects (cons cells, structures, etc): These objects have no
557 ;;; header as all slots, or almost all slots, are descriptors.
558 ;;; This also includes code objects, which are mostly non-descriptors.
559 ;;; * Unboxed objects (bignums): There is a single header word that contains
560 ;;; the length.
561 ;;; * Vector objects: There is a header word with the type, then a word for
562 ;;; the length, then the data.
563 (defun allocate-object (gspace length lowtag &optional layoutp)
564 "Allocate LENGTH words in GSPACE and return a new descriptor of type LOWTAG
565 pointing to them."
566 (allocate-cold-descriptor gspace (ash length sb!vm:word-shift) lowtag
567 (make-page-attributes layoutp 0)))
568 (defun allocate-header+object (gspace length widetag)
569 "Allocate LENGTH words plus a header word in GSPACE and
570 return an ``other-pointer'' descriptor to them. Initialize the header word
571 with the resultant length and WIDETAG."
572 (let ((des (allocate-cold-descriptor
573 gspace (ash (1+ length) sb!vm:word-shift)
574 sb!vm:other-pointer-lowtag
575 (make-page-attributes nil 0))))
576 (write-header-word des length widetag)
577 des))
578 (defun allocate-vector-object (gspace element-bits length widetag)
579 "Allocate LENGTH units of ELEMENT-BITS size plus a header plus a length slot in
580 GSPACE and return an ``other-pointer'' descriptor to them. Initialize the
581 header word with WIDETAG and the length slot with LENGTH."
582 ;; ALLOCATE-COLD-DESCRIPTOR will take any rational number of bytes
583 ;; and round up to a double-word. This doesn't need to use CEILING.
584 (let* ((bytes (/ (* element-bits length) sb!vm:n-byte-bits))
585 (des (allocate-cold-descriptor gspace
586 (+ bytes (* 2 sb!vm:n-word-bytes))
587 sb!vm:other-pointer-lowtag)))
588 (write-header-word des 0 widetag)
589 (write-wordindexed des
590 sb!vm:vector-length-slot
591 (make-fixnum-descriptor length))
592 des))
594 ;;; the hosts's representation of LAYOUT-of-LAYOUT
595 (eval-when (:compile-toplevel :load-toplevel :execute)
596 (defvar *host-layout-of-layout* (find-layout 'layout)))
598 (defun cold-layout-length (layout)
599 (descriptor-fixnum (read-slot layout *host-layout-of-layout* :length)))
600 (defun cold-layout-depthoid (layout)
601 (descriptor-fixnum (read-slot layout *host-layout-of-layout* :depthoid)))
603 ;; Make a structure and set the header word and layout.
604 ;; LAYOUT-LENGTH is as returned by the like-named function.
605 (defun allocate-struct
606 (gspace layout &optional (layout-length (cold-layout-length layout))
607 is-layout)
608 ;; Count +1 for the header word when allocating.
609 (let ((des (allocate-object gspace (1+ layout-length)
610 sb!vm:instance-pointer-lowtag is-layout)))
611 ;; Length as stored in the header is the exact number of useful words
612 ;; that follow, as is customary. A padding word, if any is not "useful"
613 (write-header-word des
614 (logior layout-length
615 #!+compact-instance-header
616 (if layout (ash (descriptor-bits layout) 24) 0))
617 sb!vm:instance-widetag)
618 #!-compact-instance-header
619 (write-wordindexed des sb!vm:instance-slots-offset layout)
620 des))
622 ;;;; copying simple objects into the cold core
624 (defun base-string-to-core (string &optional (gspace *dynamic*))
625 "Copy STRING (which must only contain STANDARD-CHARs) into the cold
626 core and return a descriptor to it."
627 ;; (Remember that the system convention for storage of strings leaves an
628 ;; extra null byte at the end to aid in call-out to C.)
629 (let* ((length (length string))
630 (des (allocate-vector-object gspace
631 sb!vm:n-byte-bits
632 (1+ length)
633 sb!vm:simple-base-string-widetag))
634 (bytes (gspace-data gspace))
635 (offset (+ (* sb!vm:vector-data-offset sb!vm:n-word-bytes)
636 (descriptor-byte-offset des))))
637 (write-wordindexed des
638 sb!vm:vector-length-slot
639 (make-fixnum-descriptor length))
640 (dotimes (i length)
641 (setf (bvref bytes (+ offset i))
642 (sb!xc:char-code (aref string i))))
643 (setf (bvref bytes (+ offset length))
644 0) ; null string-termination character for C
645 des))
647 (defun base-string-from-core (descriptor)
648 (let* ((len (descriptor-fixnum
649 (read-wordindexed descriptor sb!vm:vector-length-slot)))
650 (str (make-string len))
651 (bytes (descriptor-mem descriptor)))
652 (dotimes (i len str)
653 (setf (aref str i)
654 (code-char (bvref bytes
655 (+ (descriptor-byte-offset descriptor)
656 (* sb!vm:vector-data-offset sb!vm:n-word-bytes)
657 i)))))))
659 (defun bignum-to-core (n)
660 "Copy a bignum to the cold core."
661 (let* ((words (ceiling (1+ (integer-length n)) sb!vm:n-word-bits))
662 (handle
663 (allocate-header+object *dynamic* words sb!vm:bignum-widetag)))
664 (declare (fixnum words))
665 (do ((index 1 (1+ index))
666 (remainder n (ash remainder (- sb!vm:n-word-bits))))
667 ((> index words)
668 (unless (zerop (integer-length remainder))
669 ;; FIXME: Shouldn't this be a fatal error?
670 (warn "~W words of ~W were written, but ~W bits were left over."
671 words n remainder)))
672 (write-wordindexed/raw handle index
673 (ldb (byte sb!vm:n-word-bits 0) remainder)))
674 handle))
676 (defun bignum-from-core (descriptor)
677 (let ((n-words (ash (descriptor-bits (read-memory descriptor))
678 (- sb!vm:n-widetag-bits)))
679 (val 0))
680 (dotimes (i n-words val)
681 (let ((bits (read-bits-wordindexed descriptor
682 (+ i sb!vm:bignum-digits-offset))))
683 ;; sign-extend the highest word
684 (when (and (= i (1- n-words)) (logbitp (1- sb!vm:n-word-bits) bits))
685 (setq bits (dpb bits (byte sb!vm:n-word-bits 0) -1)))
686 (setq val (logior (ash bits (* i sb!vm:n-word-bits)) val))))))
688 (defun number-pair-to-core (first second type)
689 "Makes a number pair of TYPE (ratio or complex) and fills it in."
690 (let ((des (allocate-header+object *dynamic* 2 type)))
691 (write-wordindexed des 1 first)
692 (write-wordindexed des 2 second)
693 des))
695 (defun write-double-float-bits (address index x)
696 (let ((high-bits (double-float-high-bits x))
697 (low-bits (double-float-low-bits x)))
698 (ecase sb!vm:n-word-bits
700 (ecase sb!c:*backend-byte-order*
701 (:little-endian
702 (write-wordindexed/raw address index low-bits)
703 (write-wordindexed/raw address (1+ index) high-bits))
704 (:big-endian
705 (write-wordindexed/raw address index high-bits)
706 (write-wordindexed/raw address (1+ index) low-bits))))
708 (let ((bits (ecase sb!c:*backend-byte-order*
709 (:little-endian (logior low-bits (ash high-bits 32)))
710 ;; Just guessing.
711 #+nil (:big-endian (logior (logand high-bits #xffffffff)
712 (ash low-bits 32))))))
713 (write-wordindexed/raw address index bits))))
715 address))
717 (defun float-to-core (x)
718 (etypecase x
719 (single-float
720 ;; 64-bit platforms have immediate single-floats.
721 #!+64-bit
722 (make-random-descriptor (logior (ash (single-float-bits x) 32)
723 sb!vm:single-float-widetag))
724 #!-64-bit
725 (let ((des (allocate-header+object *dynamic*
726 (1- sb!vm:single-float-size)
727 sb!vm:single-float-widetag)))
728 (write-wordindexed/raw des sb!vm:single-float-value-slot
729 (single-float-bits x))
730 des))
731 (double-float
732 (let ((des (allocate-header+object *dynamic*
733 (1- sb!vm:double-float-size)
734 sb!vm:double-float-widetag)))
735 (write-double-float-bits des sb!vm:double-float-value-slot x)))))
737 (defun complex-single-float-to-core (num)
738 (declare (type (complex single-float) num))
739 (let ((des (allocate-header+object *dynamic*
740 (1- sb!vm:complex-single-float-size)
741 sb!vm:complex-single-float-widetag)))
742 #!-64-bit
743 (progn
744 (write-wordindexed/raw des sb!vm:complex-single-float-real-slot
745 (single-float-bits (realpart num)))
746 (write-wordindexed/raw des sb!vm:complex-single-float-imag-slot
747 (single-float-bits (imagpart num))))
748 #!+64-bit
749 (write-wordindexed/raw
750 des sb!vm:complex-single-float-data-slot
751 (logior (ldb (byte 32 0) (single-float-bits (realpart num)))
752 (ash (single-float-bits (imagpart num)) 32)))
753 des))
755 (defun complex-double-float-to-core (num)
756 (declare (type (complex double-float) num))
757 (let ((des (allocate-header+object *dynamic*
758 (1- sb!vm:complex-double-float-size)
759 sb!vm:complex-double-float-widetag)))
760 (write-double-float-bits des sb!vm:complex-double-float-real-slot
761 (realpart num))
762 (write-double-float-bits des sb!vm:complex-double-float-imag-slot
763 (imagpart num))))
765 ;;; Copy the given number to the core.
766 (defun number-to-core (number)
767 (typecase number
768 (integer (or (%fixnum-descriptor-if-possible number)
769 (bignum-to-core number)))
770 (ratio (number-pair-to-core (number-to-core (numerator number))
771 (number-to-core (denominator number))
772 sb!vm:ratio-widetag))
773 ((complex single-float) (complex-single-float-to-core number))
774 ((complex double-float) (complex-double-float-to-core number))
775 #!+long-float
776 ((complex long-float)
777 (error "~S isn't a cold-loadable number at all!" number))
778 (complex (number-pair-to-core (number-to-core (realpart number))
779 (number-to-core (imagpart number))
780 sb!vm:complex-widetag))
781 (float (float-to-core number))
782 (t (error "~S isn't a cold-loadable number at all!" number))))
784 ;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR.
785 (defun cold-cons (car cdr &optional (gspace *dynamic*))
786 (let ((dest (allocate-object gspace 2 sb!vm:list-pointer-lowtag)))
787 (write-wordindexed dest sb!vm:cons-car-slot car)
788 (write-wordindexed dest sb!vm:cons-cdr-slot cdr)
789 dest))
790 (defun list-to-core (list)
791 (let ((head *nil-descriptor*)
792 (tail nil))
793 ;; A recursive algorithm would have the first cons at the highest
794 ;; address. This way looks nicer when viewed in ldb.
795 (loop
796 (unless list (return head))
797 (let ((cons (cold-cons (pop list) *nil-descriptor*)))
798 (if tail (cold-rplacd tail cons) (setq head cons))
799 (setq tail cons)))))
800 (defun cold-list (&rest args) (list-to-core args))
801 (defun cold-list-length (list) ; but no circularity detection
802 ;; a recursive implementation uses too much stack for some Lisps
803 (let ((n 0))
804 (loop (if (cold-null list) (return n))
805 (incf n)
806 (setq list (cold-cdr list)))))
808 ;;; Make a simple-vector on the target that holds the specified
809 ;;; OBJECTS, and return its descriptor.
810 ;;; This is really "vectorify-list-into-core" but that's too wordy,
811 ;;; so historically it was "vector-in-core" which is a fine name.
812 (defun vector-in-core (objects &optional (gspace *dynamic*))
813 (let* ((size (length objects))
814 (result (allocate-vector-object gspace sb!vm:n-word-bits size
815 sb!vm:simple-vector-widetag)))
816 (dotimes (index size result)
817 (write-wordindexed result (+ index sb!vm:vector-data-offset)
818 (pop objects)))))
819 #!+x86
820 (defun ub32-vector-in-core (objects)
821 (let* ((size (length objects))
822 (result (allocate-vector-object *dynamic* sb!vm:n-word-bits size
823 sb!vm:simple-array-unsigned-byte-32-widetag)))
824 (dotimes (index size result)
825 (write-wordindexed/raw result (+ index sb!vm:vector-data-offset)
826 (pop objects)))))
827 (defun cold-svset (vector index value)
828 (let ((i (if (integerp index) index (descriptor-fixnum index))))
829 (write-wordindexed vector (+ i sb!vm:vector-data-offset) value)))
831 (setf (get 'vector :sb-cold-funcall-handler/for-value)
832 (lambda (&rest args) (vector-in-core args)))
834 (declaim (inline cold-vector-len cold-svref))
835 (defun cold-vector-len (vector)
836 (descriptor-fixnum (read-wordindexed vector sb!vm:vector-length-slot)))
837 (defun cold-svref (vector i)
838 (read-wordindexed vector (+ (if (integerp i) i (descriptor-fixnum i))
839 sb!vm:vector-data-offset)))
840 (defun cold-vector-elements-eq (a b)
841 (and (eql (cold-vector-len a) (cold-vector-len b))
842 (dotimes (k (cold-vector-len a) t)
843 (unless (descriptor= (cold-svref a k) (cold-svref b k))
844 (return nil)))))
845 (defun vector-from-core (descriptor &optional (transform #'identity))
846 (let* ((len (cold-vector-len descriptor))
847 (vector (make-array len)))
848 (dotimes (i len vector)
849 (setf (aref vector i) (funcall transform (cold-svref descriptor i))))))
851 ;;;; symbol magic
853 ;; Simulate *FREE-TLS-INDEX*. This is a count, not a displacement.
854 ;; In C, sizeof counts 1 word for the variable-length interrupt_contexts[]
855 ;; but primitive-object-size counts 0, so add 1, though in fact the C code
856 ;; implies that it might have overcounted by 1. We could make this agnostic
857 ;; of MAX-INTERRUPTS by moving the thread base register up by TLS-SIZE words,
858 ;; using negative offsets for all dynamically assigned indices.
859 (defvar *genesis-tls-counter*
860 (+ 1 sb!vm:max-interrupts
861 (sb!vm:primitive-object-size
862 (find 'sb!vm::thread sb!vm:*primitive-objects*
863 :key #'sb!vm:primitive-object-name))))
865 #!+sb-thread
866 (progn
867 ;; Assign SYMBOL the tls-index INDEX. SYMBOL must be a descriptor.
868 ;; This is a backend support routine, but the style within this file
869 ;; is to conditionalize by the target features.
870 (defun cold-assign-tls-index (symbol index)
871 #!+64-bit
872 (write-wordindexed/raw
873 symbol 0 (logior (ash index 32) (read-bits-wordindexed symbol 0)))
874 #!-64-bit
875 (write-wordindexed/raw symbol sb!vm:symbol-tls-index-slot index))
877 ;; Return SYMBOL's tls-index,
878 ;; choosing a new index if it doesn't have one yet.
879 (defun ensure-symbol-tls-index (symbol)
880 (let* ((cold-sym (cold-intern symbol))
881 (tls-index
882 #!+64-bit
883 (ldb (byte 32 32) (read-bits-wordindexed cold-sym 0))
884 #!-64-bit
885 (read-bits-wordindexed cold-sym sb!vm:symbol-tls-index-slot)))
886 (unless (plusp tls-index)
887 (let ((next (prog1 *genesis-tls-counter* (incf *genesis-tls-counter*))))
888 (setq tls-index (ash next sb!vm:word-shift))
889 (cold-assign-tls-index cold-sym tls-index)))
890 tls-index)))
892 (defvar *cold-symbol-gspace* (or #!+immobile-space '*immobile-fixedobj* '*dynamic*))
894 ;;; Allocate (and initialize) a symbol.
895 (defun allocate-symbol (name &key (gspace (symbol-value *cold-symbol-gspace*)))
896 (declare (simple-string name))
897 (let ((symbol (allocate-header+object gspace (1- sb!vm:symbol-size)
898 sb!vm:symbol-widetag)))
899 (write-wordindexed symbol sb!vm:symbol-value-slot *unbound-marker*)
900 (write-wordindexed symbol sb!vm:symbol-hash-slot (make-fixnum-descriptor 0))
901 (write-wordindexed symbol sb!vm:symbol-info-slot *nil-descriptor*)
902 (write-wordindexed symbol sb!vm:symbol-name-slot
903 (set-readonly (base-string-to-core name *dynamic*)))
904 (write-wordindexed symbol sb!vm:symbol-package-slot *nil-descriptor*)
905 symbol))
907 ;;; Set the cold symbol value of SYMBOL-OR-SYMBOL-DES, which can be either a
908 ;;; descriptor of a cold symbol or (in an abbreviation for the
909 ;;; most common usage pattern) an ordinary symbol, which will be
910 ;;; automatically cold-interned.
911 (defun cold-set (symbol-or-symbol-des value)
912 (let ((symbol-des (etypecase symbol-or-symbol-des
913 (descriptor symbol-or-symbol-des)
914 (symbol (cold-intern symbol-or-symbol-des)))))
915 (write-wordindexed symbol-des sb!vm:symbol-value-slot value)))
916 (defun cold-symbol-value (symbol)
917 (let ((val (read-wordindexed (cold-intern symbol) sb!vm:symbol-value-slot)))
918 (if (= (descriptor-bits val) sb!vm:unbound-marker-widetag)
919 (unbound-cold-symbol-handler symbol)
920 val)))
921 (defun cold-fdefn-fun (cold-fdefn)
922 (read-wordindexed cold-fdefn sb!vm:fdefn-fun-slot))
924 (defun unbound-cold-symbol-handler (symbol)
925 (let ((host-val (and (boundp symbol) (symbol-value symbol))))
926 (if (typep host-val 'sb!kernel:named-type)
927 (let ((target-val (ctype-to-core (sb!kernel:named-type-name host-val)
928 host-val)))
929 ;; Though it looks complicated to assign cold symbols on demand,
930 ;; it avoids writing code to build the layout of NAMED-TYPE in the
931 ;; way we build other primordial stuff such as layout-of-layout.
932 (cold-set symbol target-val)
933 target-val)
934 (error "Taking Cold-symbol-value of unbound symbol ~S" symbol))))
936 ;;;; layouts and type system pre-initialization
938 ;;; Since we want to be able to dump structure constants and
939 ;;; predicates with reference layouts, we need to create layouts at
940 ;;; cold-load time. We use the name to intern layouts by, and dump a
941 ;;; list of all cold layouts in *!INITIAL-LAYOUTS* so that type system
942 ;;; initialization can find them. The only thing that's tricky [sic --
943 ;;; WHN 19990816] is initializing layout's layout, which must point to
944 ;;; itself.
946 ;;; a map from name as a host symbol to the descriptor of its target layout
947 (defvar *cold-layouts*)
949 ;;; a map from DESCRIPTOR-BITS of cold layouts to the name, for inverting
950 ;;; mapping
951 (defvar *cold-layout-names*)
953 ;;; the descriptor for layout's layout (needed when making layouts)
954 (defvar *layout-layout*)
956 (defvar *known-structure-classoids*)
958 (defconstant target-layout-length
959 ;; LAYOUT-LENGTH counts the number of words in an instance,
960 ;; including the layout itself as 1 word
961 (layout-length *host-layout-of-layout*))
963 ;;; Trivial methods [sic] require that we sort possible methods by the depthoid.
964 ;;; Most of the objects printed in cold-init are ordered hierarchically in our
965 ;;; type lattice; the major exceptions are ARRAY and VECTOR at depthoid -1.
966 ;;; Of course we need to print VECTORs because a STRING is a vector,
967 ;;; and vector has to precede ARRAY. Kludge it for now.
968 (defun class-depthoid (class-name) ; DEPTHOID-ish thing, any which way you can
969 (case class-name
970 (vector 0.5)
971 (array 0.25)
972 ;; The depthoid of CONDITION has to be faked. The proper value is 1.
973 ;; But STRUCTURE-OBJECT is also at depthoid 1, and its predicate
974 ;; is %INSTANCEP (which is too weak), so to select the correct method
975 ;; we have to make CONDITION more specific.
976 ;; In reality it is type disjoint from structure-object.
977 (condition 2)
979 (let ((target-layout (gethash class-name *cold-layouts*)))
980 (if target-layout
981 (cold-layout-depthoid target-layout)
982 (let ((host-layout (find-layout class-name)))
983 (if (layout-invalid host-layout)
984 (error "~S has neither a host not target layout" class-name)
985 (layout-depthoid host-layout))))))))
987 ;;; Return a list of names created from the cold layout INHERITS data
988 ;;; in X.
989 (defun listify-cold-inherits (x)
990 (map 'list (lambda (cold-layout)
991 (or (gethash (descriptor-bits cold-layout) *cold-layout-names*)
992 (error "~S is not the descriptor of a cold-layout" cold-layout)))
993 (vector-from-core x)))
995 ;;; COLD-DD-SLOTS is a cold descriptor for the list of slots
996 ;;; in a cold defstruct-description. INDEX is a DSD-INDEX.
997 ;;; Return the host's accessor name for the host image of that slot.
998 (defun dsd-accessor-from-cold-slots (cold-dd-slots desired-index)
999 (let* ((dsd-slots (dd-slots
1000 (find-defstruct-description 'defstruct-slot-description)))
1001 (bits-slot
1002 (dsd-index (find 'sb!kernel::bits dsd-slots :key #'dsd-name)))
1003 (accessor-fun-name-slot
1004 (dsd-index (find 'sb!kernel::accessor-name dsd-slots :key #'dsd-name))))
1005 (do ((list cold-dd-slots (cold-cdr list)))
1006 ((cold-null list))
1007 (when (= (ash (descriptor-fixnum
1008 (read-wordindexed (cold-car list)
1009 (+ sb!vm:instance-slots-offset bits-slot)))
1010 (- sb!kernel::+dsd-index-shift+))
1011 desired-index)
1012 (return
1013 (warm-symbol
1014 (read-wordindexed (cold-car list)
1015 (+ sb!vm:instance-slots-offset
1016 accessor-fun-name-slot))))))))
1018 (defun cold-dsd-index (cold-dsd dsd-layout)
1019 (ash (descriptor-fixnum (read-slot cold-dsd dsd-layout :bits))
1020 (- sb!kernel::+dsd-index-shift+)))
1022 (defun cold-dsd-raw-type (cold-dsd dsd-layout)
1023 (1- (ldb (byte 3 0) (descriptor-fixnum (read-slot cold-dsd dsd-layout :bits)))))
1025 (flet ((get-slots (host-layout-or-type)
1026 (etypecase host-layout-or-type
1027 (layout (dd-slots (layout-info host-layout-or-type)))
1028 (symbol (dd-slots-from-core host-layout-or-type))))
1029 (get-slot-index (slots initarg)
1030 (+ sb!vm:instance-slots-offset
1031 (if (descriptor-p slots)
1032 (do ((dsd-layout (find-layout 'defstruct-slot-description))
1033 (slots slots (cold-cdr slots)))
1034 ((cold-null slots) (error "No slot for ~S" initarg))
1035 (let* ((dsd (cold-car slots))
1036 (slot-name (read-slot dsd dsd-layout :name)))
1037 (when (eq (keywordicate (warm-symbol slot-name)) initarg)
1038 ;; Untagged slots are not accessible during cold-load
1039 (aver (eql (cold-dsd-raw-type dsd dsd-layout) -1))
1040 (return (cold-dsd-index dsd dsd-layout)))))
1041 (let ((dsd (find initarg slots
1042 :test (lambda (x y)
1043 (eq x (keywordicate (dsd-name y)))))))
1044 (aver (eq (dsd-raw-type dsd) t)) ; Same as above: no can do.
1045 (dsd-index dsd))))))
1046 (defun write-slots (cold-object host-layout-or-type &rest assignments)
1047 (aver (evenp (length assignments)))
1048 (let ((slots (get-slots host-layout-or-type)))
1049 (loop for (initarg value) on assignments by #'cddr
1050 do (write-wordindexed
1051 cold-object (get-slot-index slots initarg) value)))
1052 cold-object)
1054 ;; For symmetry, the reader takes an initarg, not a slot name.
1055 (defun read-slot (cold-object host-layout-or-type slot-initarg)
1056 (let ((slots (get-slots host-layout-or-type)))
1057 (read-wordindexed cold-object (get-slot-index slots slot-initarg)))))
1059 ;; Given a TYPE-NAME of a structure-class, find its defstruct-description
1060 ;; as a target descriptor, and return the slot list as a target descriptor.
1061 (defun dd-slots-from-core (type-name)
1062 (let* ((host-dd-layout (find-layout 'defstruct-description))
1063 (target-dd
1064 ;; This is inefficient, but not enough so to worry about.
1065 (or (car (assoc (cold-intern type-name) *known-structure-classoids*
1066 :key (lambda (x) (read-slot x host-dd-layout :name))
1067 :test #'descriptor=))
1068 (error "No known layout for ~S" type-name))))
1069 (read-slot target-dd host-dd-layout :slots)))
1071 (defvar *simple-vector-0-descriptor*)
1072 (defvar *vacuous-slot-table*)
1073 (defvar *cold-layout-gspace* (or #!+immobile-space '*immobile-fixedobj* '*dynamic*))
1074 (defvar *cold-package-gspace*
1075 (or #!+(and immobile-space 64-bit) '*immobile-fixedobj* '*dynamic*))
1076 (declaim (ftype (function (symbol descriptor descriptor descriptor descriptor)
1077 descriptor)
1078 make-cold-layout))
1079 (defun make-cold-layout (name length inherits depthoid bitmap)
1080 (let ((result (allocate-struct (symbol-value *cold-layout-gspace*) *layout-layout*
1081 target-layout-length t)))
1082 ;; Don't set the CLOS hash value: done in cold-init instead.
1084 ;; Set other slot values.
1086 ;; leave CLASSOID uninitialized for now
1087 (multiple-value-call
1088 #'write-slots result *host-layout-of-layout*
1089 :invalid *nil-descriptor*
1090 :inherits inherits
1091 :depthoid depthoid
1092 :length length
1093 :%flags (let* ((inherit-names (listify-cold-inherits inherits))
1094 (second (second inherit-names)))
1095 (make-fixnum-descriptor
1096 ;; Note similarity to FOP-LAYOUT here, but with extra
1097 ;; test for the subtree roots.
1098 (cond ((or (eq second 'structure-object) (eq name 'structure-object))
1099 +structure-layout-flag+)
1100 ((or (eq second 'condition) (eq name 'condition))
1101 +condition-layout-flag+)
1102 (t 0))))
1103 :info *nil-descriptor*
1104 :bitmap bitmap
1105 ;; Nothing in cold-init needs to call EQUALP on a structure with raw slots,
1106 ;; but for type-correctness this slot needs to be a simple-vector.
1107 :equalp-tests *simple-vector-0-descriptor*
1108 :source-location *nil-descriptor*
1109 :slot-list *nil-descriptor*
1110 (if (member name '(null list symbol))
1111 ;; Assign an empty slot-table. Why this is done only for three
1112 ;; classoids is ... too complicated to explain here in a few words,
1113 ;; but revision 18c239205d9349abc017b07e7894a710835c5205 broke it.
1114 ;; Keep this in sync with MAKE-SLOT-TABLE in pcl/slots-boot.
1115 (values :slot-table (if (boundp '*vacuous-slot-table*)
1116 *vacuous-slot-table*
1117 (setq *vacuous-slot-table*
1118 (host-constant-to-core '#(1 nil)))))
1119 (values)))
1121 (setf (gethash (descriptor-bits result) *cold-layout-names*) name
1122 (gethash name *cold-layouts*) result)))
1124 (defun predicate-for-specializer (type-name)
1125 (let ((classoid (find-classoid type-name nil)))
1126 (typecase classoid
1127 (structure-classoid
1128 (cond ((dd-predicate-name (layout-info (classoid-layout classoid))))
1129 ;; All early INSTANCEs should be STRUCTURE-OBJECTs.
1130 ;; Except: see hack for CONDITIONs in CLASS-DEPTHOID.
1131 ((eq type-name 'structure-object) 'sb!kernel:%instancep)))
1132 (built-in-classoid
1133 (let ((translation (specifier-type type-name)))
1134 (aver (not (contains-unknown-type-p translation)))
1135 (let ((predicate (find translation sb!c::*backend-type-predicates*
1136 :test #'type= :key #'car)))
1137 (cond (predicate (cdr predicate))
1138 ((eq type-name 'stream) 'streamp)
1139 ((eq type-name 't) 'sb!int:constantly-t)
1140 (t (error "No predicate for builtin: ~S" type-name))))))
1141 (null
1142 #+nil (format t "~&; PREDICATE-FOR-SPECIALIZER: no classoid for ~S~%"
1143 type-name)
1144 (case type-name
1145 (condition 'sb!kernel::!condition-p))))))
1147 ;;; Convert SPECIFIER (equivalently OBJ) to its representation as a ctype
1148 ;;; in the cold core.
1149 (defvar *ctype-cache*)
1151 (defvar *ctype-nullified-slots* nil)
1152 (defvar *built-in-classoid-nullified-slots* nil)
1154 ;; This function is memoized because it's essentially a constant,
1155 ;; but *nil-descriptor* isn't initialized by the time it's defined.
1156 (defun get-exceptional-slots (obj-type)
1157 (flet ((index (classoid-name slot-name)
1158 (dsd-index (find slot-name
1159 (dd-slots (find-defstruct-description classoid-name))
1160 :key #'dsd-name))))
1161 (case obj-type
1162 (built-in-classoid
1163 (or *built-in-classoid-nullified-slots*
1164 (setq *built-in-classoid-nullified-slots*
1165 (append (get-exceptional-slots 'ctype)
1166 (list (cons (index 'built-in-classoid 'sb!kernel::subclasses)
1167 *nil-descriptor*)
1168 (cons (index 'built-in-classoid 'layout)
1169 *nil-descriptor*))))))
1171 (or *ctype-nullified-slots*
1172 (setq *ctype-nullified-slots*
1173 (list (cons (index 'ctype 'sb!kernel::class-info)
1174 *nil-descriptor*))))))))
1176 (defun ctype-to-core (specifier obj)
1177 (declare (type ctype obj))
1178 (if (classoid-p obj)
1179 (let* ((cell (cold-find-classoid-cell (classoid-name obj) :create t))
1180 (cold-classoid
1181 (read-slot cell (find-layout 'sb!kernel::classoid-cell) :classoid)))
1182 (unless (cold-null cold-classoid)
1183 (return-from ctype-to-core cold-classoid)))
1184 ;; CTYPEs can't be TYPE=-hashed, but specifiers can be EQUAL-hashed.
1185 ;; Don't check the cache for classoids though; that would be wrong.
1186 ;; e.g. named-type T and classoid T both unparse to T.
1187 (awhen (gethash specifier *ctype-cache*)
1188 (return-from ctype-to-core it)))
1189 (let ((result
1190 (ctype-to-core-helper
1192 (lambda (obj)
1193 (typecase obj
1194 (xset (ctype-to-core-helper obj nil nil))
1195 (ctype (ctype-to-core (type-specifier obj) obj))))
1196 (get-exceptional-slots (type-of obj)))))
1197 (let ((type-class-vector
1198 (cold-symbol-value 'sb!kernel::*type-classes*))
1199 (index (position (sb!kernel::type-class-info obj)
1200 sb!kernel::*type-classes*)))
1201 ;; Push this instance into the list of fixups for its type class
1202 (cold-svset type-class-vector index
1203 (cold-cons result (cold-svref type-class-vector index))))
1204 (if (classoid-p obj)
1205 ;; Place this classoid into its clasoid-cell.
1206 (let ((cell (cold-find-classoid-cell (classoid-name obj) :create t)))
1207 (write-slots cell (find-layout 'sb!kernel::classoid-cell)
1208 :classoid result))
1209 ;; Otherwise put it in the general cache
1210 (setf (gethash specifier *ctype-cache*) result))
1211 result))
1213 (defun ctype-to-core-helper (obj obj-to-core-helper exceptional-slots)
1214 (let* ((host-type (type-of obj))
1215 (target-layout (or (gethash host-type *cold-layouts*)
1216 (error "No target layout for ~S" obj)))
1217 (result (allocate-struct *dynamic* target-layout))
1218 (cold-dd-slots (dd-slots-from-core host-type)))
1219 (aver (eql (layout-bitmap (find-layout host-type))
1220 sb!kernel::+layout-all-tagged+))
1221 ;; Dump the slots.
1222 (do ((len (cold-layout-length target-layout))
1223 (index sb!vm:instance-data-start (1+ index)))
1224 ((= index len) result)
1225 (write-wordindexed
1226 result
1227 (+ sb!vm:instance-slots-offset index)
1228 (acond ((assq index exceptional-slots) (cdr it))
1229 (t (host-constant-to-core
1230 (funcall (dsd-accessor-from-cold-slots cold-dd-slots index)
1231 obj)
1232 obj-to-core-helper)))))))
1234 ;; This is called to backpatch two small sets of objects:
1235 ;; - layouts created before layout-of-layout is made (3 counting LAYOUT itself)
1236 ;; - a small number of classoid-cells (~ 4).
1237 (defun set-instance-layout (thing layout)
1238 #!+compact-instance-header
1239 ;; High half of the header points to the layout
1240 (write-wordindexed/raw thing 0 (logior (ash (descriptor-bits layout) 32)
1241 (read-bits-wordindexed thing 0)))
1242 #!-compact-instance-header
1243 ;; Word following the header is the layout
1244 (write-wordindexed thing sb!vm:instance-slots-offset layout))
1246 (defun cold-layout-of (cold-struct)
1247 #!+compact-instance-header
1248 (let ((bits (ash (read-bits-wordindexed cold-struct 0) -32)))
1249 (if (zerop bits) *nil-descriptor* (make-random-descriptor bits)))
1250 #!-compact-instance-header
1251 (read-wordindexed cold-struct sb!vm:instance-slots-offset))
1253 (defun initialize-layouts ()
1254 (clrhash *cold-layouts*)
1255 ;; This assertion is due to the fact that MAKE-COLD-LAYOUT does not
1256 ;; know how to set any raw slots.
1257 (aver (eql (layout-bitmap *host-layout-of-layout*)
1258 sb!kernel::+layout-all-tagged+))
1259 (setq *layout-layout* (make-fixnum-descriptor 0))
1260 (flet ((chill-layout (name &rest inherits)
1261 ;; Check that the number of specified INHERITS matches
1262 ;; the length of the layout's inherits in the cross-compiler.
1263 (let ((warm-layout (classoid-layout (find-classoid name))))
1264 (assert (eql (length (layout-inherits warm-layout))
1265 (length inherits)))
1266 (make-cold-layout
1267 name
1268 (number-to-core (layout-length warm-layout))
1269 (vector-in-core inherits)
1270 (number-to-core (layout-depthoid warm-layout))
1271 (number-to-core (layout-bitmap warm-layout))))))
1272 (let* ((t-layout (chill-layout 't))
1273 (fun-layout (chill-layout 'function t-layout))
1274 (s-o-layout (chill-layout 'structure-object t-layout)))
1275 (setf *layout-layout* (chill-layout 'layout t-layout s-o-layout))
1276 (dolist (layout (list t-layout fun-layout s-o-layout *layout-layout*))
1277 (set-instance-layout layout *layout-layout*))
1278 (chill-layout 'package t-layout s-o-layout)
1279 (let* ((sequence (chill-layout 'sequence t-layout))
1280 (list (chill-layout 'list t-layout sequence))
1281 (symbol (chill-layout 'symbol t-layout)))
1282 (chill-layout 'null t-layout sequence list symbol)))))
1284 ;;;; interning symbols in the cold image
1286 ;;; a map from package name as a host string to
1287 ;;; ((external-symbols . internal-symbols) . cold-package-descriptor)
1288 (defvar *cold-package-symbols*)
1289 (declaim (type hash-table *cold-package-symbols*))
1291 (setf (get 'find-package :sb-cold-funcall-handler/for-value)
1292 (lambda (descriptor &aux (name (base-string-from-core descriptor)))
1293 (or (cdr (gethash name *cold-package-symbols*))
1294 (error "Genesis could not find a target package named ~S" name))))
1296 (defvar *classoid-cells*)
1297 (defun cold-find-classoid-cell (name &key create)
1298 (aver (eq create t))
1299 (or (gethash name *classoid-cells*)
1300 (let ((layout (gethash 'sb!kernel::classoid-cell *cold-layouts*)) ; ok if nil
1301 (host-layout (find-layout 'sb!kernel::classoid-cell)))
1302 (setf (gethash name *classoid-cells*)
1303 (write-slots (allocate-struct *dynamic* layout
1304 (layout-length host-layout))
1305 host-layout
1306 :name name
1307 :pcl-class *nil-descriptor*
1308 :classoid *nil-descriptor*)))))
1310 (setf (get 'find-classoid-cell :sb-cold-funcall-handler/for-value)
1311 #'cold-find-classoid-cell)
1313 ;;; a map from descriptors to symbols, so that we can back up. The key
1314 ;;; is the address in the target core.
1315 (defvar *cold-symbols*)
1316 (declaim (type hash-table *cold-symbols*))
1318 (defun set-readonly (string) (set-header-data string sb!vm:+vector-shareable+))
1320 (defun initialize-packages ()
1321 (let ((package-data-list
1322 ;; docstrings are set in src/cold/warm. It would work to do it here,
1323 ;; but seems preferable not to saddle Genesis with such responsibility.
1324 (list* (sb-cold:make-package-data :name "COMMON-LISP" :doc nil)
1325 (sb-cold:make-package-data :name "KEYWORD" :doc nil)
1326 ;; ANSI encourages us to put extension packages
1327 ;; in the USE list of COMMON-LISP-USER.
1328 (sb-cold:make-package-data
1329 :name "COMMON-LISP-USER" :doc nil
1330 :use '("COMMON-LISP" "SB!ALIEN" "SB!DEBUG" "SB!EXT" "SB!GRAY" "SB!PROFILE"))
1331 (sb-cold::package-list-for-genesis)))
1332 (package-layout (find-layout 'package))
1333 (target-pkg-list nil))
1334 (labels ((init-cold-package (name &optional docstring)
1335 (let ((cold-package (allocate-struct (symbol-value *cold-package-gspace*)
1336 (gethash 'package *cold-layouts*))))
1337 (setf (gethash name *cold-package-symbols*)
1338 (cons (cons nil nil) cold-package))
1339 ;; Initialize string slots
1340 (write-slots cold-package package-layout
1341 :%name (set-readonly
1342 (base-string-to-core
1343 (target-package-name name)))
1344 :%nicknames (chill-nicknames name)
1345 :doc-string (if docstring
1346 (base-string-to-core docstring)
1347 *nil-descriptor*)
1348 :%use-list *nil-descriptor*)
1349 ;; the cddr of this will accumulate the 'used-by' package list
1350 (push (list name cold-package) target-pkg-list)))
1351 (target-package-name (string)
1352 (if (eql (mismatch string "SB!") 3)
1353 (concatenate 'string "SB-" (subseq string 3))
1354 string))
1355 (chill-nicknames (pkg-name)
1356 ;; Make the package nickname lists for the standard packages
1357 ;; be the minimum specified by ANSI, regardless of what value
1358 ;; the cross-compilation host happens to use.
1359 ;; For packages other than the standard packages, the nickname
1360 ;; list was specified by our package setup code, and we can just
1361 ;; propagate the current state into the target.
1362 (list-to-core
1363 (mapcar #'base-string-to-core
1364 (cond ((string= pkg-name "COMMON-LISP") '("CL"))
1365 ((string= pkg-name "COMMON-LISP-USER")
1366 '("CL-USER"))
1367 ((string= pkg-name "KEYWORD") '())
1369 ;; 'package-data-list' contains no nicknames.
1370 ;; (See comment in 'set-up-cold-packages')
1371 (aver (null (package-nicknames
1372 (find-package pkg-name))))
1373 nil)))))
1374 (find-cold-package (name)
1375 (cadr (find-package-cell name)))
1376 (find-package-cell (name)
1377 (or (assoc (if (string= name "CL") "COMMON-LISP" name)
1378 target-pkg-list :test #'string=)
1379 (error "No cold package named ~S" name))))
1380 ;; pass 1: make all proto-packages
1381 (dolist (pd package-data-list)
1382 (init-cold-package (sb-cold:package-data-name pd)
1383 #!+sb-doc(sb-cold::package-data-doc pd)))
1384 ;; pass 2: set the 'use' lists and collect the 'used-by' lists
1385 (dolist (pd package-data-list)
1386 (let ((this (find-cold-package (sb-cold:package-data-name pd)))
1387 (use nil))
1388 (dolist (that (sb-cold:package-data-use pd))
1389 (let ((cell (find-package-cell that)))
1390 (push (cadr cell) use)
1391 (push this (cddr cell))))
1392 (write-slots this package-layout
1393 :%use-list (list-to-core (nreverse use)))))
1394 ;; pass 3: set the 'used-by' lists
1395 (dolist (cell target-pkg-list)
1396 (write-slots (cadr cell) package-layout
1397 :%used-by-list (list-to-core (cddr cell)))))))
1399 ;;; sanity check for a symbol we're about to create on the target
1401 ;;; Make sure that the symbol has an appropriate package. In
1402 ;;; particular, catch the so-easy-to-make error of typing something
1403 ;;; like SB-KERNEL:%BYTE-BLT in cold sources when what you really
1404 ;;; need is SB!KERNEL:%BYTE-BLT.
1405 (defun package-ok-for-target-symbol-p (package)
1406 (let ((package-name (package-name package)))
1408 ;; Cold interning things in these standard packages is OK. (Cold
1409 ;; interning things in the other standard package, CL-USER, isn't
1410 ;; OK. We just use CL-USER to expose symbols whose homes are in
1411 ;; other packages. Thus, trying to cold intern a symbol whose
1412 ;; home package is CL-USER probably means that a coding error has
1413 ;; been made somewhere.)
1414 (find package-name '("COMMON-LISP" "KEYWORD") :test #'string=)
1415 ;; Cold interning something in one of our target-code packages,
1416 ;; which are ever-so-rigorously-and-elegantly distinguished by
1417 ;; this prefix on their names, is OK too.
1418 (string= package-name "SB!" :end1 3 :end2 3)
1419 ;; This one is OK too, since it ends up being COMMON-LISP on the
1420 ;; target.
1421 (string= package-name "SB!XC")
1422 ;; Anything else looks bad. (maybe COMMON-LISP-USER? maybe an extension
1423 ;; package in the xc host? something we can't think of
1424 ;; a valid reason to cold intern, anyway...)
1427 ;;; like SYMBOL-PACKAGE, but safe for symbols which end up on the target
1429 ;;; Most host symbols we dump onto the target are created by SBCL
1430 ;;; itself, so that as long as we avoid gratuitously
1431 ;;; cross-compilation-unfriendly hacks, it just happens that their
1432 ;;; SYMBOL-PACKAGE in the host system corresponds to their
1433 ;;; SYMBOL-PACKAGE in the target system. However, that's not the case
1434 ;;; in the COMMON-LISP package, where we don't get to create the
1435 ;;; symbols but instead have to use the ones that the xc host created.
1436 ;;; In particular, while ANSI specifies which symbols are exported
1437 ;;; from COMMON-LISP, it doesn't specify that their home packages are
1438 ;;; COMMON-LISP, so the xc host can keep them in random packages which
1439 ;;; don't exist on the target (e.g. CLISP keeping some CL-exported
1440 ;;; symbols in the CLOS package).
1441 (defun symbol-package-for-target-symbol (symbol)
1442 ;; We want to catch weird symbols like CLISP's
1443 ;; CL:FIND-METHOD=CLOS::FIND-METHOD, but we don't want to get
1444 ;; sidetracked by ordinary symbols like :CHARACTER which happen to
1445 ;; have the same SYMBOL-NAME as exports from COMMON-LISP.
1446 (multiple-value-bind (cl-symbol cl-status)
1447 (find-symbol (symbol-name symbol) *cl-package*)
1448 (if (and (eq symbol cl-symbol)
1449 (eq cl-status :external))
1450 ;; special case, to work around possible xc host weirdness
1451 ;; in COMMON-LISP package
1452 *cl-package*
1453 ;; ordinary case
1454 (let ((result (symbol-package symbol)))
1455 (unless (package-ok-for-target-symbol-p result)
1456 (bug "~A in bad package for target: ~A" symbol result))
1457 result))))
1459 (defvar *uninterned-symbol-table* (make-hash-table :test #'equal))
1460 ;; This coalesces references to uninterned symbols, which is allowed because
1461 ;; "similar-as-constant" is defined by string comparison, and since we only have
1462 ;; base-strings during Genesis, there is no concern about upgraded array type.
1463 ;; There is a subtlety of whether coalescing may occur across files
1464 ;; - the target compiler doesn't and couldn't - but here it doesn't matter.
1465 (defun get-uninterned-symbol (name)
1466 (ensure-gethash name *uninterned-symbol-table* (allocate-symbol name)))
1468 ;;; Dump the target representation of HOST-VALUE,
1469 ;;; the type of which is in a restrictive set.
1470 (defun host-constant-to-core (host-value &optional helper)
1471 (let ((visited (make-hash-table :test #'eq)))
1472 (named-let target-representation ((value host-value))
1473 (unless (typep value '(or symbol number descriptor))
1474 (let ((found (gethash value visited)))
1475 (cond ((eq found :pending)
1476 (bug "circular constant?")) ; Circularity not permitted
1477 (found
1478 (return-from target-representation found))))
1479 (setf (gethash value visited) :pending))
1480 (setf (gethash value visited)
1481 (typecase value
1482 (descriptor value)
1483 (symbol (if (symbol-package value)
1484 (cold-intern value)
1485 (get-uninterned-symbol (string value))))
1486 (number (number-to-core value))
1487 (string (base-string-to-core value))
1488 (cons (cold-cons (target-representation (car value))
1489 (target-representation (cdr value))))
1490 (simple-vector
1491 (vector-in-core (map 'list #'target-representation value)))
1493 (or (and helper (funcall helper value))
1494 (error "host-constant-to-core: can't convert ~S"
1495 value))))))))
1497 ;; Look up the target's descriptor for #'FUN where FUN is a host symbol.
1498 (defun target-symbol-function (symbol)
1499 (let ((f (cold-fdefn-fun (cold-fdefinition-object symbol))))
1500 ;; It works only if DEFUN F was seen first.
1501 (aver (not (cold-null f)))
1504 ;;; Return a handle on an interned symbol. If necessary allocate the
1505 ;;; symbol and record its home package.
1506 (defun cold-intern (symbol
1507 &key (access nil)
1508 (gspace (symbol-value *cold-symbol-gspace*))
1509 &aux (package (symbol-package-for-target-symbol symbol)))
1511 ;; Anything on the cross-compilation host which refers to the target
1512 ;; machinery through the host SB!XC package should be translated to
1513 ;; something on the target which refers to the same machinery
1514 ;; through the target COMMON-LISP package.
1515 (let ((p (find-package "SB!XC")))
1516 (when (eq package p)
1517 (setf package *cl-package*))
1518 (when (eq (symbol-package symbol) p)
1519 (setf symbol (intern (symbol-name symbol) *cl-package*))))
1521 (or (get symbol 'cold-intern-info)
1522 (let ((handle (allocate-symbol (symbol-name symbol) :gspace gspace)))
1523 (setf (get symbol 'cold-intern-info) handle)
1524 ;; maintain reverse map from target descriptor to host symbol
1525 (setf (gethash (descriptor-bits handle) *cold-symbols*) symbol)
1526 (let ((pkg-info (or (gethash (package-name package) *cold-package-symbols*)
1527 (error "No target package descriptor for ~S" package))))
1528 (write-wordindexed handle sb!vm:symbol-package-slot (cdr pkg-info))
1529 (record-accessibility
1530 (or access (nth-value 1 (find-symbol (symbol-name symbol) package)))
1531 pkg-info handle package symbol))
1532 #!+sb-thread
1533 (let ((index (info :variable :wired-tls symbol)))
1534 (when (integerp index) ; thread slot
1535 (cold-assign-tls-index handle index)))
1536 (when (eq package *keyword-package*)
1537 (cold-set handle handle))
1538 handle)))
1540 (defun record-accessibility (accessibility target-pkg-info symbol-descriptor
1541 &optional host-package host-symbol)
1542 (let ((access-lists (car target-pkg-info)))
1543 (case accessibility
1544 (:external (push symbol-descriptor (car access-lists)))
1545 (:internal (push symbol-descriptor (cdr access-lists)))
1546 (t (error "~S inaccessible in package ~S" host-symbol host-package)))))
1548 ;;; Construct and return a value for use as *NIL-DESCRIPTOR*.
1549 ;;; It might be nice to put NIL on a readonly page by itself to prevent unsafe
1550 ;;; code from destroying the world with (RPLACx nil 'kablooey)
1551 (defun make-nil-descriptor ()
1552 (let* ((des (allocate-header+object *static* sb!vm:symbol-size 0))
1553 (result (make-descriptor (+ (descriptor-bits des)
1554 (* 2 sb!vm:n-word-bytes)
1555 (- sb!vm:list-pointer-lowtag
1556 sb!vm:other-pointer-lowtag)))))
1557 (write-wordindexed des
1559 (make-other-immediate-descriptor
1561 sb!vm:symbol-widetag))
1562 (write-wordindexed des
1563 (+ 1 sb!vm:symbol-value-slot)
1564 result)
1565 (write-wordindexed des
1566 (+ 2 sb!vm:symbol-value-slot) ; = 1 + symbol-hash-slot
1567 result)
1568 (write-wordindexed des
1569 (+ 1 sb!vm:symbol-info-slot)
1570 (cold-cons result result)) ; NIL's info is (nil . nil)
1571 (write-wordindexed des
1572 (+ 1 sb!vm:symbol-name-slot)
1573 ;; NIL's name is in dynamic space because any extra
1574 ;; bytes allocated in static space would need to
1575 ;; be accounted for by STATIC-SYMBOL-OFFSET.
1576 (set-readonly (base-string-to-core "NIL" *dynamic*)))
1577 (setf (gethash (descriptor-bits result) *cold-symbols*) nil
1578 (get nil 'cold-intern-info) result)))
1580 ;;; Since the initial symbols must be allocated before we can intern
1581 ;;; anything else, we intern those here. We also set the value of T.
1582 (defun initialize-static-space ()
1583 "Initialize the cold load symbol-hacking data structures."
1584 ;; NIL did not have its package assigned. Do that now.
1585 (let ((target-cl-pkg-info (gethash "COMMON-LISP" *cold-package-symbols*)))
1586 ;; -1 is magic having to do with nil-as-cons vs. nil-as-symbol
1587 (write-wordindexed *nil-descriptor* (- sb!vm:symbol-package-slot 1)
1588 (cdr target-cl-pkg-info))
1589 (record-accessibility :external target-cl-pkg-info *nil-descriptor*))
1590 ;; Intern the others.
1591 (dovector (symbol sb!vm:+static-symbols+)
1592 (let* ((des (cold-intern symbol :gspace *static*))
1593 (offset-wanted (sb!vm:static-symbol-offset symbol))
1594 (offset-found (- (descriptor-bits des)
1595 (descriptor-bits *nil-descriptor*))))
1596 (unless (= offset-wanted offset-found)
1597 (error "Offset from ~S to ~S is ~W, not ~W"
1598 symbol
1600 offset-found
1601 offset-wanted))))
1603 ;; Assign TLS indices of C interface symbols
1604 #!+sb-thread
1605 (dolist (binding sb!vm::!per-thread-c-interface-symbols)
1606 (ensure-symbol-tls-index (car (ensure-list binding))))
1608 ;; Establish the value of T.
1609 (let ((t-symbol (cold-intern t :gspace *static*)))
1610 (cold-set t-symbol t-symbol))
1612 ;; Establish the value of SB-VM:FUNCTION-LAYOUT
1613 #!+(and immobile-space 64-bit)
1614 (let ((address-bits (descriptor-bits (gethash 'function *cold-layouts*))))
1615 (aver (eql address-bits sb!vm:function-layout))
1616 (write-wordindexed/raw (cold-intern 'sb!vm:function-layout)
1617 sb!vm:symbol-value-slot
1618 (ash address-bits 32)))
1620 (dolist (sym sb!vm::+c-callable-fdefns+)
1621 (cold-fdefinition-object (cold-intern sym) nil *static*))
1623 ;; With immobile-code, static-fdefns as a concept are useful -
1624 ;; the implication is that the function's definition will not change.
1625 ;; But the fdefn per se is not useful - callers refer to callees directly.
1626 #!-immobile-code
1627 (dovector (sym sb!vm:+static-fdefns+)
1628 (let* ((fdefn (cold-fdefinition-object (cold-intern sym) nil *static*))
1629 (offset (- (+ (- (descriptor-bits fdefn)
1630 sb!vm:other-pointer-lowtag)
1631 (* sb!vm:fdefn-raw-addr-slot sb!vm:n-word-bytes))
1632 (descriptor-bits *nil-descriptor*)))
1633 (desired (sb!vm:static-fun-offset sym)))
1634 (unless (= offset desired)
1635 (error "Offset from FDEFN ~S to ~S is ~W, not ~W."
1636 sym nil offset desired)))))
1638 ;;; Sort *COLD-LAYOUTS* to return them in a deterministic order.
1639 (defun sort-cold-layouts ()
1640 (sort (%hash-table-alist *cold-layouts*) #'<
1641 :key (lambda (x) (descriptor-bits (cdr x)))))
1643 ;;; Establish initial values for magic symbols.
1645 (defun finish-symbols ()
1646 (cold-set '*!initial-layouts*
1647 (vector-in-core
1648 (mapcar (lambda (layout)
1649 (cold-cons (cold-intern (car layout)) (cdr layout)))
1650 (sort-cold-layouts))))
1652 #!+sb-thread
1653 (let ((bindings sb!kernel::*!thread-initial-bindings*))
1654 ;; Assign the initialization vector for create_thread_struct()
1655 (cold-set 'sb!thread::*thread-initial-bindings*
1656 (vector-in-core
1657 (mapcar (lambda (pair)
1658 (let* ((name (cold-intern (car pair)))
1659 (value (cdr pair))
1660 (initform (cold-intern value)))
1661 (aver (symbolp value))
1662 (if (null value) name (cold-cons initform name))))
1663 bindings)))
1664 (dolist (binding bindings)
1665 (ensure-symbol-tls-index (car (ensure-list binding))))
1666 (cold-set 'sb!vm::*free-tls-index*
1667 (make-descriptor (ash *genesis-tls-counter* sb!vm:word-shift))))
1669 (dolist (symbol sb!impl::*cache-vector-symbols*)
1670 (cold-set symbol *nil-descriptor*))
1672 ;; Symbols for which no call to COLD-INTERN would occur - due to not being
1673 ;; referenced until warm init - must be artificially cold-interned.
1674 ;; Inasmuch as the "offending" things are compiled by ordinary target code
1675 ;; and not cold-init, I think we should use an ordinary DEFPACKAGE for
1676 ;; the added-on bits. What I've done is somewhat of a fragile kludge.
1677 (let (syms)
1678 (with-package-iterator (iter '("SB!PCL" "SB!MOP" "SB!GRAY" "SB!SEQUENCE"
1679 "SB!PROFILE" "SB!EXT" "SB!VM"
1680 "SB!C" "SB!FASL" "SB!DEBUG")
1681 :external)
1682 (loop
1683 (multiple-value-bind (foundp sym accessibility package) (iter)
1684 (declare (ignore accessibility))
1685 (cond ((not foundp) (return))
1686 ((eq (symbol-package sym) package) (push sym syms))))))
1687 (setf syms (stable-sort syms #'string<))
1688 (dolist (sym syms)
1689 (cold-intern sym)))
1691 (cold-set
1692 'sb!impl::*!initial-symbols*
1693 (list-to-core
1694 (mapcar
1695 (lambda (pkgcons)
1696 (destructuring-bind (pkg-name . pkg-info) pkgcons
1697 (let ((shadow
1698 ;; Record shadowing symbols (except from SB!XC) in SB! packages.
1699 (when (eql (mismatch pkg-name "SB!") 3)
1700 ;; Be insensitive to the host's ordering.
1701 (sort (remove (find-package "SB!XC")
1702 (package-shadowing-symbols (find-package pkg-name))
1703 :key #'symbol-package) #'string<))))
1704 (write-slots (cdr pkg-info) ; package
1705 (find-layout 'package)
1706 :%shadowing-symbols (list-to-core
1707 (mapcar 'cold-intern shadow))))
1708 (unless (member pkg-name '("COMMON-LISP" "KEYWORD") :test 'string=)
1709 (let ((host-pkg (find-package pkg-name))
1710 (sb-xc-pkg (find-package "SB!XC"))
1711 syms)
1712 ;; Now for each symbol directly present in this host-pkg,
1713 ;; i.e. accessible but not :INHERITED, figure out if the symbol
1714 ;; came from a different package, and if so, make a note of it.
1715 (with-package-iterator (iter host-pkg :internal :external)
1716 (loop (multiple-value-bind (foundp sym accessibility) (iter)
1717 (unless foundp (return))
1718 (unless (or (eq (symbol-package sym) host-pkg)
1719 (eq (symbol-package sym) sb-xc-pkg))
1720 (push (cons sym accessibility) syms)))))
1721 (dolist (symcons (sort syms #'string< :key #'car))
1722 (destructuring-bind (sym . accessibility) symcons
1723 (record-accessibility accessibility pkg-info (cold-intern sym)
1724 host-pkg sym)))))
1725 (cold-list (cdr pkg-info)
1726 (vector-in-core (caar pkg-info))
1727 (vector-in-core (cdar pkg-info)))))
1728 (sort (%hash-table-alist *cold-package-symbols*)
1729 #'string< :key #'car)))) ; Sort by package-name
1731 (dump-symbol-info-vectors
1732 (attach-fdefinitions-to-symbols
1733 (attach-classoid-cells-to-symbols (make-hash-table :test #'eq))))
1735 #!+x86
1736 (progn
1737 (cold-set 'sb!vm::*fp-constant-0d0* (number-to-core 0d0))
1738 (cold-set 'sb!vm::*fp-constant-1d0* (number-to-core 1d0))
1739 (cold-set 'sb!vm::*fp-constant-0f0* (number-to-core 0f0))
1740 (cold-set 'sb!vm::*fp-constant-1f0* (number-to-core 1f0))))
1742 ;;;; functions and fdefinition objects
1744 ;;; a hash table mapping from fdefinition names to descriptors of cold
1745 ;;; objects
1747 ;;; Note: Since fdefinition names can be lists like '(SETF FOO), and
1748 ;;; we want to have only one entry per name, this must be an 'EQUAL
1749 ;;; hash table, not the default 'EQL.
1750 (defvar *cold-fdefn-objects*)
1752 ;;; Given a cold representation of a symbol, return a warm
1753 ;;; representation.
1754 (defun warm-symbol (des)
1755 ;; Note that COLD-INTERN is responsible for keeping the
1756 ;; *COLD-SYMBOLS* table up to date, so if DES happens to refer to an
1757 ;; uninterned symbol, the code below will fail. But as long as we
1758 ;; don't need to look up uninterned symbols during bootstrapping,
1759 ;; that's OK..
1760 (multiple-value-bind (symbol found-p)
1761 (gethash (descriptor-bits des) *cold-symbols*)
1762 (declare (type symbol symbol))
1763 (unless found-p
1764 (error "no warm symbol"))
1765 symbol))
1767 ;;; like CL:CAR, CL:CDR, and CL:NULL but for cold values
1768 (defun cold-car (des)
1769 (aver (= (descriptor-lowtag des) sb!vm:list-pointer-lowtag))
1770 (read-wordindexed des sb!vm:cons-car-slot))
1771 (defun cold-cdr (des)
1772 (aver (= (descriptor-lowtag des) sb!vm:list-pointer-lowtag))
1773 (read-wordindexed des sb!vm:cons-cdr-slot))
1774 (defun cold-rplacd (des newval)
1775 (aver (= (descriptor-lowtag des) sb!vm:list-pointer-lowtag))
1776 (write-wordindexed des sb!vm:cons-cdr-slot newval)
1777 des)
1778 (defun cold-null (des) (descriptor= des *nil-descriptor*))
1780 ;;; Given a cold representation of a function name, return a warm
1781 ;;; representation.
1782 (declaim (ftype (function ((or symbol descriptor)) (or symbol list)) warm-fun-name))
1783 (defun warm-fun-name (des)
1784 (let ((result
1785 (if (symbolp des)
1786 ;; This parallels the logic at the start of COLD-INTERN
1787 ;; which re-homes symbols in SB!XC to COMMON-LISP.
1788 (if (eq (symbol-package des) (find-package "SB!XC"))
1789 (intern (symbol-name des) *cl-package*)
1790 des)
1791 (ecase (descriptor-lowtag des)
1792 (#.sb!vm:list-pointer-lowtag
1793 (aver (not (cold-null des))) ; function named NIL? please no..
1794 (let ((rest (cold-cdr des)))
1795 (aver (cold-null (cold-cdr rest)))
1796 (list (warm-symbol (cold-car des))
1797 (warm-symbol (cold-car rest)))))
1798 (#.sb!vm:other-pointer-lowtag
1799 (warm-symbol des))))))
1800 (legal-fun-name-or-type-error result)
1801 result))
1803 #!+x86-64
1804 (defun encode-fdefn-raw-addr (fdefn jump-target opcode)
1805 (let ((disp (- jump-target
1806 (+ (descriptor-bits fdefn)
1807 (- sb!vm:other-pointer-lowtag)
1808 (ash sb!vm:fdefn-raw-addr-slot sb!vm:word-shift)
1809 5))))
1810 (logior (ash (ldb (byte 32 0) (the (signed-byte 32) disp)) 8) opcode)))
1812 (defun cold-fdefinition-object (cold-name &optional leave-fn-raw
1813 (gspace #!+immobile-space *immobile-fixedobj*
1814 #!-immobile-space *dynamic*))
1815 (declare (type (or symbol descriptor) cold-name))
1816 (declare (special core-file-name))
1817 (let ((warm-name (warm-fun-name cold-name)))
1818 (or (gethash warm-name *cold-fdefn-objects*)
1819 (let ((fdefn (allocate-header+object gspace (1- sb!vm:fdefn-size) sb!vm:fdefn-widetag)))
1820 (setf (gethash warm-name *cold-fdefn-objects*) fdefn)
1821 (write-wordindexed fdefn sb!vm:fdefn-name-slot cold-name)
1822 (unless leave-fn-raw
1823 (write-wordindexed fdefn sb!vm:fdefn-fun-slot *nil-descriptor*)
1824 (let ((tramp
1825 (or (lookup-assembler-reference 'sb!vm::undefined-tramp core-file-name)
1826 ;; Our preload for the tramps doesn't happen during host-1,
1827 ;; so substitute a usable value.
1828 0)))
1829 (write-wordindexed/raw fdefn sb!vm:fdefn-raw-addr-slot
1830 #!+(and immobile-code x86-64)
1831 (encode-fdefn-raw-addr fdefn tramp #xE8)
1832 #!-immobile-code tramp)))
1833 fdefn))))
1835 (defun cold-functionp (descriptor)
1836 (eql (descriptor-lowtag descriptor) sb!vm:fun-pointer-lowtag))
1838 (defun cold-fun-entry-addr (fun)
1839 (aver (= (descriptor-lowtag fun) sb!vm:fun-pointer-lowtag))
1840 (+ (descriptor-bits fun)
1841 (- sb!vm:fun-pointer-lowtag)
1842 (ash sb!vm:simple-fun-code-offset sb!vm:word-shift)))
1844 ;;; Handle a DEFUN in cold-load.
1845 (defun cold-fset (name defn source-loc &optional inline-expansion)
1846 ;; SOURCE-LOC can be ignored, because functions intrinsically store
1847 ;; their location as part of the code component.
1848 ;; The argument is supplied here only to provide context for
1849 ;; a redefinition warning, which can't happen in cold load.
1850 (declare (ignore source-loc))
1851 (sb!int:binding* (((cold-name warm-name)
1852 ;; (SETF f) was descriptorized when dumped, symbols were not.
1853 (if (symbolp name)
1854 (values (cold-intern name) name)
1855 (values name (warm-fun-name name))))
1856 (fdefn (cold-fdefinition-object cold-name t)))
1857 (when (cold-functionp (cold-fdefn-fun fdefn))
1858 (error "Duplicate DEFUN for ~S" warm-name))
1859 ;; There can't be any closures or funcallable instances.
1860 (aver (= (logand (descriptor-bits (read-memory defn)) sb!vm:widetag-mask)
1861 sb!vm:simple-fun-widetag))
1862 (push (cold-cons cold-name inline-expansion) *!cold-defuns*)
1863 (write-wordindexed fdefn sb!vm:fdefn-fun-slot defn)
1864 (let ((fun-entry-addr
1865 (+ (logandc2 (descriptor-bits defn) sb!vm:lowtag-mask)
1866 (ash sb!vm:simple-fun-code-offset sb!vm:word-shift))))
1867 (declare (ignorable fun-entry-addr)) ; sparc and arm don't need
1868 #!+(and immobile-code x86-64)
1869 (write-wordindexed/raw fdefn sb!vm:fdefn-raw-addr-slot
1870 (encode-fdefn-raw-addr fdefn fun-entry-addr #xE9))
1871 #!-immobile-code
1872 (progn
1873 #!+(or sparc arm) (write-wordindexed fdefn sb!vm:fdefn-raw-addr-slot defn)
1874 #!-(or sparc arm) (write-wordindexed/raw fdefn sb!vm:fdefn-raw-addr-slot
1875 fun-entry-addr)))
1876 fdefn))
1878 ;;; Handle a DEFMETHOD in cold-load. "Very easily done". Right.
1879 (defun cold-defmethod (name &rest stuff)
1880 (let ((gf (assoc name *cold-methods*)))
1881 (unless gf
1882 (setq gf (cons name nil))
1883 (push gf *cold-methods*))
1884 (push stuff (cdr gf))))
1886 (defun attach-classoid-cells-to-symbols (hashtable)
1887 (let ((num (sb!c::meta-info-number (sb!c::meta-info :type :classoid-cell)))
1888 (layout (gethash 'sb!kernel::classoid-cell *cold-layouts*)))
1889 (when (plusp (hash-table-count *classoid-cells*))
1890 (aver layout))
1891 ;; Iteration order is immaterial. The symbols will get sorted later.
1892 (maphash (lambda (symbol cold-classoid-cell)
1893 ;; Some classoid-cells are dumped before the cold layout
1894 ;; of classoid-cell has been made, so fix those cases now.
1895 ;; Obviously it would be better if, in general, ALLOCATE-STRUCT
1896 ;; knew when something later must backpatch a cold layout
1897 ;; so that it could make a note to itself to do those ASAP
1898 ;; after the cold layout became known.
1899 (when (cold-null (cold-layout-of cold-classoid-cell))
1900 (set-instance-layout cold-classoid-cell layout))
1901 (setf (gethash symbol hashtable)
1902 (packed-info-insert
1903 (gethash symbol hashtable +nil-packed-infos+)
1904 sb!impl::+no-auxilliary-key+ num cold-classoid-cell)))
1905 *classoid-cells*))
1906 hashtable)
1908 ;; Create pointer from SYMBOL and/or (SETF SYMBOL) to respective fdefinition
1910 (defun attach-fdefinitions-to-symbols (hashtable)
1911 ;; Collect fdefinitions that go with one symbol, e.g. CAR and (SETF CAR),
1912 ;; using the host's code for manipulating a packed info-vector.
1913 (maphash (lambda (warm-name cold-fdefn)
1914 (with-globaldb-name (key1 key2) warm-name
1915 :hairy (error "Hairy fdefn name in genesis: ~S" warm-name)
1916 :simple
1917 (setf (gethash key1 hashtable)
1918 (packed-info-insert
1919 (gethash key1 hashtable +nil-packed-infos+)
1920 key2 +fdefn-info-num+ cold-fdefn))))
1921 *cold-fdefn-objects*)
1922 hashtable)
1924 (defun dump-symbol-info-vectors (hashtable)
1925 ;; Emit in the same order symbols reside in core to avoid
1926 ;; sensitivity to the iteration order of host's maphash.
1927 (loop for (warm-sym . info)
1928 in (sort (%hash-table-alist hashtable) #'<
1929 :key (lambda (x) (descriptor-bits (cold-intern (car x)))))
1930 do (write-wordindexed
1931 (cold-intern warm-sym) sb!vm:symbol-info-slot
1932 ;; Each vector will have one fixnum, possibly the symbol SETF,
1933 ;; and one or two #<fdefn> objects in it, and/or a classoid-cell.
1934 (vector-in-core
1935 (map 'list (lambda (elt)
1936 (etypecase elt
1937 (symbol (cold-intern elt))
1938 (fixnum (make-fixnum-descriptor elt))
1939 (descriptor elt)))
1940 info)))))
1943 ;;;; fixups and related stuff
1945 ;;; an EQUAL hash table
1946 (defvar *cold-foreign-symbol-table*)
1947 (declaim (type hash-table *cold-foreign-symbol-table*))
1949 ;; Read the sbcl.nm file to find the addresses for foreign-symbols in
1950 ;; the C runtime.
1951 #!-sb-dynamic-core
1952 (defun load-cold-foreign-symbol-table (filename)
1953 (with-open-file (file filename)
1954 (loop for line = (read-line file nil nil)
1955 while line do
1956 ;; UNIX symbol tables might have tabs in them, and tabs are
1957 ;; not in Common Lisp STANDARD-CHAR, so there seems to be no
1958 ;; nice portable way to deal with them within Lisp, alas.
1959 ;; Fortunately, it's easy to use UNIX command line tools like
1960 ;; sed to remove the problem, so it's not too painful for us
1961 ;; to push responsibility for converting tabs to spaces out to
1962 ;; the caller.
1964 ;; Other non-STANDARD-CHARs are problematic for the same reason.
1965 ;; Make sure that there aren't any..
1966 (let ((ch (find-if (lambda (char)
1967 (not (typep char 'standard-char)))
1968 line)))
1969 (when ch
1970 (error "non-STANDARD-CHAR ~S found in foreign symbol table:~%~S"
1972 line)))
1973 (setf line (string-trim '(#\space) line))
1974 (let ((p1 (position #\space line :from-end nil))
1975 (p2 (position #\space line :from-end t)))
1976 (if (not (and p1 p2 (< p1 p2)))
1977 ;; KLUDGE: It's too messy to try to understand all
1978 ;; possible output from nm, so we just punt the lines we
1979 ;; don't recognize. We realize that there's some chance
1980 ;; that might get us in trouble someday, so we warn
1981 ;; about it.
1982 (warn "ignoring unrecognized line ~S in ~A" line filename)
1983 (multiple-value-bind (value name)
1984 (if (string= "0x" line :end2 2)
1985 (values (parse-integer line :start 2 :end p1 :radix 16)
1986 (subseq line (1+ p2)))
1987 (values (parse-integer line :end p1 :radix 16)
1988 (subseq line (1+ p2))))
1989 ;; KLUDGE CLH 2010-05-31: on darwin, nm gives us
1990 ;; _function but dlsym expects us to look up
1991 ;; function, without the leading _ . Therefore, we
1992 ;; strip it off here.
1993 #!+darwin
1994 (when (equal (char name 0) #\_)
1995 (setf name (subseq name 1)))
1996 (multiple-value-bind (old-value found)
1997 (gethash name *cold-foreign-symbol-table*)
1998 (when (and found
1999 (not (= old-value value)))
2000 (warn "redefining ~S from #X~X to #X~X"
2001 name old-value value)))
2002 (setf (gethash name *cold-foreign-symbol-table*) value)
2003 #!+win32
2004 (let ((at-position (position #\@ name)))
2005 (when at-position
2006 (let ((name (subseq name 0 at-position)))
2007 (multiple-value-bind (old-value found)
2008 (gethash name *cold-foreign-symbol-table*)
2009 (when (and found
2010 (not (= old-value value)))
2011 (warn "redefining ~S from #X~X to #X~X"
2012 name old-value value)))
2013 (setf (gethash name *cold-foreign-symbol-table*)
2014 value)))))))))
2015 (values)) ;; PROGN
2017 #!-sb-dynamic-core
2018 (defun cold-foreign-symbol-address (name)
2019 (declare (ignorable name))
2020 #!+crossbuild-test #xf00fa8 ; any random 4-octet-aligned value should do
2021 #!-crossbuild-test
2022 (or (find-foreign-symbol-in-table name *cold-foreign-symbol-table*)
2023 *foreign-symbol-placeholder-value*
2024 (progn
2025 (format *error-output* "~&The foreign symbol table is:~%")
2026 (maphash (lambda (k v)
2027 (format *error-output* "~&~S = #X~8X~%" k v))
2028 *cold-foreign-symbol-table*)
2029 (error "The foreign symbol ~S is undefined." name))))
2031 (defvar *cold-assembler-obj*) ; a single code component
2032 (defvar *cold-assembler-routines*)
2033 (defvar *cold-static-call-fixups*)
2035 (defun lookup-assembler-reference (symbol &optional (errorp t))
2036 (let ((code-component (car *cold-assembler-obj*))
2037 (offset (or (cdr (assoc symbol *cold-assembler-routines*))
2038 (and errorp (error "Assembler routine ~S not defined." symbol)))))
2039 (when offset
2040 (+ (logandc2 (descriptor-bits code-component) sb!vm:lowtag-mask)
2041 (calc-offset code-component offset)))))
2043 ;;; Unlike in the target, FOP-KNOWN-FUN sometimes has to backpatch.
2044 (defvar *deferred-known-fun-refs*)
2046 ;;; In case we need to store code fixups in code objects.
2047 ;;; At present only the x86 backends use this
2048 (defvar *code-fixup-notes*)
2050 ;;; Given a pointer to a code object and a byte offset relative to the
2051 ;;; tail of the code object's header, return a byte offset relative to the
2052 ;;; (beginning of the) code object.
2054 (declaim (ftype (function (descriptor sb!vm:word)) calc-offset))
2055 (defun calc-offset (code-object insts-offset-bytes)
2056 (+ (ash (logand (get-header-data code-object) sb!vm:short-header-max-words)
2057 sb!vm:word-shift)
2058 insts-offset-bytes))
2060 (declaim (ftype (function (descriptor sb!vm:word sb!vm:word
2061 keyword &optional keyword) descriptor)
2062 cold-fixup))
2063 (defun cold-fixup (code-object after-header value kind &optional flavor)
2064 (declare (ignorable flavor))
2065 (let* ((offset-within-code-object (calc-offset code-object after-header))
2066 (gspace-byte-offset (+ (descriptor-byte-offset code-object)
2067 offset-within-code-object)))
2068 #!-(or x86 x86-64)
2069 (sb!vm::fixup-code-object code-object gspace-byte-offset value kind)
2071 #!+(or x86 x86-64)
2072 (let* ((gspace-data (descriptor-mem code-object))
2073 (obj-start-addr (logandc2 (descriptor-bits code-object) sb!vm:lowtag-mask))
2074 (code-end-addr
2075 (+ obj-start-addr
2076 (ash (logand (get-header-data code-object)
2077 sb!vm:short-header-max-words) sb!vm:word-shift)
2078 (descriptor-fixnum
2079 (read-wordindexed code-object sb!vm:code-code-size-slot))))
2080 (gspace-base (gspace-byte-address (descriptor-gspace code-object)))
2081 (in-dynamic-space
2082 (= (gspace-identifier (descriptor-intuit-gspace code-object))
2083 dynamic-core-space-id))
2084 (addr (+ value
2085 (sb!vm::sign-extend (bvref-32 gspace-data gspace-byte-offset)
2086 32))))
2088 (declare (ignorable code-end-addr in-dynamic-space))
2089 (assert (= obj-start-addr
2090 (+ gspace-base (descriptor-byte-offset code-object))))
2092 ;; See FIXUP-CODE-OBJECT in x86-vm.lisp and x86-64-vm.lisp.
2093 ;; Except for the use of saps, this is basically identical.
2094 (when (ecase kind
2095 (:absolute
2096 (setf (bvref-32 gspace-data gspace-byte-offset)
2097 (the (unsigned-byte 32) addr))
2098 ;; Absolute fixups are recorded if within the object for x86.
2099 #!+x86 (and in-dynamic-space
2100 (< obj-start-addr addr code-end-addr))
2101 ;; Absolute fixups on x86-64 do not refer to this code component,
2102 ;; because we have RIP-relative addressing, but references to
2103 ;; other immobile-space objects must be recorded.
2104 #!+x86-64
2105 (member flavor '(:named-call :layout :immobile-object
2106 :assembly-routine :static-call)))
2107 (:relative ; (used for arguments to X86 relative CALL instruction)
2108 (setf (bvref-32 gspace-data gspace-byte-offset)
2109 (the (signed-byte 32)
2110 (- addr (+ gspace-base gspace-byte-offset 4)))) ; 4 = size of rel32off
2111 ;; Relative fixups are recorded if without the object.
2112 ;; Except that read-only space contains calls to asm routines,
2113 ;; and we don't record those fixups.
2114 #!+x86 (and in-dynamic-space
2115 (not (< obj-start-addr addr code-end-addr)))
2116 #!+x86-64 nil))
2117 (push after-header (gethash (descriptor-bits code-object)
2118 *code-fixup-notes*)))))
2119 code-object)
2121 (defun resolve-static-call-fixups ()
2122 (dolist (fixup *cold-static-call-fixups*)
2123 (destructuring-bind (name kind code offset) fixup
2124 (cold-fixup code offset
2125 (cold-fun-entry-addr
2126 (cold-fdefn-fun (cold-fdefinition-object name)))
2127 kind :static-call))))
2129 #!+sb-dynamic-core
2130 (defun dyncore-note-symbol (symbol-name datap)
2131 "Register a symbol and return its address in proto-linkage-table."
2132 (+ sb!vm:linkage-table-space-start
2133 (* sb!vm:linkage-table-entry-size
2134 (ensure-gethash (if datap (list symbol-name) symbol-name)
2135 *cold-foreign-symbol-table*
2136 (hash-table-count *cold-foreign-symbol-table*)))))
2138 ;;; *COLD-FOREIGN-SYMBOL-TABLE* becomes *!INITIAL-FOREIGN-SYMBOLS* in
2139 ;;; the core. When the core is loaded, !LOADER-COLD-INIT uses this to
2140 ;;; create *STATIC-FOREIGN-SYMBOLS*, which the code in
2141 ;;; target-load.lisp refers to.
2142 (defun foreign-symbols-to-core ()
2143 (flet ((to-core (list transducer target-symbol)
2144 (cold-set target-symbol (vector-in-core (mapcar transducer list)))))
2145 #!-sb-dynamic-core
2146 ;; Sort by name
2147 (to-core (sort (%hash-table-alist *cold-foreign-symbol-table*) #'string< :key #'car)
2148 (lambda (symbol)
2149 (cold-cons (set-readonly (base-string-to-core (car symbol)))
2150 (number-to-core (cdr symbol))))
2151 '*!initial-foreign-symbols*)
2152 #!+sb-dynamic-core
2153 ;; Sort by index into linkage table
2154 (to-core (sort (%hash-table-alist *cold-foreign-symbol-table*) #'< :key #'cdr)
2155 (lambda (pair &aux (key (car pair))
2156 (sym (set-readonly (base-string-to-core
2157 (if (listp key) (car key) key)))))
2158 (if (listp key) (cold-list sym) sym))
2159 'sb!vm::+required-foreign-symbols+)
2160 (cold-set (cold-intern '*assembler-routines*) (car *cold-assembler-obj*))
2161 (to-core (sort *cold-assembler-routines* #'< :key 'cdr)
2162 (lambda (rtn)
2163 (cold-cons (cold-intern (first rtn)) (make-fixnum-descriptor (cdr rtn))))
2164 '*!initial-assembler-routines*)))
2167 ;;;; general machinery for cold-loading FASL files
2169 (defun pop-fop-stack (stack)
2170 (let ((top (svref stack 0)))
2171 (declare (type index top))
2172 (when (eql 0 top)
2173 (error "FOP stack empty"))
2174 (setf (svref stack 0) (1- top))
2175 (svref stack top)))
2177 ;;; Cause a fop to have a special definition for cold load.
2179 ;;; This is similar to DEFINE-FOP, but unlike DEFINE-FOP, this version
2180 ;;; looks up the encoding for this name (created by a previous DEFINE-FOP)
2181 ;;; instead of creating a new encoding.
2182 (defmacro define-cold-fop ((name &optional arglist) &rest forms)
2183 #+c-headers-only (declare (ignore name arglist forms))
2184 #-c-headers-only
2185 (let* ((code (get name 'opcode))
2186 (argc (aref (car **fop-signatures**) code))
2187 (fname (symbolicate "COLD-" name)))
2188 (unless code
2189 (error "~S is not a defined FOP." name))
2190 (when (and (plusp argc) (not (singleton-p arglist)))
2191 (error "~S must take one argument" name))
2192 `(progn
2193 (defun ,fname (.fasl-input. ,@arglist)
2194 (declare (ignorable .fasl-input.))
2195 (macrolet ((fasl-input () '(the fasl-input .fasl-input.))
2196 (fasl-input-stream () '(%fasl-input-stream (fasl-input)))
2197 (pop-stack ()
2198 '(pop-fop-stack (%fasl-input-stack (fasl-input)))))
2199 ,@forms))
2200 ;; We simply overwrite elements of **FOP-FUNS** since the contents
2201 ;; of the host are never propagated directly into the target core.
2202 ,@(loop for i from code to (logior code (if (plusp argc) 3 0))
2203 collect `(setf (svref **fop-funs** ,i) #',fname)))))
2205 ;;; Cause a fop to be undefined in cold load.
2206 (defmacro not-cold-fop (name)
2207 `(define-cold-fop (,name)
2208 (error "The fop ~S is not supported in cold load." ',name)))
2210 ;;; COLD-LOAD loads stuff into the core image being built by calling
2211 ;;; LOAD-AS-FASL with the fop function table rebound to a table of cold
2212 ;;; loading functions.
2213 (defun cold-load (filename verbose)
2214 "Load the file named by FILENAME into the cold load image being built."
2215 (when verbose
2216 (write-line (namestring filename)))
2217 (with-open-file (s filename :element-type '(unsigned-byte 8))
2218 (load-as-fasl s nil nil)))
2220 ;;;; miscellaneous cold fops
2222 (define-cold-fop (fop-misc-trap) *unbound-marker*)
2224 (define-cold-fop (fop-character (c))
2225 (make-character-descriptor c))
2227 (define-cold-fop (fop-empty-list) nil)
2228 (define-cold-fop (fop-truth) t)
2230 (define-cold-fop (fop-struct (size)) ; n-words incl. layout, excluding header
2231 (let* ((layout (pop-stack))
2232 (result (allocate-struct *dynamic* layout size))
2233 (bitmap (descriptor-fixnum
2234 (read-slot layout *host-layout-of-layout* :bitmap))))
2235 ;; Raw slots can not possibly work because dump-struct uses
2236 ;; %RAW-INSTANCE-REF/WORD which does not exist in the cross-compiler.
2237 ;; Remove this assertion if that problem is somehow circumvented.
2238 (unless (eql bitmap sb!kernel::+layout-all-tagged+)
2239 (error "Raw slots not working in genesis."))
2240 (loop for index downfrom (1- size) to sb!vm:instance-data-start
2241 for val = (pop-stack) then (pop-stack)
2242 do (write-wordindexed result
2243 (+ index sb!vm:instance-slots-offset)
2244 (if (logbitp index bitmap)
2246 (descriptor-word-sized-integer val))))
2247 result))
2249 (define-cold-fop (fop-layout)
2250 (let* ((bitmap-des (pop-stack))
2251 (length-des (pop-stack))
2252 (depthoid-des (pop-stack))
2253 (cold-inherits (pop-stack))
2254 (name (pop-stack))
2255 (old-layout-descriptor (gethash name *cold-layouts*)))
2256 (declare (type descriptor length-des depthoid-des cold-inherits))
2257 (declare (type symbol name))
2258 ;; If a layout of this name has been defined already
2259 (if old-layout-descriptor
2260 ;; Enforce consistency between the previous definition and the
2261 ;; current definition, then return the previous definition.
2262 (flet ((get-slot (keyword)
2263 (read-slot old-layout-descriptor *host-layout-of-layout* keyword)))
2264 (let ((old-length (descriptor-fixnum (get-slot :length)))
2265 (old-depthoid (descriptor-fixnum (get-slot :depthoid)))
2266 (old-bitmap (host-object-from-core (get-slot :bitmap)))
2267 (length (descriptor-fixnum length-des))
2268 (depthoid (descriptor-fixnum depthoid-des))
2269 (bitmap (host-object-from-core bitmap-des)))
2270 (unless (= length old-length)
2271 (error "cold loading a reference to class ~S when the compile~%~
2272 time length was ~S and current length is ~S"
2273 name
2274 length
2275 old-length))
2276 (unless (cold-vector-elements-eq cold-inherits (get-slot :inherits))
2277 (error "cold loading a reference to class ~S when the compile~%~
2278 time inherits were ~S~%~
2279 and current inherits are ~S"
2280 name
2281 (listify-cold-inherits cold-inherits)
2282 (listify-cold-inherits (get-slot :inherits))))
2283 (unless (= depthoid old-depthoid)
2284 (error "cold loading a reference to class ~S when the compile~%~
2285 time inheritance depthoid was ~S and current inheritance~%~
2286 depthoid is ~S"
2287 name
2288 depthoid
2289 old-depthoid))
2290 (unless (= bitmap old-bitmap)
2291 (error "cold loading a reference to class ~S when the compile~%~
2292 time raw-slot-bitmap was ~S and is currently ~S"
2293 name bitmap old-bitmap)))
2294 old-layout-descriptor)
2295 ;; Make a new definition from scratch.
2296 (make-cold-layout name length-des cold-inherits depthoid-des bitmap-des))))
2298 ;;;; cold fops for loading symbols
2300 ;;; Load a symbol SIZE characters long from FASL-INPUT, and
2301 ;;; intern that symbol in PACKAGE.
2302 (defun cold-load-symbol (length+flag package fasl-input)
2303 (let ((string (make-string (ash length+flag -1))))
2304 (read-string-as-bytes (%fasl-input-stream fasl-input) string)
2305 (push-fop-table (intern string package) fasl-input)))
2307 ;; I don't feel like hacking up DEFINE-COLD-FOP any more than necessary,
2308 ;; so this code is handcrafted to accept two operands.
2309 #-c-headers-only
2310 (flet ((fop-cold-symbol-in-package-save (fasl-input length+flag pkg-index)
2311 (cold-load-symbol length+flag (ref-fop-table fasl-input pkg-index)
2312 fasl-input)))
2313 (let ((i (get 'fop-symbol-in-package-save 'opcode)))
2314 (fill **fop-funs** #'fop-cold-symbol-in-package-save :start i :end (+ i 4))
2315 (values)))
2317 (define-cold-fop (fop-lisp-symbol-save (length+flag))
2318 (cold-load-symbol length+flag *cl-package* (fasl-input)))
2320 (define-cold-fop (fop-keyword-symbol-save (length+flag))
2321 (cold-load-symbol length+flag *keyword-package* (fasl-input)))
2323 (define-cold-fop (fop-uninterned-symbol-save (length+flag))
2324 (let ((name (make-string (ash length+flag -1))))
2325 (read-string-as-bytes (fasl-input-stream) name)
2326 (push-fop-table (get-uninterned-symbol name) (fasl-input))))
2328 (define-cold-fop (fop-copy-symbol-save (index))
2329 (let* ((symbol (ref-fop-table (fasl-input) index))
2330 (name
2331 (if (symbolp symbol)
2332 (symbol-name symbol)
2333 (base-string-from-core
2334 (read-wordindexed symbol sb!vm:symbol-name-slot)))))
2335 ;; Genesis performs additional coalescing of uninterned symbols
2336 (push-fop-table (get-uninterned-symbol name) (fasl-input))))
2338 ;;;; cold fops for loading packages
2340 (define-cold-fop (fop-named-package-save (namelen))
2341 (let ((name (make-string namelen)))
2342 (read-string-as-bytes (fasl-input-stream) name)
2343 (push-fop-table (find-package name) (fasl-input))))
2345 ;;;; cold fops for loading lists
2347 ;;; Make a list of the top LENGTH things on the fop stack. The last
2348 ;;; cdr of the list is set to LAST.
2349 (defmacro cold-stack-list (length last)
2350 `(do* ((index ,length (1- index))
2351 (result ,last (cold-cons (pop-stack) result)))
2352 ((= index 0) result)
2353 (declare (fixnum index))))
2355 (define-cold-fop (fop-list)
2356 (cold-stack-list (read-byte-arg (fasl-input-stream)) *nil-descriptor*))
2357 (define-cold-fop (fop-list*)
2358 (cold-stack-list (read-byte-arg (fasl-input-stream)) (pop-stack)))
2359 (define-cold-fop (fop-list-1)
2360 (cold-stack-list 1 *nil-descriptor*))
2361 (define-cold-fop (fop-list-2)
2362 (cold-stack-list 2 *nil-descriptor*))
2363 (define-cold-fop (fop-list-3)
2364 (cold-stack-list 3 *nil-descriptor*))
2365 (define-cold-fop (fop-list-4)
2366 (cold-stack-list 4 *nil-descriptor*))
2367 (define-cold-fop (fop-list-5)
2368 (cold-stack-list 5 *nil-descriptor*))
2369 (define-cold-fop (fop-list-6)
2370 (cold-stack-list 6 *nil-descriptor*))
2371 (define-cold-fop (fop-list-7)
2372 (cold-stack-list 7 *nil-descriptor*))
2373 (define-cold-fop (fop-list-8)
2374 (cold-stack-list 8 *nil-descriptor*))
2375 (define-cold-fop (fop-list*-1)
2376 (cold-stack-list 1 (pop-stack)))
2377 (define-cold-fop (fop-list*-2)
2378 (cold-stack-list 2 (pop-stack)))
2379 (define-cold-fop (fop-list*-3)
2380 (cold-stack-list 3 (pop-stack)))
2381 (define-cold-fop (fop-list*-4)
2382 (cold-stack-list 4 (pop-stack)))
2383 (define-cold-fop (fop-list*-5)
2384 (cold-stack-list 5 (pop-stack)))
2385 (define-cold-fop (fop-list*-6)
2386 (cold-stack-list 6 (pop-stack)))
2387 (define-cold-fop (fop-list*-7)
2388 (cold-stack-list 7 (pop-stack)))
2389 (define-cold-fop (fop-list*-8)
2390 (cold-stack-list 8 (pop-stack)))
2392 ;;;; cold fops for loading vectors
2394 (define-cold-fop (fop-base-string (len))
2395 (let ((string (make-string len)))
2396 (read-string-as-bytes (fasl-input-stream) string)
2397 (set-readonly (base-string-to-core string))))
2399 #!+sb-unicode
2400 (define-cold-fop (fop-character-string (len))
2401 (bug "CHARACTER-STRING[~D] dumped by cross-compiler." len))
2403 (define-cold-fop (fop-vector (size))
2404 (if (zerop size)
2405 *simple-vector-0-descriptor*
2406 (let ((result (allocate-vector-object *dynamic*
2407 sb!vm:n-word-bits
2408 size
2409 sb!vm:simple-vector-widetag)))
2410 (do ((index (1- size) (1- index)))
2411 ((minusp index))
2412 (declare (fixnum index))
2413 (write-wordindexed result
2414 (+ index sb!vm:vector-data-offset)
2415 (pop-stack)))
2416 (set-readonly result))))
2418 (define-cold-fop (fop-spec-vector)
2419 (let* ((len (read-word-arg (fasl-input-stream)))
2420 (type (read-byte-arg (fasl-input-stream)))
2421 (sizebits (aref **saetp-bits-per-length** type))
2422 (result (progn (aver (< sizebits 255))
2423 (allocate-vector-object *dynamic* sizebits len type)))
2424 (start (+ (descriptor-byte-offset result)
2425 (ash sb!vm:vector-data-offset sb!vm:word-shift)))
2426 (end (+ start
2427 (ceiling (* len sizebits)
2428 sb!vm:n-byte-bits))))
2429 (read-bigvec-as-sequence-or-die (descriptor-mem result)
2430 (fasl-input-stream)
2431 :start start
2432 :end end)
2433 (set-readonly result)))
2435 (not-cold-fop fop-array)
2436 #+nil
2437 ;; This code is unexercised. The only use of FOP-ARRAY is from target-dump.
2438 ;; It would be a shame to delete it though, as it might come in handy.
2439 (define-cold-fop (fop-array)
2440 (let* ((rank (read-word-arg (fasl-input-stream)))
2441 (data-vector (pop-stack))
2442 (result (allocate-object *dynamic*
2443 (+ sb!vm:array-dimensions-offset rank)
2444 sb!vm:other-pointer-lowtag)))
2445 (write-header-word result rank sb!vm:simple-array-widetag)
2446 (write-wordindexed result sb!vm:array-fill-pointer-slot *nil-descriptor*)
2447 (write-wordindexed result sb!vm:array-data-slot data-vector)
2448 (write-wordindexed result sb!vm:array-displacement-slot *nil-descriptor*)
2449 (write-wordindexed result sb!vm:array-displaced-p-slot *nil-descriptor*)
2450 (write-wordindexed result sb!vm:array-displaced-from-slot *nil-descriptor*)
2451 (let ((total-elements 1))
2452 (dotimes (axis rank)
2453 (let ((dim (pop-stack)))
2454 (unless (is-fixnum-lowtag (descriptor-lowtag dim))
2455 (error "non-fixnum dimension? (~S)" dim))
2456 (setf total-elements (* total-elements (descriptor-fixnum dim)))
2457 (write-wordindexed result
2458 (+ sb!vm:array-dimensions-offset axis)
2459 dim)))
2460 (write-wordindexed result
2461 sb!vm:array-elements-slot
2462 (make-fixnum-descriptor total-elements)))
2463 result))
2466 ;;;; cold fops for loading numbers
2468 (defmacro define-cold-number-fop (fop &optional arglist)
2469 ;; Invoke the ordinary warm version of this fop to cons the number.
2470 `(define-cold-fop (,fop ,arglist)
2471 (number-to-core (,fop (fasl-input) ,@arglist))))
2473 (define-cold-number-fop fop-single-float)
2474 (define-cold-number-fop fop-double-float)
2475 (define-cold-number-fop fop-word-integer)
2476 (define-cold-number-fop fop-byte-integer)
2477 (define-cold-number-fop fop-complex-single-float)
2478 (define-cold-number-fop fop-complex-double-float)
2479 (define-cold-number-fop fop-integer (n-bytes))
2481 (define-cold-fop (fop-ratio)
2482 (let ((den (pop-stack)))
2483 (number-pair-to-core (pop-stack) den sb!vm:ratio-widetag)))
2485 (define-cold-fop (fop-complex)
2486 (let ((im (pop-stack)))
2487 (number-pair-to-core (pop-stack) im sb!vm:complex-widetag)))
2489 ;;;; cold fops for calling (or not calling)
2491 (not-cold-fop fop-eval)
2492 (not-cold-fop fop-eval-for-effect)
2494 (defvar *load-time-value-counter*)
2496 (flet ((pop-args (fasl-input)
2497 (let ((args)
2498 (stack (%fasl-input-stack fasl-input)))
2499 (dotimes (i (read-byte-arg (%fasl-input-stream fasl-input))
2500 (values (pop-fop-stack stack) args))
2501 (push (pop-fop-stack stack) args))))
2502 (call (fun-name handler-name args)
2503 (acond ((get fun-name handler-name) (apply it args))
2504 (t (error "Can't ~S ~S in cold load" handler-name fun-name)))))
2506 (define-cold-fop (fop-funcall)
2507 (multiple-value-bind (fun args) (pop-args (fasl-input))
2508 (if args
2509 (case fun
2510 (fdefinition
2511 ;; Special form #'F fopcompiles into `(FDEFINITION ,f)
2512 (aver (and (singleton-p args) (symbolp (car args))))
2513 (target-symbol-function (car args)))
2514 (cons (cold-cons (first args) (second args)))
2515 (symbol-global-value (cold-symbol-value (first args)))
2516 (t (call fun :sb-cold-funcall-handler/for-value args)))
2517 (let ((counter *load-time-value-counter*))
2518 (push (cold-list (cold-intern :load-time-value) fun
2519 (number-to-core counter)) *!cold-toplevels*)
2520 (setf *load-time-value-counter* (1+ counter))
2521 (make-descriptor 0 :load-time-value counter)))))
2523 (define-cold-fop (fop-funcall-for-effect)
2524 (multiple-value-bind (fun args) (pop-args (fasl-input))
2525 (if (not args)
2526 (push fun *!cold-toplevels*)
2527 (case fun
2528 (sb!impl::%defun (apply #'cold-fset args))
2529 (sb!pcl::!trivial-defmethod (apply #'cold-defmethod args))
2530 (sb!kernel::%defstruct
2531 (push args *known-structure-classoids*)
2532 (push (apply #'cold-list (cold-intern 'defstruct) args)
2533 *!cold-toplevels*))
2534 (sb!c::%defconstant
2535 (destructuring-bind (name val . rest) args
2536 (cold-set name (if (symbolp val) (cold-intern val) val))
2537 (push (cold-cons (cold-intern name) (list-to-core rest))
2538 *!cold-defconstants*)))
2539 (set
2540 (aver (= (length args) 2))
2541 (cold-set (first args)
2542 (let ((val (second args)))
2543 (if (symbolp val) (cold-intern val) val))))
2544 (%svset (apply 'cold-svset args))
2545 (t (call fun :sb-cold-funcall-handler/for-effect args)))))))
2547 (defun finalize-load-time-value-noise ()
2548 (cold-set '*!load-time-values*
2549 (allocate-vector-object *dynamic*
2550 sb!vm:n-word-bits
2551 *load-time-value-counter*
2552 sb!vm:simple-vector-widetag)))
2555 ;;;; cold fops for fixing up circularities
2557 (define-cold-fop (fop-rplaca)
2558 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2559 (idx (read-word-arg (fasl-input-stream))))
2560 (write-memory (cold-nthcdr idx obj) (pop-stack))))
2562 (define-cold-fop (fop-rplacd)
2563 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2564 (idx (read-word-arg (fasl-input-stream))))
2565 (write-wordindexed (cold-nthcdr idx obj) 1 (pop-stack))))
2567 (define-cold-fop (fop-svset)
2568 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2569 (idx (read-word-arg (fasl-input-stream))))
2570 (write-wordindexed obj
2571 (+ idx
2572 (ecase (descriptor-lowtag obj)
2573 (#.sb!vm:instance-pointer-lowtag 1)
2574 (#.sb!vm:other-pointer-lowtag 2)))
2575 (pop-stack))))
2577 (define-cold-fop (fop-structset)
2578 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2579 (idx (read-word-arg (fasl-input-stream))))
2580 (write-wordindexed obj (+ idx sb!vm:instance-slots-offset) (pop-stack))))
2582 (define-cold-fop (fop-nthcdr)
2583 (cold-nthcdr (read-word-arg (fasl-input-stream)) (pop-stack)))
2585 (defun cold-nthcdr (index obj)
2586 (dotimes (i index)
2587 (setq obj (read-wordindexed obj sb!vm:cons-cdr-slot)))
2588 obj)
2590 ;;;; cold fops for loading code objects and functions
2592 (define-cold-fop (fop-fdefn)
2593 (cold-fdefinition-object (pop-stack)))
2595 (define-cold-fop (fop-known-fun)
2596 (let* ((name (pop-stack))
2597 (fun (cold-fdefn-fun (cold-fdefinition-object name))))
2598 (if (cold-null fun) `(:known-fun . ,name) fun)))
2600 #!-(or x86 (and x86-64 (not immobile-space)))
2601 (define-cold-fop (fop-sanctify-for-execution)
2602 (pop-stack))
2604 ;;; Setting this variable shows what code looks like before any
2605 ;;; fixups (or function headers) are applied.
2606 #!+sb-show (defvar *show-pre-fixup-code-p* nil)
2608 (defun cold-load-code (fasl-input code-size nconst nfuns)
2609 (macrolet ((pop-stack () '(pop-fop-stack (%fasl-input-stack fasl-input))))
2610 (let* ((raw-header-n-words (+ sb!vm:code-constants-offset nconst))
2611 ;; Note that the number of constants is rounded up to ensure
2612 ;; that the code vector will be properly aligned.
2613 (header-n-words (round-up raw-header-n-words 2))
2614 (toplevel-p (pop-stack))
2615 (debug-info (pop-stack))
2616 (des (allocate-cold-descriptor
2617 #!-immobile-code *dynamic*
2618 ;; toplevel-p is an indicator of whether the code will
2619 ;; will become garbage. If so, put it in dynamic space,
2620 ;; otherwise immobile space.
2621 #!+immobile-code
2622 (if toplevel-p *dynamic* *immobile-varyobj*)
2623 (+ (ash header-n-words sb!vm:word-shift) code-size)
2624 sb!vm:other-pointer-lowtag)))
2625 (declare (ignorable toplevel-p))
2626 (write-header-word des header-n-words sb!vm:code-header-widetag)
2627 (write-wordindexed des sb!vm:code-code-size-slot
2628 (make-fixnum-descriptor code-size))
2629 (write-wordindexed des sb!vm:code-debug-info-slot debug-info)
2630 (do ((index (1- raw-header-n-words) (1- index)))
2631 ((< index sb!vm:code-constants-offset))
2632 (let ((obj (pop-stack)))
2633 (if (and (consp obj) (eq (car obj) :known-fun))
2634 (push (list* (cdr obj) des index) *deferred-known-fun-refs*)
2635 (write-wordindexed des index obj))))
2636 (let* ((start (+ (descriptor-byte-offset des)
2637 (ash header-n-words sb!vm:word-shift)))
2638 (end (+ start code-size)))
2639 (read-bigvec-as-sequence-or-die (descriptor-mem des)
2640 (%fasl-input-stream fasl-input)
2641 :start start
2642 :end end)
2644 ;; Emulate NEW-SIMPLE-FUN in target-core
2645 (loop for fun-index from (1- nfuns) downto 0
2646 do (let ((offset (read-varint-arg fasl-input)))
2647 (if (> fun-index 0)
2648 (let ((bytes (descriptor-mem des))
2649 (index (+ (descriptor-byte-offset des)
2650 (calc-offset des (ash (1- fun-index) 2)))))
2651 (aver (eql (bvref-32 bytes index) 0))
2652 (setf (bvref-32 bytes index) offset))
2653 #!-64-bit
2654 (write-wordindexed/raw
2656 sb!vm::code-n-entries-slot
2657 (logior (ash offset 16)
2658 (ash nfuns sb!vm:n-fixnum-tag-bits)))
2659 #!+64-bit
2660 (write-wordindexed/raw
2661 des 0
2662 (logior (ash (logior (ash offset 16) nfuns) 32)
2663 (read-bits-wordindexed des 0))))))
2665 #!+sb-show
2666 (when *show-pre-fixup-code-p*
2667 (format *trace-output*
2668 "~&/raw code from code-fop ~W ~W:~%"
2669 nconst
2670 code-size)
2671 (do ((i start (+ i sb!vm:n-word-bytes)))
2672 ((>= i end))
2673 (format *trace-output*
2674 "/#X~8,'0x: #X~8,'0x~%"
2675 (+ i (gspace-byte-address (descriptor-gspace des)))
2676 (bvref-32 (descriptor-mem des) i)))))
2677 des)))
2679 #-c-headers-only
2680 (let ((i (get 'fop-code 'opcode)))
2681 (fill **fop-funs** #'cold-load-code :start i :end (+ i 4))
2682 (values))
2684 (defun resolve-deferred-known-funs ()
2685 (dolist (item *deferred-known-fun-refs*)
2686 (let ((fun (cold-fdefn-fun (cold-fdefinition-object (car item)))))
2687 (aver (not (cold-null fun)))
2688 (let ((place (cdr item)))
2689 (write-wordindexed (car place) (cdr place) fun)))))
2691 (define-cold-fop (fop-alter-code (slot))
2692 (let ((value (pop-stack))
2693 (code (pop-stack)))
2694 (write-wordindexed code slot value)))
2696 (defun fun-offset (code-object fun-index)
2697 (if (> fun-index 0)
2698 (bvref-32 (descriptor-mem code-object)
2699 (+ (descriptor-byte-offset code-object)
2700 (calc-offset code-object (ash (1- fun-index) 2))))
2701 (ldb (byte 16 16)
2702 #!-64-bit (read-bits-wordindexed code-object sb!vm::code-n-entries-slot)
2703 #!+64-bit (ldb (byte 32 32) (read-bits-wordindexed code-object 0)))))
2705 (defun compute-fun (code-object fun-index)
2706 (let* ((offset-from-insns-start (fun-offset code-object fun-index))
2707 (offset-from-code-start (calc-offset code-object offset-from-insns-start)))
2708 (unless (zerop (logand offset-from-code-start sb!vm:lowtag-mask))
2709 (error "unaligned function entry ~S ~S" code-object fun-index))
2710 (make-descriptor (logior (+ (logandc2 (descriptor-bits code-object) sb!vm:lowtag-mask)
2711 offset-from-code-start)
2712 sb!vm:fun-pointer-lowtag))))
2714 (defun cold-fop-fun-entry (fasl-input fun-index)
2715 (binding* (((info type arglist name code-object)
2716 (macrolet ((pop-stack ()
2717 '(pop-fop-stack (%fasl-input-stack fasl-input))))
2718 (values (pop-stack) (pop-stack) (pop-stack) (pop-stack) (pop-stack))))
2719 (fn (compute-fun code-object fun-index)))
2720 #!+(or x86 x86-64) ; store a machine-native pointer to the function entry
2721 ;; note that the bit pattern looks like fixnum due to alignment
2722 (write-wordindexed/raw fn sb!vm:simple-fun-self-slot
2723 (+ (- (descriptor-bits fn) sb!vm:fun-pointer-lowtag)
2724 (ash sb!vm:simple-fun-code-offset sb!vm:word-shift)))
2725 #!-(or x86 x86-64) ; store a pointer back to the function itself in 'self'
2726 (write-wordindexed fn sb!vm:simple-fun-self-slot fn)
2727 (write-wordindexed fn sb!vm:simple-fun-name-slot name)
2728 (write-wordindexed fn sb!vm:simple-fun-arglist-slot arglist)
2729 (write-wordindexed fn sb!vm:simple-fun-type-slot type)
2730 (write-wordindexed fn sb!vm::simple-fun-info-slot info)
2731 fn))
2733 #-c-headers-only
2734 (let ((i (get 'fop-fun-entry 'opcode)))
2735 (fill **fop-funs** #'cold-fop-fun-entry :start i :end (+ i 4))
2736 (values))
2738 ;;; For combining all assembler code components into one code component
2739 ;;; we have to adjust offsets of fixups into the single new component
2740 (defvar *fixup-offset-addend*)
2741 (defun read-fixup-offset (stream) (+ (read-word-arg stream) *fixup-offset-addend*))
2743 #!+sb-thread
2744 (define-cold-fop (fop-symbol-tls-fixup)
2745 (let* ((symbol (pop-stack))
2746 (kind (pop-stack))
2747 (code-object (pop-stack)))
2748 (cold-fixup code-object
2749 (read-fixup-offset (fasl-input-stream))
2750 (ensure-symbol-tls-index symbol)
2751 kind))) ; and re-push code-object
2753 (define-cold-fop (fop-foreign-fixup)
2754 (let* ((kind (pop-stack))
2755 (code-object (pop-stack))
2756 (len (read-byte-arg (fasl-input-stream)))
2757 (sym (make-string len))
2758 (dummy (read-string-as-bytes (fasl-input-stream) sym))
2759 (offset (read-fixup-offset (fasl-input-stream)))
2760 (value #!+sb-dynamic-core (dyncore-note-symbol sym nil)
2761 #!-sb-dynamic-core (cold-foreign-symbol-address sym)))
2762 (declare (ignore dummy))
2763 (cold-fixup code-object offset value kind :foreign))) ; and re-push code-object
2765 #!+linkage-table
2766 (define-cold-fop (fop-foreign-dataref-fixup)
2767 (let* ((kind (pop-stack))
2768 (code-object (pop-stack))
2769 (len (read-byte-arg (fasl-input-stream)))
2770 (sym (make-string len)))
2771 #!-sb-dynamic-core (declare (ignore code-object))
2772 (read-string-as-bytes (fasl-input-stream) sym)
2773 #!+sb-dynamic-core
2774 (let ((offset (read-word-arg (fasl-input-stream)))
2775 (value (dyncore-note-symbol sym t)))
2776 (cold-fixup code-object offset value kind :foreign-dataref)) ; and re-push code-object
2777 #!-sb-dynamic-core
2778 (progn
2779 (maphash (lambda (k v)
2780 (format *error-output* "~&~S = #X~8X~%" k v))
2781 *cold-foreign-symbol-table*)
2782 (error "shared foreign symbol in cold load: ~S (~S)" sym kind))))
2784 (define-cold-fop (fop-assembler-code)
2785 (let* ((length (read-word-arg (fasl-input-stream)))
2786 (aligned-length (round-up length (* 2 sb!vm:n-word-bytes)))
2787 (header-n-words
2788 ;; Note: we round the number of constants up to ensure that
2789 ;; the code vector will be properly aligned.
2790 (round-up sb!vm:code-constants-offset 2))
2791 (asm-code *cold-assembler-obj*)
2792 (des (car asm-code))
2793 (cur-length 0)
2794 (space (or #!+immobile-space *immobile-varyobj* *read-only*)))
2795 (cond (des
2796 (setq cur-length
2797 (descriptor-fixnum (read-wordindexed des sb!vm:code-code-size-slot)))
2798 (aver (= (gspace-free-word-index space)
2799 (+ (/ cur-length sb!vm:n-word-bytes) header-n-words)))
2800 (incf (gspace-free-word-index space) (/ aligned-length sb!vm:n-word-bytes)))
2802 (setq des (allocate-cold-descriptor
2803 space
2804 (+ (ash header-n-words sb!vm:word-shift) length)
2805 sb!vm:other-pointer-lowtag))
2806 (setf asm-code (list des) *cold-assembler-obj* asm-code)
2807 (write-header-word des header-n-words sb!vm:code-header-widetag)))
2808 (write-wordindexed des sb!vm:code-code-size-slot
2809 (make-fixnum-descriptor (+ cur-length aligned-length)))
2810 (push aligned-length (cdr asm-code))
2811 (let ((start (+ (descriptor-byte-offset des)
2812 (ash header-n-words sb!vm:word-shift)
2813 cur-length)))
2814 (read-bigvec-as-sequence-or-die (descriptor-mem des)
2815 (fasl-input-stream)
2816 :start start
2817 :end (+ start length)))
2818 des))
2820 (define-cold-fop (fop-assembler-routine)
2821 (let* ((name (pop-stack))
2822 (code-component (pop-stack))
2823 (offset (read-word-arg (fasl-input-stream))))
2824 (aver (eq code-component (car *cold-assembler-obj*)))
2825 (push (cons name (apply #'+ offset (cddr *cold-assembler-obj*)))
2826 *cold-assembler-routines*)
2827 code-component))
2829 (define-cold-fop (fop-assembler-fixup)
2830 (let* ((routine (pop-stack))
2831 (kind (pop-stack))
2832 (code-object (pop-stack))
2833 (offset (read-fixup-offset (fasl-input-stream))))
2834 (cold-fixup code-object offset (lookup-assembler-reference routine) kind)))
2836 (define-cold-fop (fop-code-object-fixup)
2837 (let* ((kind (pop-stack))
2838 (code-object (pop-stack))
2839 (offset (read-fixup-offset (fasl-input-stream)))
2840 (value (descriptor-bits code-object)))
2841 (cold-fixup code-object offset value kind))) ; and re-push code-object
2843 #!+immobile-space
2844 (progn
2845 (define-cold-fop (fop-layout-fixup)
2846 (let* ((obj (pop-stack))
2847 (kind (pop-stack))
2848 (code-object (pop-stack))
2849 (offset (read-fixup-offset (fasl-input-stream)))
2850 (cold-layout (or (gethash obj *cold-layouts*)
2851 (error "No cold-layout for ~S~%" obj))))
2852 (cold-fixup code-object offset
2853 (descriptor-bits cold-layout)
2854 kind :layout)))
2855 (define-cold-fop (fop-immobile-obj-fixup)
2856 (let ((obj (pop-stack))
2857 (kind (pop-stack))
2858 (code-object (pop-stack))
2859 (offset (read-fixup-offset (fasl-input-stream))))
2860 (cold-fixup code-object offset
2861 (descriptor-bits (if (symbolp obj) (cold-intern obj) obj))
2862 kind :immobile-object))))
2864 #!+immobile-code
2865 (define-cold-fop (fop-named-call-fixup)
2866 (let* ((name (pop-stack))
2867 (fdefn (cold-fdefinition-object name))
2868 (kind (pop-stack))
2869 (code-object (pop-stack))
2870 (offset (read-fixup-offset (fasl-input-stream))))
2871 (cold-fixup code-object offset
2872 (+ (descriptor-bits fdefn)
2873 (ash sb!vm:fdefn-raw-addr-slot sb!vm:word-shift)
2874 (- sb!vm:other-pointer-lowtag))
2875 kind :named-call)))
2877 #!+immobile-code
2878 (define-cold-fop (fop-static-call-fixup)
2879 (let ((name (pop-stack))
2880 (kind (pop-stack))
2881 (code-object (pop-stack))
2882 (offset (read-fixup-offset (fasl-input-stream))))
2883 (push (list name kind code-object offset) *cold-static-call-fixups*)
2884 code-object))
2887 ;;;; sanity checking space layouts
2889 (defun check-spaces ()
2890 ;;; Co-opt type machinery to check for intersections...
2891 (let (types)
2892 (flet ((check (start end space)
2893 (unless (< start end)
2894 (error "Bogus space: ~A" space))
2895 (let ((type (specifier-type `(integer ,start (,end)))))
2896 (dolist (other types)
2897 (unless (eq *empty-type* (type-intersection (cdr other) type))
2898 (error "Space overlap: ~A with ~A" space (car other))))
2899 (push (cons space type) types))))
2900 (check sb!vm:read-only-space-start sb!vm:read-only-space-end :read-only)
2901 (check sb!vm:static-space-start sb!vm:static-space-end :static)
2902 #!+gencgc
2903 (check sb!vm:dynamic-space-start
2904 (+ sb!vm:dynamic-space-start sb!vm::default-dynamic-space-size)
2905 :dynamic)
2906 #!+immobile-space
2907 ;; Must be a multiple of 32 because it makes the math a nicer
2908 ;; when computing word and bit index into the 'touched' bitmap.
2909 (assert (zerop (rem sb!vm:fixedobj-space-size
2910 (* 32 sb!vm:immobile-card-bytes))))
2911 #!-gencgc
2912 (progn
2913 (check sb!vm:dynamic-0-space-start sb!vm:dynamic-0-space-end :dynamic-0)
2914 (check sb!vm:dynamic-1-space-start sb!vm:dynamic-1-space-end :dynamic-1))
2915 #!+linkage-table
2916 (check sb!vm:linkage-table-space-start sb!vm:linkage-table-space-end :linkage-table))))
2918 ;;;; emitting C header file
2920 (defun tailwise-equal (string tail)
2921 (and (>= (length string) (length tail))
2922 (string= string tail :start1 (- (length string) (length tail)))))
2924 (defun write-boilerplate (*standard-output*)
2925 (format t "/*~%")
2926 (dolist (line
2927 '("This is a machine-generated file. Please do not edit it by hand."
2928 "(As of sbcl-0.8.14, it came from WRITE-CONFIG-H in genesis.lisp.)"
2930 "This file contains low-level information about the"
2931 "internals of a particular version and configuration"
2932 "of SBCL. It is used by the C compiler to create a runtime"
2933 "support environment, an executable program in the host"
2934 "operating system's native format, which can then be used to"
2935 "load and run 'core' files, which are basically programs"
2936 "in SBCL's own format."))
2937 (format t " *~@[ ~A~]~%" line))
2938 (format t " */~%"))
2940 (defun c-name (string &optional strip)
2941 (delete #\+
2942 (substitute-if #\_ (lambda (c) (member c '(#\- #\/ #\%)))
2943 (remove-if (lambda (c) (position c strip))
2944 string))))
2946 (defun c-symbol-name (symbol &optional strip)
2947 (c-name (symbol-name symbol) strip))
2949 (defun write-makefile-features (*standard-output*)
2950 ;; propagating *SHEBANG-FEATURES* into the Makefiles
2951 (dolist (shebang-feature-name (sort (mapcar #'c-symbol-name
2952 sb-cold:*shebang-features*)
2953 #'string<))
2954 (format t "LISP_FEATURE_~A=1~%" shebang-feature-name)))
2956 (defun write-config-h (*standard-output*)
2957 ;; propagating *SHEBANG-FEATURES* into C-level #define's
2958 (dolist (shebang-feature-name (sort (mapcar #'c-symbol-name
2959 sb-cold:*shebang-features*)
2960 #'string<))
2961 (format t "#define LISP_FEATURE_~A~%" shebang-feature-name))
2962 (terpri)
2963 ;; and miscellaneous constants
2964 (format t "#define SBCL_VERSION_STRING ~S~%"
2965 (sb!xc:lisp-implementation-version))
2966 (format t "#define CORE_MAGIC 0x~X~%" core-magic)
2967 (format t "#ifndef LANGUAGE_ASSEMBLY~2%")
2968 (format t "#define LISPOBJ(x) ((lispobj)x)~2%")
2969 (format t "#else /* LANGUAGE_ASSEMBLY */~2%")
2970 (format t "#define LISPOBJ(thing) thing~2%")
2971 (format t "#endif /* LANGUAGE_ASSEMBLY */~2%")
2972 (terpri))
2974 (defvar +c-literal-64bit+
2975 #!+(and win32 x86-64) "LLU" ; "long" is 32 bits, "long long" is 64 bits
2976 #!-(and win32 x86-64) "LU") ; "long" is 64 bits
2978 (defun write-constants-h (*standard-output*)
2979 ;; writing entire families of named constants
2980 (let ((constants nil))
2981 (dolist (package-name '("SB!VM"
2982 ;; We also propagate magic numbers
2983 ;; related to file format,
2984 ;; which live here instead of SB!VM.
2985 "SB!FASL"))
2986 (do-external-symbols (symbol (find-package package-name))
2987 (when (constantp symbol)
2988 (let ((name (symbol-name symbol)))
2989 (labels ( ;; shared machinery
2990 (record (string priority suffix)
2991 (push (list string
2992 priority
2993 (symbol-value symbol)
2994 suffix
2995 (documentation symbol 'variable))
2996 constants))
2997 ;; machinery for old-style CMU CL Lisp-to-C
2998 ;; arbitrary renaming, being phased out in favor of
2999 ;; the newer systematic RECORD-WITH-TRANSLATED-NAME
3000 ;; renaming
3001 (record-with-munged-name (prefix string priority)
3002 (record (concatenate
3003 'simple-string
3004 prefix
3005 (delete #\- (string-capitalize string)))
3006 priority
3007 ""))
3008 (maybe-record-with-munged-name (tail prefix priority)
3009 (when (tailwise-equal name tail)
3010 (record-with-munged-name prefix
3011 (subseq name 0
3012 (- (length name)
3013 (length tail)))
3014 priority)))
3015 ;; machinery for new-style SBCL Lisp-to-C naming
3016 (record-with-translated-name (priority large)
3017 (record (c-name name) priority
3018 (if large +c-literal-64bit+ "")))
3019 (maybe-record-with-translated-name (suffixes priority &key large)
3020 (when (some (lambda (suffix)
3021 (tailwise-equal name suffix))
3022 suffixes)
3023 (record-with-translated-name priority large))))
3024 (maybe-record-with-translated-name '("-LOWTAG" "-ALIGN") 0)
3025 (maybe-record-with-translated-name '("-WIDETAG" "-SHIFT") 1)
3026 (maybe-record-with-munged-name "-FLAG" "flag_" 2)
3027 (maybe-record-with-munged-name "-TRAP" "trap_" 3)
3028 (maybe-record-with-munged-name "-SUBTYPE" "subtype_" 4)
3029 (maybe-record-with-translated-name '("SHAREABLE+" "SHAREABLE-NONSTD+") 4)
3030 (maybe-record-with-munged-name "-SC-NUMBER" "sc_" 5)
3031 (maybe-record-with-translated-name '("-SIZE" "-INTERRUPTS") 6)
3032 (maybe-record-with-translated-name '("-START" "-END" "-PAGE-BYTES"
3033 "-CARD-BYTES" "-GRANULARITY")
3034 7 :large t)
3035 (maybe-record-with-translated-name '("-CORE-ENTRY-TYPE-CODE") 8)
3036 (maybe-record-with-translated-name '("-CORE-SPACE-ID") 9)
3037 (maybe-record-with-translated-name '("-CORE-SPACE-ID-FLAG") 9)
3038 (maybe-record-with-translated-name '("-GENERATION+") 10))))))
3039 ;; KLUDGE: these constants are sort of important, but there's no
3040 ;; pleasing way to inform the code above about them. So we fake
3041 ;; it for now. nikodemus on #lisp (2004-08-09) suggested simply
3042 ;; exporting every numeric constant from SB!VM; that would work,
3043 ;; but the C runtime would have to be altered to use Lisp-like names
3044 ;; rather than the munged names currently exported. --njf, 2004-08-09
3045 (dolist (c '(sb!vm:n-word-bits sb!vm:n-word-bytes
3046 sb!vm:n-lowtag-bits sb!vm:lowtag-mask
3047 sb!vm:n-widetag-bits sb!vm:widetag-mask
3048 sb!vm:n-fixnum-tag-bits sb!vm:fixnum-tag-mask
3049 sb!vm:short-header-max-words))
3050 (push (list (c-symbol-name c)
3051 -1 ; invent a new priority
3052 (symbol-value c)
3054 nil)
3055 constants))
3056 ;; One more symbol that doesn't fit into the code above.
3057 (let ((c 'sb!impl::+magic-hash-vector-value+))
3058 (push (list (c-symbol-name c) 9 (symbol-value c) +c-literal-64bit+ nil)
3059 constants))
3060 ;; And still one more
3061 #!+64-bit
3062 (let ((c 'sb!vm::immediate-widetags-mask))
3063 (push (list (c-symbol-name c)
3065 (logior (ash 1 (ash sb!vm:character-widetag -2))
3066 (ash 1 (ash sb!vm:single-float-widetag -2))
3067 (ash 1 (ash sb!vm:unbound-marker-widetag -2)))
3068 "LU"
3069 nil)
3070 constants))
3071 (setf constants
3072 (sort constants
3073 (lambda (const1 const2)
3074 (if (= (second const1) (second const2))
3075 (if (= (third const1) (third const2))
3076 (string< (first const1) (first const2))
3077 (< (third const1) (third const2)))
3078 (< (second const1) (second const2))))))
3079 (let ((prev-priority (second (car constants))))
3080 (dolist (const constants)
3081 (destructuring-bind (name priority value suffix doc) const
3082 (unless (= prev-priority priority)
3083 (terpri)
3084 (setf prev-priority priority))
3085 (when (minusp value)
3086 (error "stub: negative values unsupported"))
3087 (format t "#define ~A ~A~A /* 0x~X ~@[ -- ~A ~]*/~%" name value suffix value doc))))
3088 (terpri))
3090 (format t "#define BACKEND_PAGE_BYTES ~D~%" sb!c:+backend-page-bytes+)
3091 #!+gencgc
3092 (progn
3093 ;; value never needed in Lisp, so therefore not a defconstant
3094 (format t "#define GENCGC_CARD_SHIFT ~D~%"
3095 (1- (integer-length sb!vm:gencgc-card-bytes)))
3096 ;; symbol intentionally internal to sb-vm so that it won't add a #define
3097 (format t "#ifndef DEFAULT_DYNAMIC_SPACE_SIZE
3098 #define DEFAULT_DYNAMIC_SPACE_SIZE ~D /* ~:*0x~X */
3099 #endif~2%" sb!vm::default-dynamic-space-size))
3101 ;; writing information about internal errors
3102 ;; Assembly code needs only the constants for UNDEFINED_[ALIEN_]FUN_ERROR
3103 ;; but to avoid imparting that knowledge here, we'll expose all error
3104 ;; number constants except for OBJECT-NOT-<x>-ERROR ones.
3105 (loop for (description name) across sb!c:+backend-internal-errors+
3106 for i from 0
3107 when (stringp description)
3108 do (format t "#define ~A ~D~%" (c-symbol-name name) i))
3110 (terpri)
3112 ;; FIXME: The SPARC has a PSEUDO-ATOMIC-TRAP that differs between
3113 ;; platforms. If we export this from the SB!VM package, it gets
3114 ;; written out as #define trap_PseudoAtomic, which is confusing as
3115 ;; the runtime treats trap_ as the prefix for illegal instruction
3116 ;; type things. We therefore don't export it, but instead do
3117 #!+sparc
3118 (when (boundp 'sb!vm::pseudo-atomic-trap)
3119 (format t
3120 "#define PSEUDO_ATOMIC_TRAP ~D /* 0x~:*~X */~%"
3121 sb!vm::pseudo-atomic-trap)
3122 (terpri))
3123 ;; possibly this is another candidate for a rename (to
3124 ;; pseudo-atomic-trap-number or pseudo-atomic-magic-constant
3125 ;; [possibly applicable to other platforms])
3127 #!+sb-safepoint
3128 (format t "#define GC_SAFEPOINT_PAGE_ADDR ((void*)0x~XUL) /* ~:*~A */~%"
3129 sb!vm:gc-safepoint-page-addr)
3131 (dolist (symbol '(sb!vm::float-traps-byte
3132 sb!vm::float-exceptions-byte
3133 sb!vm::float-sticky-bits
3134 sb!vm::float-rounding-mode))
3135 (format t "#define ~A_POSITION ~A /* ~:*0x~X */~%"
3136 (c-symbol-name symbol)
3137 (sb!xc:byte-position (symbol-value symbol)))
3138 (format t "#define ~A_MASK 0x~X /* ~:*~A */~%"
3139 (c-symbol-name symbol)
3140 (sb!xc:mask-field (symbol-value symbol) -1))))
3142 (defun write-errnames-h (stream)
3143 ;; C code needs strings for describe_internal_error()
3144 (format stream "#define INTERNAL_ERROR_NAMES ~{\\~%~S~^, ~}~2%"
3145 (map 'list 'sb!kernel::!c-stringify-internal-error
3146 sb!c:+backend-internal-errors+))
3147 (format stream "#define INTERNAL_ERROR_NARGS {~{~S~^, ~}}~2%"
3148 (map 'list #'cddr sb!c:+backend-internal-errors+)))
3150 (defun write-tagnames-h (out)
3151 (labels
3152 ((pretty-name (symbol strip)
3153 (let ((name (string-downcase symbol)))
3154 (substitute #\Space #\-
3155 (subseq name 0 (- (length name) (length strip))))))
3156 (list-sorted-tags (tail)
3157 (loop for symbol being the external-symbols of "SB!VM"
3158 when (and (constantp symbol)
3159 (tailwise-equal (string symbol) tail)
3160 ;; FIXME: these symbols are obsolete
3161 (not (member symbol
3162 '(sb!vm:simple-fun-header-widetag
3163 sb!vm:closure-header-widetag))))
3164 collect symbol into tags
3165 finally (return (sort tags #'< :key #'symbol-value))))
3166 (write-tags (visibility kind limit ash-count)
3167 (format out "~%~Aconst char *~(~A~)_names[] = {~%"
3168 visibility (subseq kind 1))
3169 (let ((tags (list-sorted-tags kind)))
3170 (dotimes (i limit)
3171 (if (eql i (ash (or (symbol-value (first tags)) -1) ash-count))
3172 (format out " \"~A\"" (pretty-name (pop tags) kind))
3173 (format out " \"unknown [~D]\"" i))
3174 (unless (eql i (1- limit))
3175 (write-string "," out))
3176 (terpri out)))
3177 (write-line "};" out)))
3178 (write-tags "static " "-LOWTAG" sb!vm:lowtag-limit 0)
3179 ;; this -2 shift depends on every OTHER-IMMEDIATE-?-LOWTAG
3180 ;; ending with the same 2 bits. (#b10)
3181 (write-tags "" "-WIDETAG" (ash (1+ sb!vm:widetag-mask) -2) -2))
3182 ;; Inform print_otherptr() of all array types that it's too dumb to print
3183 (let ((array-type-bits (make-array 32 :initial-element 0)))
3184 (flet ((toggle (b)
3185 (multiple-value-bind (ofs bit) (floor b 8)
3186 (setf (aref array-type-bits ofs) (ash 1 bit)))))
3187 (dovector (saetp sb!vm:*specialized-array-element-type-properties*)
3188 (unless (member (sb!vm:saetp-specifier saetp) '(character base-char t))
3189 (toggle (sb!vm:saetp-typecode saetp))
3190 (awhen (sb!vm:saetp-complex-typecode saetp) (toggle it)))))
3191 (format out
3192 "~%static unsigned char unprintable_array_types[32] =~% {~{~d~^,~}};~%"
3193 (coerce array-type-bits 'list)))
3194 (dolist (prim-obj '(symbol ratio complex sb!vm::code simple-fun
3195 closure funcallable-instance
3196 weak-pointer fdefn sb!vm::value-cell))
3197 (format out "static char *~A_slots[] = {~%~{ \"~A: \",~} NULL~%};~%"
3198 (c-name (string-downcase prim-obj))
3199 (mapcar (lambda (x) (c-name (string-downcase (sb!vm:slot-name x))))
3200 (remove-if 'sb!vm:slot-rest-p
3201 (sb!vm::primitive-object-slots
3202 (find prim-obj sb!vm:*primitive-objects*
3203 :key 'sb!vm:primitive-object-name))))))
3204 (values))
3206 (defun write-cast-operator (name c-name lowtag)
3207 (format t "static inline struct ~A* ~A(lispobj obj) {
3208 return (struct ~A*)(obj - ~D);~%}~%" c-name name c-name lowtag))
3210 (defun write-primitive-object (obj *standard-output*)
3211 (let* ((name (sb!vm:primitive-object-name obj))
3212 (c-name (c-name (string-downcase name)))
3213 (slots (sb!vm:primitive-object-slots obj))
3214 (lowtag (or (symbol-value (sb!vm:primitive-object-lowtag obj)) 0)))
3215 ;; writing primitive object layouts
3216 (format t "#ifndef LANGUAGE_ASSEMBLY~2%")
3217 (format t "struct ~A {~%" c-name)
3218 (when (sb!vm:primitive-object-widetag obj)
3219 (format t " lispobj header;~%"))
3220 (dolist (slot slots)
3221 (format t " ~A ~A~@[[1]~];~%"
3222 (getf (sb!vm:slot-options slot) :c-type "lispobj")
3223 (c-name (string-downcase (sb!vm:slot-name slot)))
3224 (sb!vm:slot-rest-p slot)))
3225 (format t "};~%")
3226 (when (member name '(cons vector symbol fdefn))
3227 (write-cast-operator name c-name lowtag))
3228 (format t "~%#else /* LANGUAGE_ASSEMBLY */~2%")
3229 (format t "/* These offsets are SLOT-OFFSET * N-WORD-BYTES - LOWTAG~%")
3230 (format t " * so they work directly on tagged addresses. */~2%")
3231 (dolist (slot slots)
3232 (format t "#define ~A_~A_OFFSET ~D~%"
3233 (c-symbol-name name)
3234 (c-symbol-name (sb!vm:slot-name slot))
3235 (- (* (sb!vm:slot-offset slot) sb!vm:n-word-bytes) lowtag))))
3236 (format t "~%#endif /* LANGUAGE_ASSEMBLY */~2%"))
3238 (defun write-structure-object (dd *standard-output*)
3239 (flet ((cstring (designator) (c-name (string-downcase designator))))
3240 (format t "#ifndef LANGUAGE_ASSEMBLY~2%")
3241 (format t "struct ~A {~%" (cstring (dd-name dd)))
3242 (format t " lispobj header; // = word_0_~%")
3243 ;; "self layout" slots are named '_layout' instead of 'layout' so that
3244 ;; classoid's expressly declared layout isn't renamed as a special-case.
3245 #!-compact-instance-header (format t " lispobj _layout;~%")
3246 ;; Output exactly the number of Lisp words consumed by the structure,
3247 ;; no more, no less. C code can always compute the padded length from
3248 ;; the precise length, but the other way doesn't work.
3249 (let ((names
3250 (coerce (loop for i from sb!vm:instance-data-start below (dd-length dd)
3251 collect (list (format nil "word_~D_" (1+ i))))
3252 'vector)))
3253 (dolist (slot (dd-slots dd))
3254 (let ((cell (aref names (- (dsd-index slot) sb!vm:instance-data-start)))
3255 (name (cstring (dsd-name slot))))
3256 (if (eq (dsd-raw-type slot) t)
3257 (rplaca cell name)
3258 (rplacd cell name))))
3259 (loop for slot across names
3260 do (format t " lispobj ~A;~@[ // ~A~]~%" (car slot) (cdr slot))))
3261 (format t "};~%")
3262 (when (member (dd-name dd) '(layout))
3263 (write-cast-operator (dd-name dd) (cstring (dd-name dd))
3264 sb!vm:instance-pointer-lowtag))
3265 (format t "~%#endif /* LANGUAGE_ASSEMBLY */~2%")))
3267 (defun write-thread-init (stream)
3268 (dolist (binding sb!vm::!per-thread-c-interface-symbols)
3269 (format stream "write_TLS(~A, ~A, th);~%" ; KLUDGE: 'th' is a thread
3270 (c-symbol-name (if (listp binding) (car binding) binding) "*")
3271 (if (listp binding) (second binding)))))
3273 (defun write-static-symbols (stream)
3274 (dolist (symbol (cons nil (coerce sb!vm:+static-symbols+ 'list)))
3275 ;; FIXME: It would be nice to use longer names than NIL and
3276 ;; (particularly) T in #define statements.
3277 (format stream "#define ~A LISPOBJ(0x~X)~%"
3278 ;; FIXME: It would be nice not to need to strip anything
3279 ;; that doesn't get stripped always by C-SYMBOL-NAME.
3280 (c-symbol-name symbol "%*.!")
3281 (if *static* ; if we ran GENESIS
3282 ;; We actually ran GENESIS, use the real value.
3283 (descriptor-bits (cold-intern symbol))
3284 ;; We didn't run GENESIS, so guess at the address.
3285 (+ sb!vm:static-space-start
3286 sb!vm:n-word-bytes
3287 sb!vm:other-pointer-lowtag
3288 (if symbol (sb!vm:static-symbol-offset symbol) 0)))))
3289 #!+sb-thread
3290 (dolist (binding sb!vm::!per-thread-c-interface-symbols)
3291 (let* ((symbol (car (ensure-list binding)))
3292 (c-symbol (c-symbol-name symbol "*")))
3293 (unless (member symbol sb!vm::+common-static-symbols+)
3294 ;; So that "#ifdef thing" works, but not as a C expression
3295 (format stream "#define ~A (*)~%" c-symbol))
3296 (format stream "#define ~A_tlsindex 0x~X~%"
3297 c-symbol (ensure-symbol-tls-index symbol))))
3298 (loop for symbol in sb!vm::+c-callable-fdefns+
3299 for index from 0
3301 (format stream "#define ~A_FDEFN LISPOBJ(0x~X)~%"
3302 (c-symbol-name symbol)
3303 (if *static* ; if we ran GENESIS
3304 ;; We actually ran GENESIS, use the real value.
3305 (descriptor-bits (cold-fdefinition-object symbol))
3306 ;; We didn't run GENESIS, so guess at the address.
3307 (+ sb!vm:static-space-start
3308 sb!vm:n-word-bytes
3309 sb!vm:other-pointer-lowtag
3310 (* (length sb!vm:+static-symbols+)
3311 (sb!vm:pad-data-block sb!vm:symbol-size))
3312 (* index (sb!vm:pad-data-block sb!vm:fdefn-size)))))))
3314 (defun write-sc-offset-coding (stream)
3315 (flet ((write-array (name bytes)
3316 (format stream "static struct sc_offset_byte ~A[] = {~@
3317 ~{ {~{ ~2D, ~2D ~}}~^,~%~}~@
3318 };~2%"
3319 name
3320 (mapcar (lambda (byte)
3321 (list (byte-size byte) (byte-position byte)))
3322 bytes))))
3323 (format stream "struct sc_offset_byte {
3324 int size;
3325 int position;
3326 };~2%")
3327 (write-array "sc_offset_sc_number_bytes" sb!c::+sc-offset-scn-bytes+)
3328 (write-array "sc_offset_offset_bytes" sb!c::+sc-offset-offset-bytes+)))
3330 ;;;; writing map file
3332 ;;; Write a map file describing the cold load. Some of this
3333 ;;; information is subject to change due to relocating GC, but even so
3334 ;;; it can be very handy when attempting to troubleshoot the early
3335 ;;; stages of cold load.
3336 (defun write-map (*standard-output*)
3337 (let ((*print-pretty* nil)
3338 (*print-case* :upcase))
3339 (format t "Table of contents~%")
3340 (format t "=================~%")
3341 (let ((sections '("assembler routines"
3342 "defined functions"
3343 "undefined functions"
3344 "layouts"
3345 "type specifiers"
3346 "symbols")))
3347 (dotimes (i (length sections))
3348 (format t "~4<~@R.~> ~A~%" (1+ i) (nth i sections))))
3349 (format t "=================~2%")
3350 (format t "I. assembler routines defined in core image:~2%")
3351 (dolist (routine (reverse *cold-assembler-routines*))
3352 (let ((name (car routine)))
3353 (format t "~8,'0X: ~S~%" (lookup-assembler-reference name) name)))
3354 (let ((funs nil)
3355 (undefs nil))
3356 (maphash (lambda (name fdefn &aux (fun (cold-fdefn-fun fdefn)))
3357 (let ((fdefn-bits (descriptor-bits fdefn)))
3358 (if (cold-null fun)
3359 (push `(,fdefn-bits ,name) undefs)
3360 (push `(,fdefn-bits ,(descriptor-bits fun) ,name) funs))))
3361 *cold-fdefn-objects*)
3362 (format t "~%~|~%II. defined functions (alphabetically):
3364 FDEFN FUNCTION NAME
3365 ========== ========== ====~:{~%~10,'0X ~10,'0X ~S~}~%"
3366 (sort funs #'string<
3367 :key (lambda (x) (fun-name-block-name (caddr x)))))
3369 (format t "~%~|
3370 (a note about initially undefined function references: These functions
3371 are referred to by code which is installed by GENESIS, but they are not
3372 installed by GENESIS. This is not necessarily a problem; functions can
3373 be defined later, by cold init toplevel forms, or in files compiled and
3374 loaded at warm init, or elsewhere. As long as they are defined before
3375 they are called, everything should be OK. Things are also OK if the
3376 cross-compiler knew their inline definition and used that everywhere
3377 that they were called before the out-of-line definition is installed,
3378 as is fairly common for structure accessors.)
3380 III. initially undefined function references (alphabetically):
3382 FDEFN NAME
3383 ========== ====~:{~%~10,'0X ~S~}~%"
3384 (sort undefs #'string<
3385 :key (lambda (x) (fun-name-block-name (cadr x))))))
3387 (format t "~%~|~%IV. layout names:~2%")
3388 (dolist (x (sort-cold-layouts))
3389 (let* ((des (cdr x))
3390 (inherits (read-slot des *host-layout-of-layout* :inherits)))
3391 (format t "~8,'0X: ~S[~D]~%~10T~:S~%" (descriptor-bits des) (car x)
3392 (cold-layout-length des) (listify-cold-inherits inherits))))
3394 (format t "~%~|~%V. parsed type specifiers:~2%")
3395 (mapc (lambda (cell)
3396 (format t "~X: ~S~%" (descriptor-bits (cdr cell)) (car cell)))
3397 (sort (%hash-table-alist *ctype-cache*) #'<
3398 :key (lambda (x) (descriptor-bits (cdr x))))))
3400 (format t "~%~|~%VI. symbols (numerically):~2%")
3401 (mapc (lambda (cell) (format t "~X: ~S~%" (car cell) (cdr cell)))
3402 (sort (%hash-table-alist *cold-symbols*) #'< :key #'car))
3404 (values))
3406 ;;;; writing core file
3408 (defvar *core-file*)
3409 (defvar *data-page*)
3411 ;;; magic numbers to identify entries in a core file
3413 ;;; (In case you were wondering: No, AFAIK there's no special magic about
3414 ;;; these which requires them to be in the 38xx range. They're just
3415 ;;; arbitrary words, tested not for being in a particular range but just
3416 ;;; for equality. However, if you ever need to look at a .core file and
3417 ;;; figure out what's going on, it's slightly convenient that they're
3418 ;;; all in an easily recognizable range, and displacing the range away from
3419 ;;; zero seems likely to reduce the chance that random garbage will be
3420 ;;; misinterpreted as a .core file.)
3421 (defconstant build-id-core-entry-type-code 3860)
3422 (defconstant new-directory-core-entry-type-code 3861)
3423 (defconstant initial-fun-core-entry-type-code 3863)
3424 (defconstant page-table-core-entry-type-code 3880)
3425 (defconstant end-core-entry-type-code 3840)
3427 (declaim (ftype (function (sb!vm:word) sb!vm:word) write-word))
3428 (defun write-word (num)
3429 (ecase sb!c:*backend-byte-order*
3430 (:little-endian
3431 (dotimes (i sb!vm:n-word-bytes)
3432 (write-byte (ldb (byte 8 (* i 8)) num) *core-file*)))
3433 (:big-endian
3434 (dotimes (i sb!vm:n-word-bytes)
3435 (write-byte (ldb (byte 8 (* (- (1- sb!vm:n-word-bytes) i) 8)) num)
3436 *core-file*))))
3437 num)
3439 (defun output-gspace (gspace verbose)
3440 (force-output *core-file*)
3441 (let* ((posn (file-position *core-file*))
3442 (bytes (* (gspace-free-word-index gspace) sb!vm:n-word-bytes))
3443 (pages (ceiling bytes sb!c:+backend-page-bytes+))
3444 (total-bytes (* pages sb!c:+backend-page-bytes+)))
3446 (file-position *core-file*
3447 (* sb!c:+backend-page-bytes+ (1+ *data-page*)))
3448 (when verbose
3449 (format t "writing ~S byte~:P [~S page~:P] from ~S~%"
3450 total-bytes pages gspace))
3452 ;; Note: It is assumed that the GSPACE allocation routines always
3453 ;; allocate whole pages (of size +backend-page-bytes+) and that any
3454 ;; empty gspace between the free pointer and the end of page will
3455 ;; be zero-filled. This will always be true under Mach on machines
3456 ;; where the page size is equal. (RT is 4K, PMAX is 4K, Sun 3 is
3457 ;; 8K).
3458 (write-bigvec-as-sequence (gspace-data gspace)
3459 *core-file*
3460 :end total-bytes
3461 :pad-with-zeros t)
3462 (force-output *core-file*)
3463 (file-position *core-file* posn)
3465 ;; Write part of a (new) directory entry which looks like this:
3466 ;; GSPACE IDENTIFIER
3467 ;; WORD COUNT
3468 ;; DATA PAGE
3469 ;; ADDRESS
3470 ;; PAGE COUNT
3471 (write-word (gspace-identifier gspace))
3472 (write-word (gspace-free-word-index gspace))
3473 (write-word *data-page*)
3474 (multiple-value-bind (floor rem)
3475 (floor (gspace-byte-address gspace) 1024) ; units as per core.h
3476 (aver (zerop rem))
3477 (write-word floor))
3478 (write-word pages)
3480 (incf *data-page* pages)))
3482 ;;; Create a core file created from the cold loaded image. (This is
3483 ;;; the "initial core file" because core files could be created later
3484 ;;; by executing SAVE-LISP in a running system, perhaps after we've
3485 ;;; added some functionality to the system.)
3486 (defun write-initial-core-file (filename verbose)
3488 (let ((filenamestring (namestring filename))
3489 (*data-page* 0))
3491 (when verbose
3492 (format t "[building initial core file in ~S: ~%" filenamestring))
3494 (with-open-file (*core-file* filenamestring
3495 :direction :output
3496 :element-type '(unsigned-byte 8)
3497 :if-exists :rename-and-delete)
3499 ;; Write the magic number.
3500 (write-word core-magic)
3502 ;; Write the build ID, which contains a generated string
3503 ;; plus a suffix identifying a certain configuration of the C compiler.
3504 (binding* ((build-id (concatenate
3505 'string
3506 (with-open-file (s "output/build-id.inc") (read s))
3507 (if (member :msan sb-cold::*shebang-features*) "-msan" "")))
3508 ((nwords padding) (ceiling (length build-id) sb!vm:n-word-bytes)))
3509 (declare (type simple-string build-id))
3510 ;; Write BUILD-ID-CORE-ENTRY-TYPE-CODE, the length of the header,
3511 ;; length of the string, then base string chars + maybe padding.
3512 (write-word build-id-core-entry-type-code)
3513 (write-word (+ 3 nwords)) ; 3 = fixed overhead including this word
3514 (write-word (length build-id))
3515 (dovector (char build-id) (write-byte (sb!xc:char-code char) *core-file*))
3516 (dotimes (j (- padding)) (write-byte #xff *core-file*)))
3518 ;; Write the New Directory entry header.
3519 (write-word new-directory-core-entry-type-code)
3520 (let ((spaces (nconc (list *read-only* *static*)
3521 #!+immobile-space
3522 (list *immobile-fixedobj* *immobile-varyobj*)
3523 (list *dynamic*))))
3524 ;; length = (5 words/space) * N spaces + 2 for header.
3525 (write-word (+ (* (length spaces) 5) 2))
3526 (dolist (space spaces)
3527 (output-gspace space verbose)))
3529 ;; Write the initial function.
3530 (write-word initial-fun-core-entry-type-code)
3531 (write-word 3)
3532 (let* ((cold-name (cold-intern '!cold-init))
3533 (initial-fun
3534 (cold-fdefn-fun (cold-fdefinition-object cold-name))))
3535 (when verbose
3536 (format t "~&/INITIAL-FUN=#X~X~%" (descriptor-bits initial-fun)))
3537 (write-word (descriptor-bits initial-fun)))
3539 ;; Write the End entry.
3540 (write-word end-core-entry-type-code)
3541 (write-word 2)))
3543 (when verbose
3544 (format t "done]~%")
3545 (force-output))
3546 (values))
3548 ;;;; the actual GENESIS function
3550 ;;; Read the FASL files in OBJECT-FILE-NAMES and produce a Lisp core,
3551 ;;; and/or information about a Lisp core, therefrom.
3553 ;;; input file arguments:
3554 ;;; SYMBOL-TABLE-FILE-NAME names a UNIX-style .nm file *with* *any*
3555 ;;; *tab* *characters* *converted* *to* *spaces*. (We push
3556 ;;; responsibility for removing tabs out to the caller it's
3557 ;;; trivial to remove them using UNIX command line tools like
3558 ;;; sed, whereas it's a headache to do it portably in Lisp because
3559 ;;; #\TAB is not a STANDARD-CHAR.) If this file is not supplied,
3560 ;;; a core file cannot be built (but a C header file can be).
3562 ;;; output files arguments (any of which may be NIL to suppress output):
3563 ;;; CORE-FILE-NAME gets a Lisp core.
3564 ;;; C-HEADER-DIR-NAME gets the path in which to place generated headers
3565 ;;; MAP-FILE-NAME gets the name of the textual 'cold-sbcl.map' file
3566 (defun sb-cold:genesis (&key object-file-names
3567 core-file-name c-header-dir-name map-file-name
3568 symbol-table-file-name (verbose t))
3569 (declare (ignorable symbol-table-file-name))
3570 (declare (special core-file-name))
3572 (when verbose
3573 (format t
3574 "~&beginning GENESIS, ~A~%"
3575 (if core-file-name
3576 ;; Note: This output summarizing what we're doing is
3577 ;; somewhat telegraphic in style, not meant to imply that
3578 ;; we're not e.g. also creating a header file when we
3579 ;; create a core.
3580 (format nil "creating core ~S" core-file-name)
3581 (format nil "creating headers in ~S" c-header-dir-name))))
3583 (let ((*cold-foreign-symbol-table* (make-hash-table :test 'equal)))
3585 #!-(or sb-dynamic-core crossbuild-test)
3586 (when core-file-name
3587 (if symbol-table-file-name
3588 (load-cold-foreign-symbol-table symbol-table-file-name)
3589 (error "can't output a core file without symbol table file input")))
3591 ;; Now that we've successfully read our only input file (by
3592 ;; loading the symbol table, if any), it's a good time to ensure
3593 ;; that there'll be someplace for our output files to go when
3594 ;; we're done.
3595 (flet ((frob (filename)
3596 (when filename
3597 (ensure-directories-exist filename :verbose t))))
3598 (frob core-file-name)
3599 (frob map-file-name))
3601 ;; (This shouldn't matter in normal use, since GENESIS normally
3602 ;; only runs once in any given Lisp image, but it could reduce
3603 ;; confusion if we ever experiment with running, tweaking, and
3604 ;; rerunning genesis interactively.)
3605 (do-all-symbols (sym)
3606 (remprop sym 'cold-intern-info))
3608 (check-spaces)
3610 (let ((*foreign-symbol-placeholder-value* (if core-file-name nil 0))
3611 (*load-time-value-counter* 0)
3612 (*cold-fdefn-objects* (make-hash-table :test 'equal))
3613 (*cold-symbols* (make-hash-table :test 'eql)) ; integer keys
3614 (*cold-package-symbols* (make-hash-table :test 'equal)) ; string keys
3615 (*read-only* (make-gspace :read-only
3616 read-only-core-space-id
3617 sb!vm:read-only-space-start))
3618 (*static* (make-gspace :static
3619 static-core-space-id
3620 sb!vm:static-space-start))
3621 #!+immobile-space
3622 (*immobile-fixedobj* (make-gspace :immobile-fixedobj
3623 immobile-fixedobj-core-space-id
3624 sb!vm:fixedobj-space-start))
3625 #!+immobile-space
3626 (*immobile-varyobj* (make-gspace :immobile-varyobj
3627 immobile-varyobj-core-space-id
3628 sb!vm:varyobj-space-start))
3629 (*dynamic* (make-gspace :dynamic
3630 dynamic-core-space-id
3631 #!+gencgc sb!vm:dynamic-space-start
3632 #!-gencgc sb!vm:dynamic-0-space-start))
3633 (*nil-descriptor*)
3634 (*simple-vector-0-descriptor*)
3635 (*known-structure-classoids* nil)
3636 (*classoid-cells* (make-hash-table :test 'eq))
3637 (*ctype-cache* (make-hash-table :test 'equal))
3638 (*cold-layouts* (make-hash-table :test 'eq)) ; symbol -> cold-layout
3639 (*cold-layout-names* (make-hash-table :test 'eql)) ; addr -> symbol
3640 (*!cold-defconstants* nil)
3641 (*!cold-defuns* nil)
3642 ;; '*COLD-METHODS* is never seen in the target, so does not need
3643 ;; to adhere to the #\! convention for automatic uninterning.
3644 (*cold-methods* nil)
3645 (*!cold-toplevels* nil)
3646 *cold-static-call-fixups*
3647 *cold-assembler-routines*
3648 *cold-assembler-obj*
3649 (*fixup-offset-addend* 0)
3650 (*code-fixup-notes* (make-hash-table))
3651 (*deferred-known-fun-refs* nil))
3653 (setf *nil-descriptor* (make-nil-descriptor)
3654 *simple-vector-0-descriptor* (vector-in-core nil))
3656 ;; Load all assembler code
3657 (flet ((assembler-file-p (name) (tailwise-equal (namestring name) ".assem-obj")))
3658 (dolist (file-name (remove-if-not #'assembler-file-p object-file-names))
3659 (cold-load file-name verbose)
3660 (incf *fixup-offset-addend* (cadr *cold-assembler-obj*)))
3661 (setf object-file-names (remove-if #'assembler-file-p object-file-names)))
3662 (setf *fixup-offset-addend* 0)
3664 ;; Prepare for cold load.
3665 (initialize-layouts)
3666 (initialize-packages)
3667 (initialize-static-space)
3669 ;; Initialize the *COLD-SYMBOLS* system with the information
3670 ;; from common-lisp-exports.lisp-expr.
3671 ;; Packages whose names match SB!THING were set up on the host according
3672 ;; to "package-data-list.lisp-expr" which expresses the desired target
3673 ;; package configuration, so we can just mirror the host into the target.
3674 ;; But by waiting to observe calls to COLD-INTERN that occur during the
3675 ;; loading of the cross-compiler's outputs, it is possible to rid the
3676 ;; target of accidental leftover symbols, not that it wouldn't also be
3677 ;; a good idea to clean up package-data-list once in a while.
3678 (dolist (exported-name
3679 (sb-cold:read-from-file "common-lisp-exports.lisp-expr"))
3680 (cold-intern (intern exported-name *cl-package*) :access :external))
3682 ;; Create SB!KERNEL::*TYPE-CLASSES* as an array of NIL
3683 (cold-set (cold-intern 'sb!kernel::*type-classes*)
3684 (vector-in-core (make-list (length sb!kernel::*type-classes*))))
3686 ;; Cold load.
3687 (dolist (file-name object-file-names)
3688 (cold-load file-name verbose))
3690 (when *known-structure-classoids*
3691 (let ((dd-layout (find-layout 'defstruct-description)))
3692 (dolist (defstruct-args *known-structure-classoids*)
3693 (let* ((dd (first defstruct-args))
3694 (name (warm-symbol (read-slot dd dd-layout :name)))
3695 (layout (gethash name *cold-layouts*)))
3696 (aver layout)
3697 (write-slots layout *host-layout-of-layout* :info dd))))
3698 (when verbose
3699 (format t "~&; SB!Loader: (~D~@{+~D~}) structs/consts/funs/methods/other~%"
3700 (length *known-structure-classoids*)
3701 (length *!cold-defconstants*)
3702 (length *!cold-defuns*)
3703 (reduce #'+ *cold-methods* :key (lambda (x) (length (cdr x))))
3704 (length *!cold-toplevels*))))
3706 (dolist (symbol '(*!cold-defconstants* *!cold-defuns* *!cold-toplevels*))
3707 (cold-set symbol (list-to-core (nreverse (symbol-value symbol))))
3708 (makunbound symbol)) ; so no further PUSHes can be done
3710 (cold-set
3711 'sb!pcl::*!trivial-methods*
3712 (list-to-core
3713 (loop for (gf-name . methods) in *cold-methods*
3714 collect
3715 (cold-cons
3716 (cold-intern gf-name)
3717 (vector-in-core
3718 (loop for (class qual lambda-list fun source-loc)
3719 ;; Methods must be sorted because we invoke
3720 ;; only the first applicable one.
3721 in (stable-sort methods #'> ; highest depthoid first
3722 :key (lambda (method)
3723 (class-depthoid (car method))))
3724 collect
3725 (cold-list (cold-intern
3726 (and (null qual) (predicate-for-specializer class)))
3728 (cold-intern class)
3729 (cold-intern qual)
3730 lambda-list source-loc)))))))
3732 ;; Tidy up loose ends left by cold loading. ("Postpare from cold load?")
3733 (resolve-deferred-known-funs)
3734 (resolve-static-call-fixups)
3735 (foreign-symbols-to-core)
3736 #!+(or x86 immobile-space)
3737 (dolist (pair (sort (%hash-table-alist *code-fixup-notes*) #'< :key #'car))
3738 (write-wordindexed (make-random-descriptor (car pair))
3739 sb!vm::code-fixups-slot
3740 #!+x86 (ub32-vector-in-core (cdr pair))
3741 #!+x86-64 (number-to-core
3742 (sb!c::pack-code-fixup-locs
3743 (sort (cdr pair) #'<)))))
3744 (when core-file-name
3745 (finish-symbols))
3746 (finalize-load-time-value-noise)
3748 ;; Write results to files.
3749 (when map-file-name
3750 (with-open-file (stream map-file-name :direction :output :if-exists :supersede)
3751 (write-map stream)))
3752 (when core-file-name
3753 (write-initial-core-file core-file-name verbose))
3754 (unless c-header-dir-name
3755 (return-from sb-cold:genesis))
3756 (let ((filename (format nil "~A/Makefile.features" c-header-dir-name)))
3757 (ensure-directories-exist filename)
3758 (with-open-file (stream filename :direction :output :if-exists :supersede)
3759 (write-makefile-features stream)))
3761 (macrolet ((out-to (name &body body) ; write boilerplate and inclusion guard
3762 `(with-open-file (stream (format nil "~A/~A.h" c-header-dir-name ,name)
3763 :direction :output :if-exists :supersede)
3764 (write-boilerplate stream)
3765 (format stream
3766 "#ifndef SBCL_GENESIS_~A~%#define SBCL_GENESIS_~:*~A~%"
3767 (c-name (string-upcase ,name)))
3768 ,@body
3769 (format stream "#endif~%"))))
3770 (out-to "config" (write-config-h stream))
3771 (out-to "constants" (write-constants-h stream))
3772 (out-to "errnames" (write-errnames-h stream))
3773 (out-to "gc-tables" (sb!vm::write-gc-tables stream))
3774 (out-to "tagnames" (write-tagnames-h stream))
3775 (let ((structs (sort (copy-list sb!vm:*primitive-objects*) #'string<
3776 :key #'sb!vm:primitive-object-name)))
3777 (dolist (obj structs)
3778 (out-to (string-downcase (sb!vm:primitive-object-name obj))
3779 (write-primitive-object obj stream)))
3780 (out-to "primitive-objects"
3781 (dolist (obj structs)
3782 (format stream "~&#include \"~A.h\"~%"
3783 (string-downcase (sb!vm:primitive-object-name obj))))))
3784 (dolist (class '(classoid defstruct-description hash-table layout package
3785 sb!c::compiled-debug-info sb!c::compiled-debug-fun))
3786 (out-to (string-downcase class)
3787 (write-structure-object (layout-info (find-layout class)) stream)))
3788 (with-open-file (stream (format nil "~A/thread-init.inc" c-header-dir-name)
3789 :direction :output :if-exists :supersede)
3790 (write-boilerplate stream) ; no inclusion guard, it's not a ".h" file
3791 (write-thread-init stream))
3792 (out-to "static-symbols" (write-static-symbols stream))
3793 (out-to "sc-offset" (write-sc-offset-coding stream))))))
3795 ;;; Invert the action of HOST-CONSTANT-TO-CORE. If STRICTP is given as NIL,
3796 ;;; then we can produce a host object even if it is not a faithful rendition.
3797 (defun host-object-from-core (descriptor &optional (strictp t))
3798 (named-let recurse ((x descriptor))
3799 (when (cold-null x)
3800 (return-from recurse nil))
3801 (when (eq (descriptor-gspace x) :load-time-value)
3802 (error "Can't warm a deferred LTV placeholder"))
3803 (when (is-fixnum-lowtag (descriptor-lowtag x))
3804 (return-from recurse (descriptor-fixnum x)))
3805 (ecase (descriptor-lowtag x)
3806 (#.sb!vm:instance-pointer-lowtag
3807 (if strictp (error "Can't invert INSTANCE type") "#<instance>"))
3808 (#.sb!vm:list-pointer-lowtag
3809 (cons (recurse (cold-car x)) (recurse (cold-cdr x))))
3810 (#.sb!vm:fun-pointer-lowtag
3811 (if strictp
3812 (error "Can't map cold-fun -> warm-fun")
3813 (let ((name (read-wordindexed x sb!vm:simple-fun-name-slot)))
3814 `(function ,(recurse name)))))
3815 (#.sb!vm:other-pointer-lowtag
3816 (let ((widetag (logand (descriptor-bits (read-memory x))
3817 sb!vm:widetag-mask)))
3818 (ecase widetag
3819 (#.sb!vm:symbol-widetag
3820 (if strictp
3821 (warm-symbol x)
3822 (or (gethash (descriptor-bits x) *cold-symbols*) ; first try
3823 (make-symbol
3824 (recurse (read-wordindexed x sb!vm:symbol-name-slot))))))
3825 (#.sb!vm:simple-base-string-widetag (base-string-from-core x))
3826 (#.sb!vm:simple-vector-widetag (vector-from-core x #'recurse))
3827 (#.sb!vm:bignum-widetag (bignum-from-core x))))))))