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.
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
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.
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
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
+
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
57 `(simple-array (unsigned-byte 8) (,+smallvec-length
+)))
59 (defun make-smallvec ()
60 (make-array +smallvec-length
+ :element-type
'(unsigned-byte 8)
63 ;;; a big vector, implemented as a vector of SMALLVECs
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
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
+)
85 (svref (bigvec-outer-vector bigvec
) outer-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
))
95 ;;; analogous to LENGTH, but for a BIGVEC
97 ;;; the length of BIGVEC, measured in the number of BVREFable bytes it
99 (defun bvlength (bigvec)
100 (* (length (bigvec-outer-vector bigvec
))
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
)
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
)
129 (setf (bigvec-outer-vector 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
140 (let* ((name (intern (format nil
"BVREF-~A" n
)))
141 (number-octets (/ n
8))
143 (loop for i from
0 to
(1- number-octets
)
144 collect
`(ash (bvref bigvec
(+ byte-index
,i
))
147 (loop for i from
0 to
(1- number-octets
)
148 collect
`(ash (bvref bigvec
150 ,(- number-octets
1 i
)))
153 (loop for i from
0 to
(1- number-octets
)
155 `((bvref bigvec
(+ byte-index
,i
))
156 (ldb (byte 8 ,(* i
8)) new-value
))))
158 (loop for i from
0 to
(1- number-octets
)
160 `((bvref bigvec
(+ byte-index
,i
))
161 (ldb (byte 8 ,(- n
8 (* i
8))) new-value
)))))
163 (defun ,name
(bigvec byte-index
)
164 (logior ,@(ecase sb
!c
:*backend-byte-order
*
165 (:little-endian ash-list-le
)
166 (:big-endian ash-list-be
))))
167 (defun (setf ,name
) (new-value bigvec byte-index
)
168 (setf ,@(ecase sb
!c
:*backend-byte-order
*
169 (:little-endian setf-list-le
)
170 (:big-endian setf-list-be
))))))))
176 ;; lispobj-sized word, whatever that may be
177 ;; hopefully nobody ever wants a 128-bit SBCL...
178 (macrolet ((acc (bv index
) `(#!+64-bit bvref-64
#!-
64-bit bvref-32
,bv
,index
)))
179 (defun (setf bvref-word
) (new-val bytes index
) (setf (acc bytes index
) new-val
))
180 (defun bvref-word (bytes index
) (acc bytes index
)))
182 ;;;; representation of spaces in the core
184 ;;; If there is more than one dynamic space in memory (i.e., if a
185 ;;; copying GC is in use), then only the active dynamic space gets
188 (defconstant dynamic-core-space-id
1)
191 (defconstant static-core-space-id
2)
194 (defconstant read-only-core-space-id
3)
198 (defvar *immobile-fixedobj
*)
199 (defvar *immobile-varyobj
*)
200 (defconstant immobile-fixedobj-core-space-id
4)
201 (defconstant immobile-varyobj-core-space-id
5)
202 (defvar *immobile-space-map
* nil
))
204 (defconstant max-core-space-id
5)
205 (defconstant deflated-core-space-id-flag
8)
207 ;; This is somewhat arbitrary as there is no concept of the the
208 ;; number of bits in the "low" part of a descriptor any more.
209 (defconstant target-space-alignment
(ash 1 16)
210 "the alignment requirement for spaces in the target.")
212 ;;; a GENESIS-time representation of a memory space (e.g. read-only
213 ;;; space, dynamic space, or static space)
214 (defstruct (gspace (:constructor %make-gspace
)
216 ;; name and identifier for this GSPACE
217 (name (missing-arg) :type symbol
:read-only t
)
218 (identifier (missing-arg) :type fixnum
:read-only t
)
219 ;; the word address where the data will be loaded
220 (word-address (missing-arg) :type unsigned-byte
:read-only t
)
221 ;; the data themselves. (Note that in CMU CL this was a pair of
222 ;; fields SAP and WORDS-ALLOCATED, but that wasn't very portable.)
223 ;; (And then in SBCL this was a VECTOR, but turned out to be
224 ;; unportable too, since ANSI doesn't think that arrays longer than
225 ;; 1024 (!) should needed by portable CL code...)
226 (bytes (make-bigvec) :read-only t
)
227 ;; the index of the next unwritten word (i.e. chunk of
228 ;; SB!VM:N-WORD-BYTES bytes) in BYTES, or equivalently the number of
229 ;; words actually written in BYTES. In order to convert to an actual
230 ;; index into BYTES, thus must be multiplied by SB!VM:N-WORD-BYTES.
233 (defun gspace-byte-address (gspace)
234 (ash (gspace-word-address gspace
) sb
!vm
:word-shift
))
236 (cl:defmethod
print-object ((gspace gspace
) stream
)
237 (print-unreadable-object (gspace stream
:type t
)
238 (format stream
"@#x~X ~S" (gspace-byte-address gspace
) (gspace-name gspace
))))
240 (defun make-gspace (name identifier byte-address
)
241 (unless (zerop (rem byte-address target-space-alignment
))
242 (error "The byte address #X~X is not aligned on a #X~X-byte boundary."
244 target-space-alignment
))
245 (%make-gspace
:name name
246 :identifier identifier
247 :word-address
(ash byte-address
(- sb
!vm
:word-shift
))))
249 ;;;; representation of descriptors
251 (declaim (inline is-fixnum-lowtag
))
252 (defun is-fixnum-lowtag (lowtag)
253 (zerop (logand lowtag sb
!vm
:fixnum-tag-mask
)))
255 (defun is-other-immediate-lowtag (lowtag)
256 ;; The other-immediate lowtags are similar to the fixnum lowtags, in
257 ;; that they have an "effective length" that is shorter than is used
258 ;; for the pointer lowtags. Unlike the fixnum lowtags, however, the
259 ;; other-immediate lowtags are always effectively two bits wide.
260 (= (logand lowtag
3) sb
!vm
:other-immediate-0-lowtag
))
262 (defstruct (descriptor
263 (:constructor make-descriptor
(bits &optional gspace word-offset
))
265 ;; the GSPACE that this descriptor is allocated in, or NIL if not set yet.
266 (gspace nil
:type
(or gspace
(eql :load-time-value
) null
))
267 ;; the offset in words from the start of GSPACE, or NIL if not set yet
268 (word-offset nil
:type
(or sb
!vm
:word null
))
269 (bits 0 :read-only t
:type
(unsigned-byte #.sb
!vm
:n-machine-word-bits
)))
271 (declaim (inline descriptor
=))
272 (defun descriptor= (a b
) (eql (descriptor-bits a
) (descriptor-bits b
)))
274 (defun make-random-descriptor (bits)
275 (make-descriptor (logand bits sb
!ext
:most-positive-word
)))
277 (declaim (inline descriptor-lowtag
))
278 (defun descriptor-lowtag (des)
279 "the lowtag bits for DES"
280 (logand (descriptor-bits des
) sb
!vm
:lowtag-mask
))
282 (cl:defmethod
print-object ((des descriptor
) stream
)
283 (let ((lowtag (descriptor-lowtag des
)))
284 (print-unreadable-object (des stream
:type t
)
285 (cond ((eq (descriptor-gspace des
) :load-time-value
)
286 (format stream
"for LTV ~D" (descriptor-word-offset des
)))
287 ((is-fixnum-lowtag lowtag
)
288 (format stream
"for fixnum: ~W" (descriptor-fixnum des
)))
289 ((is-other-immediate-lowtag lowtag
)
291 "for other immediate: #X~X, type #b~8,'0B"
292 (ash (descriptor-bits des
) (- sb
!vm
:n-widetag-bits
))
293 (logand (descriptor-bits des
) sb
!vm
:widetag-mask
)))
296 "for pointer: #X~X, lowtag #b~v,'0B, ~A"
297 (logandc2 (descriptor-bits des
) sb
!vm
:lowtag-mask
)
298 sb
!vm
:n-lowtag-bits lowtag
299 (let ((gspace (descriptor-gspace des
)))
304 ;;; Return a descriptor for a block of LENGTH bytes out of GSPACE. The
305 ;;; free word index is boosted as necessary, and if additional memory
306 ;;; is needed, we grow the GSPACE. The descriptor returned is a
307 ;;; pointer of type LOWTAG.
308 (defun allocate-cold-descriptor (gspace length lowtag
&optional page-attributes
)
310 (gspace-claim-n-bytes gspace length page-attributes
))
311 (ptr (+ (gspace-word-address gspace
) word-index
)))
312 (make-descriptor (logior (ash ptr sb
!vm
:word-shift
) lowtag
)
316 (defun gspace-claim-n-words (gspace n-words
)
317 (let* ((old-free-word-index (gspace-free-word-index gspace
))
318 (new-free-word-index (+ old-free-word-index n-words
)))
319 ;; Grow GSPACE as necessary until it's big enough to handle
320 ;; NEW-FREE-WORD-INDEX.
322 ((>= (bvlength (gspace-bytes gspace
))
323 (* new-free-word-index sb
!vm
:n-word-bytes
)))
324 (expand-bigvec (gspace-bytes gspace
)))
325 ;; Now that GSPACE is big enough, we can meaningfully grab a chunk of it.
326 (setf (gspace-free-word-index gspace
) new-free-word-index
)
327 old-free-word-index
))
329 ;; align256p is true if we need to force objects on this page to 256-byte
330 ;; boundaries. This doesn't need to be generalized - everything of type
331 ;; INSTANCE is either on its natural alignment, or 256-byte.
332 ;; [See doc/internals-notes/compact-instance for why you might want it at all]
333 ;; PAGE-KIND is a heuristic for placement of symbols
334 ;; based on being interned/uninterned/likely-special-variable.
335 (defun make-page-attributes (align256p page-kind
)
336 (declare (type (or null
(integer 0 3)) page-kind
))
337 (logior (ash (or page-kind
0) 1) (if align256p
1 0)))
338 (defun immobile-obj-spacing-words (page-attributes)
339 (if (logbitp 0 page-attributes
)
340 (/ 256 sb
!vm
:n-word-bytes
)))
342 (defun gspace-claim-n-bytes (gspace specified-n-bytes page-attributes
)
343 (declare (ignorable page-attributes
))
344 (let* ((n-bytes (round-up specified-n-bytes
(ash 1 sb
!vm
:n-lowtag-bits
)))
345 (n-words (ash n-bytes
(- sb
!vm
:word-shift
))))
346 (aver (evenp n-words
))
347 (cond #!+immobile-space
348 ((eq gspace
*immobile-fixedobj
*)
349 (aver page-attributes
)
350 ;; An immobile fixedobj page can only have one value of object-spacing
351 ;; and size for all objects on it. Different widetags are ok.
352 (let* ((key (cons specified-n-bytes page-attributes
))
353 (found (cdr (assoc key
*immobile-space-map
* :test
'equal
)))
354 (page-n-words (/ sb
!vm
:immobile-card-bytes sb
!vm
:n-word-bytes
)))
355 (unless found
; grab one whole GC page from immobile space
356 (let ((free-word-index
357 (gspace-claim-n-words gspace page-n-words
)))
358 (setf found
(cons 0 free-word-index
))
359 (push (cons key found
) *immobile-space-map
*)))
360 (destructuring-bind (page-word-index . page-base-index
) found
363 (or (immobile-obj-spacing-words page-attributes
)
365 (if (> next-word
(- page-n-words n-words
))
366 ;; no more objects fit on this page
367 (setf *immobile-space-map
*
368 (delete key
*immobile-space-map
* :key
'car
:test
'equal
))
369 (setf (car found
) next-word
)))
370 (+ page-word-index page-base-index
))))
372 (gspace-claim-n-words gspace n-words
)))))
374 (defun descriptor-fixnum (des)
375 (unless (is-fixnum-lowtag (descriptor-lowtag des
))
376 (error "descriptor-fixnum called on non-fixnum ~S" des
))
377 (let* ((descriptor-bits (descriptor-bits des
))
378 (bits (ash descriptor-bits
(- sb
!vm
:n-fixnum-tag-bits
))))
379 (if (logbitp (1- sb
!vm
:n-word-bits
) descriptor-bits
)
380 (logior bits
(ash -
1 (1+ sb
!vm
:n-positive-fixnum-bits
)))
383 (defun descriptor-word-sized-integer (des)
384 ;; Extract an (unsigned-byte 32), from either its fixnum or bignum
386 (let ((lowtag (descriptor-lowtag des
)))
387 (if (is-fixnum-lowtag lowtag
)
388 (make-random-descriptor (descriptor-fixnum des
))
389 (read-wordindexed des
1))))
392 (defun descriptor-mem (des)
393 (gspace-bytes (descriptor-intuit-gspace des
)))
394 (defun descriptor-byte-offset (des)
395 (ash (descriptor-word-offset des
) sb
!vm
:word-shift
))
397 ;;; If DESCRIPTOR-GSPACE is already set, just return that. Otherwise,
398 ;;; figure out a GSPACE which corresponds to DES, set it into
399 ;;; (DESCRIPTOR-GSPACE DES), set a consistent value into
400 ;;; (DESCRIPTOR-WORD-OFFSET DES), and return the GSPACE.
401 (declaim (ftype (function (descriptor) gspace
) descriptor-intuit-gspace
))
402 (defun descriptor-intuit-gspace (des)
403 (or (descriptor-gspace des
)
405 ;; gspace wasn't set, now we have to search for it.
406 (let* ((lowtag (descriptor-lowtag des
))
407 (abs-word-addr (ash (- (descriptor-bits des
) lowtag
)
408 (- sb
!vm
:word-shift
))))
410 ;; Non-pointer objects don't have a gspace.
411 (unless (or (eql lowtag sb
!vm
:fun-pointer-lowtag
)
412 (eql lowtag sb
!vm
:instance-pointer-lowtag
)
413 (eql lowtag sb
!vm
:list-pointer-lowtag
)
414 (eql lowtag sb
!vm
:other-pointer-lowtag
))
415 (error "don't even know how to look for a GSPACE for ~S" des
))
417 (dolist (gspace (list *dynamic
* *static
* *read-only
*
418 #!+immobile-space
*immobile-fixedobj
*
419 #!+immobile-space
*immobile-varyobj
*)
420 (error "couldn't find a GSPACE for ~S" des
))
421 ;; Bounds-check the descriptor against the allocated area
422 ;; within each gspace.
423 (when (and (<= (gspace-word-address gspace
)
425 (+ (gspace-word-address gspace
)
426 (gspace-free-word-index gspace
))))
427 ;; Update the descriptor with the correct gspace and the
428 ;; offset within the gspace and return the gspace.
429 (setf (descriptor-word-offset des
)
430 (- abs-word-addr
(gspace-word-address gspace
)))
431 (return (setf (descriptor-gspace des
) gspace
)))))))
433 (defun %fixnum-descriptor-if-possible
(num)
434 (and (typep num
'(signed-byte #.sb
!vm
:n-fixnum-bits
))
435 (make-random-descriptor (ash num sb
!vm
:n-fixnum-tag-bits
))))
437 (defun make-fixnum-descriptor (num)
438 (or (%fixnum-descriptor-if-possible num
)
439 (error "~W is too big for a fixnum." num
)))
441 (defun make-other-immediate-descriptor (data type
)
442 (make-descriptor (logior (ash data sb
!vm
:n-widetag-bits
) type
)))
444 (defun make-character-descriptor (data)
445 (make-other-immediate-descriptor data sb
!vm
:character-widetag
))
448 ;;;; miscellaneous variables and other noise
450 ;;; a numeric value to be returned for undefined foreign symbols, or NIL if
451 ;;; undefined foreign symbols are to be treated as an error.
452 ;;; (In the first pass of GENESIS, needed to create a header file before
453 ;;; the C runtime can be built, various foreign symbols will necessarily
454 ;;; be undefined, but we don't need actual values for them anyway, and
455 ;;; we can just use 0 or some other placeholder. In the second pass of
456 ;;; GENESIS, all foreign symbols should be defined, so any undefined
457 ;;; foreign symbol is a problem.)
459 ;;; KLUDGE: It would probably be cleaner to rewrite GENESIS so that it
460 ;;; never tries to look up foreign symbols in the first place unless
461 ;;; it's actually creating a core file (as in the second pass) instead
462 ;;; of using this hack to allow it to go through the motions without
463 ;;; causing an error. -- WHN 20000825
464 (defvar *foreign-symbol-placeholder-value
*)
466 ;;; a handle on the trap object
467 (defvar *unbound-marker
*
468 (make-other-immediate-descriptor 0 sb
!vm
:unbound-marker-widetag
))
470 ;;; a handle on the NIL object
471 (defvar *nil-descriptor
*)
473 ;;; the head of a list of TOPLEVEL-THINGs describing stuff to be done
474 ;;; when the target Lisp starts up
476 ;;; Each TOPLEVEL-THING can be a function to be executed or a fixup or
477 ;;; loadtime value, represented by (CONS KEYWORD ..).
478 (declaim (special *!cold-toplevels
* *!cold-defconstants
*
479 *!cold-defuns
* *cold-methods
*))
481 ;;; the head of a list of DEBUG-SOURCEs which need to be patched when
482 ;;; the cold core starts up
483 (defvar *current-debug-sources
*)
485 ;;; foreign symbol references
486 (defparameter *cold-foreign-undefined-symbols
* nil
)
488 ;;;; miscellaneous stuff to read and write the core memory
490 ;;; FIXME: should be DEFINE-MODIFY-MACRO
491 (defmacro cold-push
(thing list
) ; for making a target list held in a host symbol
492 "Push THING onto the given cold-load LIST."
493 `(setq ,list
(cold-cons ,thing
,list
)))
495 ;; Like above, but the list is held in the target's image of the host symbol,
496 ;; not the host's value of the symbol.
497 (defun cold-target-push (cold-thing host-symbol
)
498 (cold-set host-symbol
(cold-cons cold-thing
(cold-symbol-value host-symbol
))))
500 (declaim (ftype (function (descriptor sb
!vm
:word
) descriptor
) read-wordindexed
))
501 (macrolet ((read-bits ()
502 `(bvref-word (descriptor-mem address
)
503 (ash (+ index
(descriptor-word-offset address
))
505 (defun read-bits-wordindexed (address index
)
507 (defun read-wordindexed (address index
)
508 "Return the value which is displaced by INDEX words from ADDRESS."
509 (make-random-descriptor (read-bits))))
511 (declaim (ftype (function (descriptor) descriptor
) read-memory
))
512 (defun read-memory (address)
513 "Return the value at ADDRESS."
514 (read-wordindexed address
0))
516 (declaim (ftype (function (descriptor
517 (integer #.
(- sb
!vm
:list-pointer-lowtag
)
518 #.sb
!ext
:most-positive-word
)
521 note-load-time-value-reference
))
522 (defun note-load-time-value-reference (address offset marker
)
523 (push (cold-list (cold-intern :load-time-value-fixup
)
525 (number-to-core offset
)
526 (number-to-core (descriptor-word-offset marker
)))
530 (declaim (ftype (function (descriptor sb
!vm
:word
(or symbol descriptor
))) write-wordindexed
))
531 (macrolet ((write-bits (bits)
532 `(setf (bvref-word (descriptor-mem address
)
533 (ash (+ index
(descriptor-word-offset address
))
536 (defun write-wordindexed (address index value
)
537 "Write VALUE displaced INDEX words from ADDRESS."
538 ;; If we're passed a symbol as a value then it needs to be interned.
539 (let ((value (cond ((symbolp value
) (cold-intern value
))
541 (if (eql (descriptor-gspace value
) :load-time-value
)
542 (note-load-time-value-reference address
543 (- (ash index sb
!vm
:word-shift
)
544 (logand (descriptor-bits address
)
547 (write-bits (descriptor-bits value
)))))
549 (defun write-wordindexed/raw
(address index bits
)
550 (declare (type descriptor address
) (type sb
!vm
:word index
)
551 (type (or sb
!vm
:word sb
!vm
:signed-word
) bits
))
552 (write-bits (logand bits sb
!ext
:most-positive-word
))))
554 (declaim (ftype (function (descriptor (or symbol descriptor
))) write-memory
))
555 (defun write-memory (address value
)
556 "Write VALUE (a DESCRIPTOR) at ADDRESS (also a DESCRIPTOR)."
557 (write-wordindexed address
0 value
))
559 ;;;; allocating images of primitive objects in the cold core
561 (defun write-header-word (des header-data widetag
)
562 ;; In immobile space, all objects start life as pseudo-static as if by 'save'.
563 (let ((gen #!+gencgc
(if (or #!+immobile-space
564 (let ((gspace (descriptor-gspace des
)))
565 (or (eq gspace
*immobile-fixedobj
*)
566 (eq gspace
*immobile-varyobj
*))))
567 sb
!vm
:+pseudo-static-generation
+
570 (write-wordindexed/raw des
0
571 (logior (ash (logior (ash gen
16) header-data
)
572 sb
!vm
:n-widetag-bits
) widetag
))))
574 (defun set-header-data (object data
)
575 (write-header-word object data
(ldb (byte sb
!vm
:n-widetag-bits
0)
576 (read-bits-wordindexed object
0))))
578 (defun get-header-data (object)
579 (ash (read-bits-wordindexed object
0) (- sb
!vm
:n-widetag-bits
)))
581 ;;; There are three kinds of blocks of memory in the type system:
582 ;;; * Boxed objects (cons cells, structures, etc): These objects have no
583 ;;; header as all slots are descriptors.
584 ;;; * Unboxed objects (bignums): There is a single header word that contains
586 ;;; * Vector objects: There is a header word with the type, then a word for
587 ;;; the length, then the data.
588 (defun allocate-object (gspace length lowtag
&optional align256p
)
589 "Allocate LENGTH words in GSPACE and return a new descriptor of type LOWTAG
591 (allocate-cold-descriptor gspace
(ash length sb
!vm
:word-shift
) lowtag
592 (make-page-attributes align256p
0)))
593 (defun allocate-header+object
(gspace length widetag
&optional page-kind
)
594 "Allocate LENGTH words plus a header word in GSPACE and
595 return an ``other-pointer'' descriptor to them. Initialize the header word
596 with the resultant length and WIDETAG."
597 (let ((des (allocate-cold-descriptor
598 gspace
(ash (1+ length
) sb
!vm
:word-shift
)
599 sb
!vm
:other-pointer-lowtag
600 (make-page-attributes nil page-kind
))))
601 (write-header-word des length widetag
)
603 (defun allocate-vector-object (gspace element-bits length widetag
)
604 "Allocate LENGTH units of ELEMENT-BITS size plus a header plus a length slot in
605 GSPACE and return an ``other-pointer'' descriptor to them. Initialize the
606 header word with WIDETAG and the length slot with LENGTH."
607 ;; ALLOCATE-COLD-DESCRIPTOR will take any rational number of bytes
608 ;; and round up to a double-word. This doesn't need to use CEILING.
609 (let* ((bytes (/ (* element-bits length
) sb
!vm
:n-byte-bits
))
610 (des (allocate-cold-descriptor gspace
611 (+ bytes
(* 2 sb
!vm
:n-word-bytes
))
612 sb
!vm
:other-pointer-lowtag
)))
613 (write-header-word des
0 widetag
)
614 (write-wordindexed des
615 sb
!vm
:vector-length-slot
616 (make-fixnum-descriptor length
))
619 ;;; the hosts's representation of LAYOUT-of-LAYOUT
620 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
621 (defvar *host-layout-of-layout
* (find-layout 'layout
)))
623 (defun cold-layout-length (layout)
624 (descriptor-fixnum (read-slot layout
*host-layout-of-layout
* :length
)))
625 (defun cold-layout-depthoid (layout)
626 (descriptor-fixnum (read-slot layout
*host-layout-of-layout
* :depthoid
)))
628 ;; Make a structure and set the header word and layout.
629 ;; LAYOUT-LENGTH is as returned by the like-named function.
630 (defun allocate-struct
631 (gspace layout
&optional
(layout-length (cold-layout-length layout
))
633 ;; Count +1 for the header word when allocating.
634 (let ((des (allocate-object gspace
(1+ layout-length
)
635 sb
!vm
:instance-pointer-lowtag is-layout
)))
636 ;; Length as stored in the header is the exact number of useful words
637 ;; that follow, as is customary. A padding word, if any is not "useful"
638 (write-header-word des
639 (logior layout-length
640 #!+compact-instance-header
641 (if layout
(ash (descriptor-bits layout
) 24) 0))
642 sb
!vm
:instance-header-widetag
)
643 #!-compact-instance-header
644 (write-wordindexed des sb
!vm
:instance-slots-offset layout
)
647 ;;;; copying simple objects into the cold core
649 (defun base-string-to-core (string &optional
(gspace *dynamic
*))
650 "Copy STRING (which must only contain STANDARD-CHARs) into the cold
651 core and return a descriptor to it."
652 ;; (Remember that the system convention for storage of strings leaves an
653 ;; extra null byte at the end to aid in call-out to C.)
654 (let* ((length (length string
))
655 (des (allocate-vector-object gspace
658 sb
!vm
:simple-base-string-widetag
))
659 (bytes (gspace-bytes gspace
))
660 (offset (+ (* sb
!vm
:vector-data-offset sb
!vm
:n-word-bytes
)
661 (descriptor-byte-offset des
))))
662 (write-wordindexed des
663 sb
!vm
:vector-length-slot
664 (make-fixnum-descriptor length
))
666 (setf (bvref bytes
(+ offset i
))
667 (sb!xc
:char-code
(aref string i
))))
668 (setf (bvref bytes
(+ offset length
))
669 0) ; null string-termination character for C
672 (defun base-string-from-core (descriptor)
673 (let* ((len (descriptor-fixnum
674 (read-wordindexed descriptor sb
!vm
:vector-length-slot
)))
675 (str (make-string len
))
676 (bytes (descriptor-mem descriptor
)))
679 (code-char (bvref bytes
680 (+ (descriptor-byte-offset descriptor
)
681 (* sb
!vm
:vector-data-offset sb
!vm
:n-word-bytes
)
684 (defun bignum-to-core (n)
685 "Copy a bignum to the cold core."
686 (let* ((words (ceiling (1+ (integer-length n
)) sb
!vm
:n-word-bits
))
688 (allocate-header+object
*dynamic
* words sb
!vm
:bignum-widetag
)))
689 (declare (fixnum words
))
690 (do ((index 1 (1+ index
))
691 (remainder n
(ash remainder
(- sb
!vm
:n-word-bits
))))
693 (unless (zerop (integer-length remainder
))
694 ;; FIXME: Shouldn't this be a fatal error?
695 (warn "~W words of ~W were written, but ~W bits were left over."
697 (write-wordindexed/raw handle index
698 (ldb (byte sb
!vm
:n-word-bits
0) remainder
)))
701 (defun bignum-from-core (descriptor)
702 (let ((n-words (ash (descriptor-bits (read-memory descriptor
))
703 (- sb
!vm
:n-widetag-bits
)))
705 (dotimes (i n-words val
)
706 (let ((bits (read-bits-wordindexed descriptor
707 (+ i sb
!vm
:bignum-digits-offset
))))
708 ;; sign-extend the highest word
709 (when (and (= i
(1- n-words
)) (logbitp (1- sb
!vm
:n-word-bits
) bits
))
710 (setq bits
(dpb bits
(byte sb
!vm
:n-word-bits
0) -
1)))
711 (setq val
(logior (ash bits
(* i sb
!vm
:n-word-bits
)) val
))))))
713 (defun number-pair-to-core (first second type
)
714 "Makes a number pair of TYPE (ratio or complex) and fills it in."
715 (let ((des (allocate-header+object
*dynamic
* 2 type
)))
716 (write-wordindexed des
1 first
)
717 (write-wordindexed des
2 second
)
720 (defun write-double-float-bits (address index x
)
721 (let ((high-bits (double-float-high-bits x
))
722 (low-bits (double-float-low-bits x
)))
723 (ecase sb
!vm
::n-word-bits
725 (ecase sb
!c
:*backend-byte-order
*
727 (write-wordindexed/raw address index low-bits
)
728 (write-wordindexed/raw address
(1+ index
) high-bits
))
730 (write-wordindexed/raw address index high-bits
)
731 (write-wordindexed/raw address
(1+ index
) low-bits
))))
733 (let ((bits (ecase sb
!c
:*backend-byte-order
*
734 (:little-endian
(logior low-bits
(ash high-bits
32)))
736 #+nil
(:big-endian
(logior (logand high-bits
#xffffffff
)
737 (ash low-bits
32))))))
738 (write-wordindexed/raw address index bits
))))
742 (defun float-to-core (x)
745 ;; 64-bit platforms have immediate single-floats.
747 (make-random-descriptor (logior (ash (single-float-bits x
) 32)
748 sb
!vm
::single-float-widetag
))
750 (let ((des (allocate-header+object
*dynamic
*
751 (1- sb
!vm
:single-float-size
)
752 sb
!vm
:single-float-widetag
)))
753 (write-wordindexed/raw des sb
!vm
:single-float-value-slot
754 (single-float-bits x
))
757 (let ((des (allocate-header+object
*dynamic
*
758 (1- sb
!vm
:double-float-size
)
759 sb
!vm
:double-float-widetag
)))
760 (write-double-float-bits des sb
!vm
:double-float-value-slot x
)))))
762 (defun complex-single-float-to-core (num)
763 (declare (type (complex single-float
) num
))
764 (let ((des (allocate-header+object
*dynamic
*
765 (1- sb
!vm
:complex-single-float-size
)
766 sb
!vm
:complex-single-float-widetag
)))
769 (write-wordindexed/raw des sb
!vm
:complex-single-float-real-slot
770 (single-float-bits (realpart num
)))
771 (write-wordindexed/raw des sb
!vm
:complex-single-float-imag-slot
772 (single-float-bits (imagpart num
))))
774 (write-wordindexed/raw
775 des sb
!vm
:complex-single-float-data-slot
776 (logior (ldb (byte 32 0) (single-float-bits (realpart num
)))
777 (ash (single-float-bits (imagpart num
)) 32)))
780 (defun complex-double-float-to-core (num)
781 (declare (type (complex double-float
) num
))
782 (let ((des (allocate-header+object
*dynamic
*
783 (1- sb
!vm
:complex-double-float-size
)
784 sb
!vm
:complex-double-float-widetag
)))
785 (write-double-float-bits des sb
!vm
:complex-double-float-real-slot
787 (write-double-float-bits des sb
!vm
:complex-double-float-imag-slot
790 ;;; Copy the given number to the core.
791 (defun number-to-core (number)
793 (integer (or (%fixnum-descriptor-if-possible number
)
794 (bignum-to-core number
)))
795 (ratio (number-pair-to-core (number-to-core (numerator number
))
796 (number-to-core (denominator number
))
797 sb
!vm
:ratio-widetag
))
798 ((complex single-float
) (complex-single-float-to-core number
))
799 ((complex double-float
) (complex-double-float-to-core number
))
801 ((complex long-float
)
802 (error "~S isn't a cold-loadable number at all!" number
))
803 (complex (number-pair-to-core (number-to-core (realpart number
))
804 (number-to-core (imagpart number
))
805 sb
!vm
:complex-widetag
))
806 (float (float-to-core number
))
807 (t (error "~S isn't a cold-loadable number at all!" number
))))
809 ;;; Allocate a cons cell in GSPACE and fill it in with CAR and CDR.
810 (defun cold-cons (car cdr
&optional
(gspace *dynamic
*))
811 (let ((dest (allocate-object gspace
2 sb
!vm
:list-pointer-lowtag
)))
812 (write-wordindexed dest sb
!vm
:cons-car-slot car
)
813 (write-wordindexed dest sb
!vm
:cons-cdr-slot cdr
)
815 (defun list-to-core (list)
816 (let ((head *nil-descriptor
*)
818 ;; A recursive algorithm would have the first cons at the highest
819 ;; address. This way looks nicer when viewed in ldb.
821 (unless list
(return head
))
822 (let ((cons (cold-cons (pop list
) *nil-descriptor
*)))
823 (if tail
(cold-rplacd tail cons
) (setq head cons
))
825 (defun cold-list (&rest args
) (list-to-core args
))
826 (defun cold-list-length (list) ; but no circularity detection
827 ;; a recursive implementation uses too much stack for some Lisps
829 (loop (if (cold-null list
) (return n
))
831 (setq list
(cold-cdr list
)))))
833 ;;; Make a simple-vector on the target that holds the specified
834 ;;; OBJECTS, and return its descriptor.
835 ;;; This is really "vectorify-list-into-core" but that's too wordy,
836 ;;; so historically it was "vector-in-core" which is a fine name.
837 (defun vector-in-core (objects &optional
(gspace *dynamic
*))
838 (let* ((size (length objects
))
839 (result (allocate-vector-object gspace sb
!vm
:n-word-bits size
840 sb
!vm
:simple-vector-widetag
)))
841 (dotimes (index size
)
842 (write-wordindexed result
(+ index sb
!vm
:vector-data-offset
)
845 (defun cold-svset (vector index value
)
846 (let ((i (if (integerp index
) index
(descriptor-fixnum index
))))
847 (write-wordindexed vector
(+ i sb
!vm
:vector-data-offset
) value
)))
849 (setf (get 'vector
:sb-cold-funcall-handler
/for-value
)
850 (lambda (&rest args
) (vector-in-core args
)))
852 (declaim (inline cold-vector-len cold-svref
))
853 (defun cold-vector-len (vector)
854 (descriptor-fixnum (read-wordindexed vector sb
!vm
:vector-length-slot
)))
855 (defun cold-svref (vector i
)
856 (read-wordindexed vector
(+ (if (integerp i
) i
(descriptor-fixnum i
))
857 sb
!vm
:vector-data-offset
)))
858 (defun cold-vector-elements-eq (a b
)
859 (and (eql (cold-vector-len a
) (cold-vector-len b
))
860 (dotimes (k (cold-vector-len a
) t
)
861 (unless (descriptor= (cold-svref a k
) (cold-svref b k
))
863 (defun vector-from-core (descriptor &optional
(transform #'identity
))
864 (let* ((len (cold-vector-len descriptor
))
865 (vector (make-array len
)))
866 (dotimes (i len vector
)
867 (setf (aref vector i
) (funcall transform
(cold-svref descriptor i
))))))
871 ;; Simulate *FREE-TLS-INDEX*. This is a count, not a displacement.
872 ;; In C, sizeof counts 1 word for the variable-length interrupt_contexts[]
873 ;; but primitive-object-size counts 0, so add 1, though in fact the C code
874 ;; implies that it might have overcounted by 1. We could make this agnostic
875 ;; of MAX-INTERRUPTS by moving the thread base register up by TLS-SIZE words,
876 ;; using negative offsets for all dynamically assigned indices.
877 (defvar *genesis-tls-counter
*
878 (+ 1 sb
!vm
::max-interrupts
879 (sb!vm
:primitive-object-size
880 (find 'sb
!vm
::thread sb
!vm
:*primitive-objects
*
881 :key
#'sb
!vm
:primitive-object-name
))))
885 ;; Assign SYMBOL the tls-index INDEX. SYMBOL must be a descriptor.
886 ;; This is a backend support routine, but the style within this file
887 ;; is to conditionalize by the target features.
888 (defun cold-assign-tls-index (symbol index
)
890 (write-wordindexed/raw
891 symbol
0 (logior (ash index
32) (read-bits-wordindexed symbol
0)))
893 (write-wordindexed/raw symbol sb
!vm
:symbol-tls-index-slot index
))
895 ;; Return SYMBOL's tls-index,
896 ;; choosing a new index if it doesn't have one yet.
897 (defun ensure-symbol-tls-index (symbol)
898 (let* ((cold-sym (cold-intern symbol
))
901 (ldb (byte 32 32) (read-bits-wordindexed cold-sym
0))
903 (read-bits-wordindexed cold-sym sb
!vm
:symbol-tls-index-slot
)))
904 (unless (plusp tls-index
)
905 (let ((next (prog1 *genesis-tls-counter
* (incf *genesis-tls-counter
*))))
906 (setq tls-index
(ash next sb
!vm
:word-shift
))
907 (cold-assign-tls-index cold-sym tls-index
)))
910 ;; A table of special variable names which get known TLS indices.
911 ;; Some of them are mapped onto 'struct thread' and have pre-determined offsets.
912 ;; Others are static symbols used with bind_variable() in the C runtime,
913 ;; and might not, in the absence of this table, get an index assigned by genesis
914 ;; depending on whether the cross-compiler used the BIND vop on them.
915 ;; Indices for those static symbols can be chosen arbitrarily, which is to say
916 ;; the value doesn't matter but must update the tls-counter correctly.
917 ;; All symbols other than the ones in this table get the indices assigned
918 ;; by the fasloader on demand.
920 (defvar *known-tls-symbols
*
921 ;; FIXME: no mechanism exists to determine which static symbols C code will
922 ;; dynamically bind. TLS is a finite resource, and wasting indices for all
923 ;; static symbols isn't the best idea. This list was hand-made with 'grep'.
924 '(sb!vm
:*alloc-signal
*
925 sb
!sys
:*allow-with-interrupts
*
926 sb
!vm
:*current-catch-block
*
927 sb
!vm
::*current-unwind-protect-block
*
928 sb
!kernel
:*free-interrupt-context-index
*
929 sb
!kernel
:*gc-inhibit
*
930 sb
!kernel
:*gc-pending
*
932 sb
!impl
::*in-safepoint
*
933 sb
!sys
:*interrupt-pending
*
934 sb
!sys
:*interrupts-enabled
*
935 sb
!vm
::*pinned-objects
*
936 sb
!kernel
:*restart-clusters
*
937 sb
!kernel
:*stop-for-gc-pending
*
939 sb
!sys
:*thruption-pending
*))
941 ;;; Symbol print names are coalesced by string=.
942 ;;; This is valid because it is an error to modify a print name.
943 (defvar *symbol-name-strings
* (make-hash-table :test
'equal
))
945 (defvar *cold-symbol-gspace
* (or #!+immobile-space
'*immobile-fixedobj
* '*dynamic
*))
947 ;;; Allocate (and initialize) a symbol.
948 (defun allocate-symbol (name interned
949 &key
(gspace (symbol-value *cold-symbol-gspace
*)))
950 (declare (simple-string name
))
951 (declare (ignore interned
))
953 (when (and (eq gspace
*immobile-fixedobj
*) (char/= (char name
0) #\
*))
954 ;; immobile symbols that aren't likely to be special vars
955 ;; should go in regular dynamic space until a de-frag pass is
956 ;; implemented for save-lisp-and-die. Otherwise they create
957 ;; tons of holes all over the immobile space.
958 (setq gspace
*dynamic
*))
959 (let ((symbol (allocate-header+object
960 gspace
(1- sb
!vm
:symbol-size
)
961 sb
!vm
:symbol-header-widetag
962 ;; Tell the allocator what kind of symbol page to prefer.
963 ;; This only affects gc performance, not correctness.
965 (write-wordindexed symbol sb
!vm
:symbol-value-slot
*unbound-marker
*)
966 (write-wordindexed symbol sb
!vm
:symbol-hash-slot
(make-fixnum-descriptor 0))
967 (write-wordindexed symbol sb
!vm
:symbol-info-slot
*nil-descriptor
*)
968 (write-wordindexed symbol sb
!vm
:symbol-name-slot
969 (or (gethash name
*symbol-name-strings
*)
970 (setf (gethash name
*symbol-name-strings
*)
971 (base-string-to-core name
*dynamic
*))))
972 (write-wordindexed symbol sb
!vm
:symbol-package-slot
*nil-descriptor
*)
976 (defun assign-tls-index (symbol cold-symbol
)
977 (let ((index (info :variable
:wired-tls symbol
)))
978 (cond ((integerp index
) ; thread slot
979 (cold-assign-tls-index cold-symbol index
))
980 ((memq symbol
*known-tls-symbols
*)
981 ;; symbols without which the C runtime could not start
982 (shiftf index
*genesis-tls-counter
* (1+ *genesis-tls-counter
*))
983 (cold-assign-tls-index cold-symbol
(ash index sb
!vm
:word-shift
))))))
985 ;;; Set the cold symbol value of SYMBOL-OR-SYMBOL-DES, which can be either a
986 ;;; descriptor of a cold symbol or (in an abbreviation for the
987 ;;; most common usage pattern) an ordinary symbol, which will be
988 ;;; automatically cold-interned.
989 (declaim (ftype (function ((or symbol descriptor
) descriptor
)) cold-set
))
990 (defun cold-set (symbol-or-symbol-des value
)
991 (let ((symbol-des (etypecase symbol-or-symbol-des
992 (descriptor symbol-or-symbol-des
)
993 (symbol (cold-intern symbol-or-symbol-des
)))))
994 (write-wordindexed symbol-des sb
!vm
:symbol-value-slot value
)))
995 (defun cold-symbol-value (symbol)
996 (let ((val (read-wordindexed (cold-intern symbol
) sb
!vm
:symbol-value-slot
)))
997 (if (= (descriptor-bits val
) sb
!vm
:unbound-marker-widetag
)
998 (unbound-cold-symbol-handler symbol
)
1000 (defun cold-fdefn-fun (cold-fdefn)
1001 (read-wordindexed cold-fdefn sb
!vm
:fdefn-fun-slot
))
1003 (defun unbound-cold-symbol-handler (symbol)
1004 (let ((host-val (and (boundp symbol
) (symbol-value symbol
))))
1005 (if (typep host-val
'sb
!kernel
:named-type
)
1006 (let ((target-val (ctype-to-core (sb!kernel
:named-type-name host-val
)
1008 ;; Though it looks complicated to assign cold symbols on demand,
1009 ;; it avoids writing code to build the layout of NAMED-TYPE in the
1010 ;; way we build other primordial stuff such as layout-of-layout.
1011 (cold-set symbol target-val
)
1013 (error "Taking Cold-symbol-value of unbound symbol ~S" symbol
))))
1015 ;;;; layouts and type system pre-initialization
1017 ;;; Since we want to be able to dump structure constants and
1018 ;;; predicates with reference layouts, we need to create layouts at
1019 ;;; cold-load time. We use the name to intern layouts by, and dump a
1020 ;;; list of all cold layouts in *!INITIAL-LAYOUTS* so that type system
1021 ;;; initialization can find them. The only thing that's tricky [sic --
1022 ;;; WHN 19990816] is initializing layout's layout, which must point to
1025 ;;; a map from name as a host symbol to the descriptor of its target layout
1026 (defvar *cold-layouts
*)
1028 ;;; a map from DESCRIPTOR-BITS of cold layouts to the name, for inverting
1030 (defvar *cold-layout-names
*)
1032 ;;; the descriptor for layout's layout (needed when making layouts)
1033 (defvar *layout-layout
*)
1035 (defvar *known-structure-classoids
*)
1037 (defconstant target-layout-length
1038 ;; LAYOUT-LENGTH counts the number of words in an instance,
1039 ;; including the layout itself as 1 word
1040 (layout-length *host-layout-of-layout
*))
1042 ;;; Trivial methods [sic] require that we sort possible methods by the depthoid.
1043 ;;; Most of the objects printed in cold-init are ordered hierarchically in our
1044 ;;; type lattice; the major exceptions are ARRAY and VECTOR at depthoid -1.
1045 ;;; Of course we need to print VECTORs because a STRING is a vector,
1046 ;;; and vector has to precede ARRAY. Kludge it for now.
1047 (defun class-depthoid (class-name) ; DEPTHOID-ish thing, any which way you can
1051 ;; The depthoid of CONDITION has to be faked. The proper value is 1.
1052 ;; But STRUCTURE-OBJECT is also at depthoid 1, and its predicate
1053 ;; is %INSTANCEP (which is too weak), so to select the correct method
1054 ;; we have to make CONDITION more specific.
1055 ;; In reality it is type disjoint from structure-object.
1058 (let ((target-layout (gethash class-name
*cold-layouts
*)))
1060 (cold-layout-depthoid target-layout
)
1061 (let ((host-layout (find-layout class-name
)))
1062 (if (layout-invalid host-layout
)
1063 (error "~S has neither a host not target layout" class-name
)
1064 (layout-depthoid host-layout
))))))))
1066 ;;; Return a list of names created from the cold layout INHERITS data
1068 (defun listify-cold-inherits (x)
1069 (map 'list
(lambda (cold-layout)
1070 (or (gethash (descriptor-bits cold-layout
) *cold-layout-names
*)
1071 (error "~S is not the descriptor of a cold-layout" cold-layout
)))
1072 (vector-from-core x
)))
1074 ;;; COLD-DD-SLOTS is a cold descriptor for the list of slots
1075 ;;; in a cold defstruct-description. INDEX is a DSD-INDEX.
1076 ;;; Return the host's accessor name for the host image of that slot.
1077 (defun dsd-accessor-from-cold-slots (cold-dd-slots desired-index
)
1078 (let* ((dsd-slots (dd-slots
1079 (find-defstruct-description 'defstruct-slot-description
)))
1081 (dsd-index (find 'sb
!kernel
::index dsd-slots
:key
#'dsd-name
)))
1082 (accessor-fun-name-slot
1083 (dsd-index (find 'sb
!kernel
::accessor-name dsd-slots
:key
#'dsd-name
))))
1084 (do ((list cold-dd-slots
(cold-cdr list
)))
1086 (when (= (descriptor-fixnum
1087 (read-wordindexed (cold-car list
)
1088 (+ sb
!vm
:instance-slots-offset index-slot
)))
1092 (read-wordindexed (cold-car list
)
1093 (+ sb
!vm
:instance-slots-offset
1094 accessor-fun-name-slot
))))))))
1096 (flet ((get-slots (host-layout-or-type)
1097 (etypecase host-layout-or-type
1098 (layout (dd-slots (layout-info host-layout-or-type
)))
1099 (symbol (dd-slots-from-core host-layout-or-type
))))
1100 (get-slot-index (slots initarg
)
1101 (+ sb
!vm
:instance-slots-offset
1102 (if (descriptor-p slots
)
1103 (do ((dsd-layout (find-layout 'defstruct-slot-description
))
1104 (slots slots
(cold-cdr slots
)))
1105 ((cold-null slots
) (error "No slot for ~S" initarg
))
1106 (let* ((dsd (cold-car slots
))
1107 (slot-name (read-slot dsd dsd-layout
:name
)))
1108 (when (eq (keywordicate (warm-symbol slot-name
)) initarg
)
1109 ;; Untagged slots are not accessible during cold-load
1110 (aver (eql (descriptor-fixnum
1111 (read-slot dsd dsd-layout
:%raw-type
)) -
1))
1112 (return (descriptor-fixnum
1113 (read-slot dsd dsd-layout
:index
))))))
1114 (let ((dsd (find initarg slots
1116 (eq x
(keywordicate (dsd-name y
)))))))
1117 (aver (eq (dsd-raw-type dsd
) t
)) ; Same as above: no can do.
1118 (dsd-index dsd
))))))
1119 (defun write-slots (cold-object host-layout-or-type
&rest assignments
)
1120 (aver (evenp (length assignments
)))
1121 (let ((slots (get-slots host-layout-or-type
)))
1122 (loop for
(initarg value
) on assignments by
#'cddr
1123 do
(write-wordindexed
1124 cold-object
(get-slot-index slots initarg
) value
)))
1127 ;; For symmetry, the reader takes an initarg, not a slot name.
1128 (defun read-slot (cold-object host-layout-or-type slot-initarg
)
1129 (let ((slots (get-slots host-layout-or-type
)))
1130 (read-wordindexed cold-object
(get-slot-index slots slot-initarg
)))))
1132 ;; Given a TYPE-NAME of a structure-class, find its defstruct-description
1133 ;; as a target descriptor, and return the slot list as a target descriptor.
1134 (defun dd-slots-from-core (type-name)
1135 (let* ((host-dd-layout (find-layout 'defstruct-description
))
1137 ;; This is inefficient, but not enough so to worry about.
1138 (or (car (assoc (cold-intern type-name
) *known-structure-classoids
*
1139 :key
(lambda (x) (read-slot x host-dd-layout
:name
))
1140 :test
#'descriptor
=))
1141 (error "No known layout for ~S" type-name
))))
1142 (read-slot target-dd host-dd-layout
:slots
)))
1144 (defvar *simple-vector-0-descriptor
*)
1145 (defvar *vacuous-slot-table
*)
1146 (defvar *cold-layout-gspace
* (or #!+immobile-space
'*immobile-fixedobj
* '*dynamic
*))
1147 (declaim (ftype (function (symbol descriptor descriptor descriptor descriptor
)
1150 (defun make-cold-layout (name length inherits depthoid bitmap
)
1151 (let ((result (allocate-struct (symbol-value *cold-layout-gspace
*) *layout-layout
*
1152 target-layout-length t
)))
1153 ;; Don't set the CLOS hash value: done in cold-init instead.
1155 ;; Set other slot values.
1157 ;; leave CLASSOID uninitialized for now
1158 (multiple-value-call
1159 #'write-slots result
*host-layout-of-layout
*
1160 :invalid
*nil-descriptor
*
1164 :info
*nil-descriptor
*
1165 :pure
*nil-descriptor
*
1167 ;; Nothing in cold-init needs to call EQUALP on a structure with raw slots,
1168 ;; but for type-correctness this slot needs to be a simple-vector.
1169 :equalp-tests
(if (boundp '*simple-vector-0-descriptor
*)
1170 *simple-vector-0-descriptor
*
1171 (setq *simple-vector-0-descriptor
*
1172 (vector-in-core nil
)))
1173 :source-location
*nil-descriptor
*
1174 :%for-std-class-b
(make-fixnum-descriptor 0)
1175 :slot-list
*nil-descriptor
*
1176 (if (member name
'(null list symbol
))
1177 ;; Assign an empty slot-table. Why this is done only for three
1178 ;; classoids is ... too complicated to explain here in a few words,
1179 ;; but revision 18c239205d9349abc017b07e7894a710835c5205 broke it.
1180 ;; Keep this in sync with MAKE-SLOT-TABLE in pcl/slots-boot.
1181 (values :slot-table
(if (boundp '*vacuous-slot-table
*)
1182 *vacuous-slot-table
*
1183 (setq *vacuous-slot-table
*
1184 (host-constant-to-core '#(1 nil
)))))
1187 (setf (gethash (descriptor-bits result
) *cold-layout-names
*) name
1188 (gethash name
*cold-layouts
*) result
)))
1190 (defun predicate-for-specializer (type-name)
1191 (let ((classoid (find-classoid type-name nil
)))
1194 (cond ((dd-predicate-name (layout-info (classoid-layout classoid
))))
1195 ;; All early INSTANCEs should be STRUCTURE-OBJECTs.
1196 ((eq type-name
'structure-object
) 'sb
!kernel
:%instancep
)))
1198 (let ((translation (specifier-type type-name
)))
1199 (aver (not (contains-unknown-type-p translation
)))
1200 (let ((predicate (find translation sb
!c
::*backend-type-predicates
*
1201 :test
#'type
= :key
#'car
)))
1202 (cond (predicate (cdr predicate
))
1203 ((eq type-name
't
) 'sb
!int
:constantly-t
)
1204 (t (error "No predicate for builtin: ~S" type-name
))))))
1206 #+nil
(format t
"~&; PREDICATE-FOR-SPECIALIZER: no classoid for ~S~%"
1209 (condition 'sb
!kernel
::!condition-p
))))))
1211 ;;; Convert SPECIFIER (equivalently OBJ) to its representation as a ctype
1212 ;;; in the cold core.
1213 (defvar *ctype-cache
*)
1215 (defvar *ctype-nullified-slots
* nil
)
1216 (defvar *built-in-classoid-nullified-slots
* nil
)
1218 ;; This function is memoized because it's essentially a constant,
1219 ;; but *nil-descriptor* isn't initialized by the time it's defined.
1220 (defun get-exceptional-slots (obj-type)
1221 (flet ((index (classoid-name slot-name
)
1222 (dsd-index (find slot-name
1223 (dd-slots (find-defstruct-description classoid-name
))
1227 (or *built-in-classoid-nullified-slots
*
1228 (setq *built-in-classoid-nullified-slots
*
1229 (append (get-exceptional-slots 'ctype
)
1230 (list (cons (index 'built-in-classoid
'sb
!kernel
::subclasses
)
1232 (cons (index 'built-in-classoid
'layout
)
1233 *nil-descriptor
*))))))
1235 (or *ctype-nullified-slots
*
1236 (setq *ctype-nullified-slots
*
1237 (list (cons (index 'ctype
'sb
!kernel
::class-info
)
1238 *nil-descriptor
*))))))))
1240 (defun ctype-to-core (specifier obj
)
1241 (declare (type ctype obj
))
1242 (if (classoid-p obj
)
1243 (let* ((cell (cold-find-classoid-cell (classoid-name obj
) :create t
))
1245 (read-slot cell
(find-layout 'sb
!kernel
::classoid-cell
) :classoid
)))
1246 (unless (cold-null cold-classoid
)
1247 (return-from ctype-to-core cold-classoid
)))
1248 ;; CTYPEs can't be TYPE=-hashed, but specifiers can be EQUAL-hashed.
1249 ;; Don't check the cache for classoids though; that would be wrong.
1250 ;; e.g. named-type T and classoid T both unparse to T.
1251 (awhen (gethash specifier
*ctype-cache
*)
1252 (return-from ctype-to-core it
)))
1254 (ctype-to-core-helper
1258 (xset (ctype-to-core-helper obj nil nil
))
1259 (ctype (ctype-to-core (type-specifier obj
) obj
))))
1260 (get-exceptional-slots (type-of obj
)))))
1261 (let ((type-class-vector
1262 (cold-symbol-value 'sb
!kernel
::*type-classes
*))
1263 (index (position (sb!kernel
::type-class-info obj
)
1264 sb
!kernel
::*type-classes
*)))
1265 ;; Push this instance into the list of fixups for its type class
1266 (cold-svset type-class-vector index
1267 (cold-cons result
(cold-svref type-class-vector index
))))
1268 (if (classoid-p obj
)
1269 ;; Place this classoid into its clasoid-cell.
1270 (let ((cell (cold-find-classoid-cell (classoid-name obj
) :create t
)))
1271 (write-slots cell
(find-layout 'sb
!kernel
::classoid-cell
)
1273 ;; Otherwise put it in the general cache
1274 (setf (gethash specifier
*ctype-cache
*) result
))
1277 (defun ctype-to-core-helper (obj obj-to-core-helper exceptional-slots
)
1278 (let* ((host-type (type-of obj
))
1279 (target-layout (or (gethash host-type
*cold-layouts
*)
1280 (error "No target layout for ~S" obj
)))
1281 (result (allocate-struct *dynamic
* target-layout
))
1282 (cold-dd-slots (dd-slots-from-core host-type
)))
1283 (aver (eql (layout-bitmap (find-layout host-type
))
1284 sb
!kernel
::+layout-all-tagged
+))
1286 (do ((len (cold-layout-length target-layout
))
1287 (index sb
!vm
:instance-data-start
(1+ index
)))
1288 ((= index len
) result
)
1291 (+ sb
!vm
:instance-slots-offset index
)
1292 (acond ((assq index exceptional-slots
) (cdr it
))
1293 (t (host-constant-to-core
1294 (funcall (dsd-accessor-from-cold-slots cold-dd-slots index
)
1296 obj-to-core-helper
)))))))
1298 ;; This is called to backpatch two small sets of objects:
1299 ;; - layouts created before layout-of-layout is made (3 counting LAYOUT itself)
1300 ;; - a small number of classoid-cells (~ 4).
1301 (defun set-instance-layout (thing layout
)
1302 #!+compact-instance-header
1303 ;; High half of the header points to the layout
1304 (write-wordindexed/raw thing
0 (logior (ash (descriptor-bits layout
) 32)
1305 (read-bits-wordindexed thing
0)))
1306 #!-compact-instance-header
1307 ;; Word following the header is the layout
1308 (write-wordindexed thing sb
!vm
:instance-slots-offset layout
))
1310 (defun cold-layout-of (cold-struct)
1311 #!+compact-instance-header
1312 (let ((bits (ash (read-bits-wordindexed cold-struct
0) -
32)))
1313 (if (zerop bits
) *nil-descriptor
* (make-random-descriptor bits
)))
1314 #!-compact-instance-header
1315 (read-wordindexed cold-struct sb
!vm
:instance-slots-offset
))
1317 (defun initialize-layouts ()
1318 (clrhash *cold-layouts
*)
1319 ;; This assertion is due to the fact that MAKE-COLD-LAYOUT does not
1320 ;; know how to set any raw slots.
1321 (aver (eql (layout-bitmap *host-layout-of-layout
*)
1322 sb
!kernel
::+layout-all-tagged
+))
1323 (setq *layout-layout
* (make-fixnum-descriptor 0))
1324 (flet ((chill-layout (name &rest inherits
)
1325 ;; Check that the number of specified INHERITS matches
1326 ;; the length of the layout's inherits in the cross-compiler.
1327 (let ((warm-layout (classoid-layout (find-classoid name
))))
1328 (assert (eql (length (layout-inherits warm-layout
))
1332 (number-to-core (layout-length warm-layout
))
1333 (vector-in-core inherits
)
1334 (number-to-core (layout-depthoid warm-layout
))
1335 (number-to-core (layout-bitmap warm-layout
))))))
1336 (let* ((t-layout (chill-layout 't
))
1337 (s-o-layout (chill-layout 'structure-object t-layout
)))
1338 (setf *layout-layout
* (chill-layout 'layout t-layout s-o-layout
))
1339 (dolist (layout (list t-layout s-o-layout
*layout-layout
*))
1340 (set-instance-layout layout
*layout-layout
*))
1341 (chill-layout 'package t-layout s-o-layout
))))
1343 ;;;; interning symbols in the cold image
1345 ;;; a map from package name as a host string to
1346 ;;; (cold-package-descriptor . (external-symbols . internal-symbols))
1347 (defvar *cold-package-symbols
*)
1348 (declaim (type hash-table
*cold-package-symbols
*))
1350 (setf (get 'find-package
:sb-cold-funcall-handler
/for-value
)
1351 (lambda (descriptor &aux
(name (base-string-from-core descriptor
)))
1352 (or (car (gethash name
*cold-package-symbols
*))
1353 (error "Genesis could not find a target package named ~S" name
))))
1355 (defvar *classoid-cells
*)
1356 (defun cold-find-classoid-cell (name &key create
)
1357 (aver (eq create t
))
1358 (or (gethash name
*classoid-cells
*)
1359 (let ((layout (gethash 'sb
!kernel
::classoid-cell
*cold-layouts
*)) ; ok if nil
1360 (host-layout (find-layout 'sb
!kernel
::classoid-cell
)))
1361 (setf (gethash name
*classoid-cells
*)
1362 (write-slots (allocate-struct *dynamic
* layout
1363 (layout-length host-layout
))
1366 :pcl-class
*nil-descriptor
*
1367 :classoid
*nil-descriptor
*)))))
1369 (setf (get 'find-classoid-cell
:sb-cold-funcall-handler
/for-value
)
1370 #'cold-find-classoid-cell
)
1372 ;;; a map from descriptors to symbols, so that we can back up. The key
1373 ;;; is the address in the target core.
1374 (defvar *cold-symbols
*)
1375 (declaim (type hash-table
*cold-symbols
*))
1377 (defun initialize-packages ()
1378 (let ((package-data-list
1379 ;; docstrings are set in src/cold/warm. It would work to do it here,
1380 ;; but seems preferable not to saddle Genesis with such responsibility.
1381 (list* (sb-cold:make-package-data
:name
"COMMON-LISP" :doc nil
)
1382 (sb-cold:make-package-data
:name
"KEYWORD" :doc nil
)
1383 ;; ANSI encourages us to put extension packages
1384 ;; in the USE list of COMMON-LISP-USER.
1385 (sb-cold:make-package-data
1386 :name
"COMMON-LISP-USER" :doc nil
1387 :use
'("COMMON-LISP" "SB!ALIEN" "SB!DEBUG" "SB!EXT" "SB!GRAY" "SB!PROFILE"))
1388 (sb-cold::package-list-for-genesis
)))
1389 (package-layout (find-layout 'package
))
1390 (target-pkg-list nil
))
1391 (labels ((init-cold-package (name &optional docstring
)
1392 (let ((cold-package (allocate-struct (symbol-value *cold-layout-gspace
*)
1393 (gethash 'package
*cold-layouts
*))))
1394 (setf (gethash name
*cold-package-symbols
*)
1395 (list* cold-package nil nil
))
1396 ;; Initialize string slots
1397 (write-slots cold-package package-layout
1398 :%name
(base-string-to-core
1399 (target-package-name name
))
1400 :%nicknames
(chill-nicknames name
)
1401 :doc-string
(if docstring
1402 (base-string-to-core docstring
)
1404 :%use-list
*nil-descriptor
*)
1405 ;; the cddr of this will accumulate the 'used-by' package list
1406 (push (list name cold-package
) target-pkg-list
)))
1407 (target-package-name (string)
1408 (if (eql (mismatch string
"SB!") 3)
1409 (concatenate 'string
"SB-" (subseq string
3))
1411 (chill-nicknames (pkg-name)
1412 (let ((result *nil-descriptor
*))
1413 ;; Make the package nickname lists for the standard packages
1414 ;; be the minimum specified by ANSI, regardless of what value
1415 ;; the cross-compilation host happens to use.
1416 ;; For packages other than the standard packages, the nickname
1417 ;; list was specified by our package setup code, and we can just
1418 ;; propagate the current state into the target.
1420 (cond ((string= pkg-name
"COMMON-LISP") '("CL"))
1421 ((string= pkg-name
"COMMON-LISP-USER")
1423 ((string= pkg-name
"KEYWORD") '())
1425 ;; 'package-data-list' contains no nicknames.
1426 ;; (See comment in 'set-up-cold-packages')
1427 (aver (null (package-nicknames
1428 (find-package pkg-name
))))
1431 (cold-push (base-string-to-core nickname
) result
))))
1432 (find-cold-package (name)
1433 (cadr (find-package-cell name
)))
1434 (find-package-cell (name)
1435 (or (assoc (if (string= name
"CL") "COMMON-LISP" name
)
1436 target-pkg-list
:test
#'string
=)
1437 (error "No cold package named ~S" name
))))
1438 ;; pass 1: make all proto-packages
1439 (dolist (pd package-data-list
)
1440 (init-cold-package (sb-cold:package-data-name pd
)
1441 #!+sb-doc
(sb-cold::package-data-doc pd
)))
1442 ;; pass 2: set the 'use' lists and collect the 'used-by' lists
1443 (dolist (pd package-data-list
)
1444 (let ((this (find-cold-package (sb-cold:package-data-name pd
)))
1446 (dolist (that (sb-cold:package-data-use pd
))
1447 (let ((cell (find-package-cell that
)))
1448 (push (cadr cell
) use
)
1449 (push this
(cddr cell
))))
1450 (write-slots this package-layout
1451 :%use-list
(list-to-core (nreverse use
)))))
1452 ;; pass 3: set the 'used-by' lists
1453 (dolist (cell target-pkg-list
)
1454 (write-slots (cadr cell
) package-layout
1455 :%used-by-list
(list-to-core (cddr cell
)))))))
1457 ;;; sanity check for a symbol we're about to create on the target
1459 ;;; Make sure that the symbol has an appropriate package. In
1460 ;;; particular, catch the so-easy-to-make error of typing something
1461 ;;; like SB-KERNEL:%BYTE-BLT in cold sources when what you really
1462 ;;; need is SB!KERNEL:%BYTE-BLT.
1463 (defun package-ok-for-target-symbol-p (package)
1464 (let ((package-name (package-name package
)))
1466 ;; Cold interning things in these standard packages is OK. (Cold
1467 ;; interning things in the other standard package, CL-USER, isn't
1468 ;; OK. We just use CL-USER to expose symbols whose homes are in
1469 ;; other packages. Thus, trying to cold intern a symbol whose
1470 ;; home package is CL-USER probably means that a coding error has
1471 ;; been made somewhere.)
1472 (find package-name
'("COMMON-LISP" "KEYWORD") :test
#'string
=)
1473 ;; Cold interning something in one of our target-code packages,
1474 ;; which are ever-so-rigorously-and-elegantly distinguished by
1475 ;; this prefix on their names, is OK too.
1476 (string= package-name
"SB!" :end1
3 :end2
3)
1477 ;; This one is OK too, since it ends up being COMMON-LISP on the
1479 (string= package-name
"SB-XC")
1480 ;; Anything else looks bad. (maybe COMMON-LISP-USER? maybe an extension
1481 ;; package in the xc host? something we can't think of
1482 ;; a valid reason to cold intern, anyway...)
1485 ;;; like SYMBOL-PACKAGE, but safe for symbols which end up on the target
1487 ;;; Most host symbols we dump onto the target are created by SBCL
1488 ;;; itself, so that as long as we avoid gratuitously
1489 ;;; cross-compilation-unfriendly hacks, it just happens that their
1490 ;;; SYMBOL-PACKAGE in the host system corresponds to their
1491 ;;; SYMBOL-PACKAGE in the target system. However, that's not the case
1492 ;;; in the COMMON-LISP package, where we don't get to create the
1493 ;;; symbols but instead have to use the ones that the xc host created.
1494 ;;; In particular, while ANSI specifies which symbols are exported
1495 ;;; from COMMON-LISP, it doesn't specify that their home packages are
1496 ;;; COMMON-LISP, so the xc host can keep them in random packages which
1497 ;;; don't exist on the target (e.g. CLISP keeping some CL-exported
1498 ;;; symbols in the CLOS package).
1499 (defun symbol-package-for-target-symbol (symbol)
1500 ;; We want to catch weird symbols like CLISP's
1501 ;; CL:FIND-METHOD=CLOS::FIND-METHOD, but we don't want to get
1502 ;; sidetracked by ordinary symbols like :CHARACTER which happen to
1503 ;; have the same SYMBOL-NAME as exports from COMMON-LISP.
1504 (multiple-value-bind (cl-symbol cl-status
)
1505 (find-symbol (symbol-name symbol
) *cl-package
*)
1506 (if (and (eq symbol cl-symbol
)
1507 (eq cl-status
:external
))
1508 ;; special case, to work around possible xc host weirdness
1509 ;; in COMMON-LISP package
1512 (let ((result (symbol-package symbol
)))
1513 (unless (package-ok-for-target-symbol-p result
)
1514 (bug "~A in bad package for target: ~A" symbol result
))
1517 (defvar *uninterned-symbol-table
* (make-hash-table :test
#'equal
))
1518 ;; This coalesces references to uninterned symbols, which is allowed because
1519 ;; "similar-as-constant" is defined by string comparison, and since we only have
1520 ;; base-strings during Genesis, there is no concern about upgraded array type.
1521 ;; There is a subtlety of whether coalescing may occur across files
1522 ;; - the target compiler doesn't and couldn't - but here it doesn't matter.
1523 (defun get-uninterned-symbol (name)
1524 (or (gethash name
*uninterned-symbol-table
*)
1525 (let ((cold-symbol (allocate-symbol name nil
)))
1526 (setf (gethash name
*uninterned-symbol-table
*) cold-symbol
))))
1528 ;;; Dump the target representation of HOST-VALUE,
1529 ;;; the type of which is in a restrictive set.
1530 (defun host-constant-to-core (host-value &optional helper
)
1531 (let ((visited (make-hash-table :test
#'eq
)))
1532 (named-let target-representation
((value host-value
))
1533 (unless (typep value
'(or symbol number descriptor
))
1534 (let ((found (gethash value visited
)))
1535 (cond ((eq found
:pending
)
1536 (bug "circular constant?")) ; Circularity not permitted
1538 (return-from target-representation found
))))
1539 (setf (gethash value visited
) :pending
))
1540 (setf (gethash value visited
)
1543 (symbol (if (symbol-package value
)
1545 (get-uninterned-symbol (string value
))))
1546 (number (number-to-core value
))
1547 (string (base-string-to-core value
))
1548 (cons (cold-cons (target-representation (car value
))
1549 (target-representation (cdr value
))))
1551 (vector-in-core (map 'list
#'target-representation value
)))
1553 (or (and helper
(funcall helper value
))
1554 (error "host-constant-to-core: can't convert ~S"
1557 ;; Look up the target's descriptor for #'FUN where FUN is a host symbol.
1558 (defun target-symbol-function (symbol)
1559 (let ((f (cold-fdefn-fun (cold-fdefinition-object symbol
))))
1560 ;; It works only if DEFUN F was seen first.
1561 (aver (not (cold-null f
)))
1564 ;;; Create the effect of executing a (MAKE-ARRAY) call on the target.
1565 ;;; This is for initializing a restricted set of vector constants
1566 ;;; whose contents are typically function pointers.
1567 (defun emulate-target-make-array (form)
1568 (destructuring-bind (size-expr &key initial-element
) (cdr form
)
1569 (let* ((size (eval size-expr
))
1570 (result (allocate-vector-object *dynamic
* sb
!vm
:n-word-bits size
1571 sb
!vm
:simple-vector-widetag
)))
1572 (aver (integerp size
))
1573 (unless (eql initial-element
0)
1574 (let ((target-initial-element
1575 (etypecase initial-element
1576 ((cons (eql function
) (cons symbol null
))
1577 (target-symbol-function (second initial-element
)))
1578 (null *nil-descriptor
*)
1579 ;; Insert more types here ...
1581 (dotimes (index size
)
1582 (cold-svset result
(make-fixnum-descriptor index
)
1583 target-initial-element
))))
1586 ;; Return a target object produced by emulating evaluation of EXPR
1587 ;; with *package* set to ORIGINAL-PACKAGE.
1588 (defun emulate-target-eval (expr original-package
)
1589 (let ((*package
* (find-package original-package
)))
1590 ;; For most things, just call EVAL and dump the host object's
1591 ;; target representation. But with MAKE-ARRAY we allow that the
1592 ;; initial-element might not be evaluable in the host.
1593 ;; Embedded MAKE-ARRAY is kept as-is because we don't "look into"
1594 ;; the EXPR, just hope that it works.
1595 (if (typep expr
'(cons (eql make-array
)))
1596 (emulate-target-make-array expr
)
1597 (host-constant-to-core (eval expr
)))))
1599 ;;; Return a handle on an interned symbol. If necessary allocate the
1600 ;;; symbol and record its home package.
1601 (defun cold-intern (symbol
1603 (gspace (symbol-value *cold-symbol-gspace
*))
1604 &aux
(package (symbol-package-for-target-symbol symbol
)))
1605 (aver (package-ok-for-target-symbol-p package
))
1607 ;; Anything on the cross-compilation host which refers to the target
1608 ;; machinery through the host SB-XC package should be translated to
1609 ;; something on the target which refers to the same machinery
1610 ;; through the target COMMON-LISP package.
1611 (let ((p (find-package "SB-XC")))
1612 (when (eq package p
)
1613 (setf package
*cl-package
*))
1614 (when (eq (symbol-package symbol
) p
)
1615 (setf symbol
(intern (symbol-name symbol
) *cl-package
*))))
1617 (or (get symbol
'cold-intern-info
)
1618 (let ((handle (allocate-symbol (symbol-name symbol
) t
:gspace gspace
)))
1619 (setf (get symbol
'cold-intern-info
) handle
)
1620 ;; maintain reverse map from target descriptor to host symbol
1621 (setf (gethash (descriptor-bits handle
) *cold-symbols
*) symbol
)
1622 (let ((pkg-info (or (gethash (package-name package
) *cold-package-symbols
*)
1623 (error "No target package descriptor for ~S" package
))))
1624 (write-wordindexed handle sb
!vm
:symbol-package-slot
(car pkg-info
))
1625 (record-accessibility
1626 (or access
(nth-value 1 (find-symbol (symbol-name symbol
) package
)))
1627 pkg-info handle package symbol
))
1629 (assign-tls-index symbol handle
)
1630 (acond ((eq package
*keyword-package
*)
1631 (setq access
:external
)
1632 (cold-set handle handle
))
1633 ((assoc symbol sb-cold
:*symbol-values-for-genesis
*)
1634 (cold-set handle
(destructuring-bind (expr . package
) (cdr it
)
1635 (emulate-target-eval expr package
)))))
1638 (defun record-accessibility (accessibility target-pkg-info symbol-descriptor
1639 &optional host-package host-symbol
)
1640 (let ((access-lists (cdr target-pkg-info
)))
1642 (:external
(push symbol-descriptor
(car access-lists
)))
1643 (:internal
(push symbol-descriptor
(cdr access-lists
)))
1644 (t (error "~S inaccessible in package ~S" host-symbol host-package
)))))
1646 ;;; Construct and return a value for use as *NIL-DESCRIPTOR*.
1647 ;;; It might be nice to put NIL on a readonly page by itself to prevent unsafe
1648 ;;; code from destroying the world with (RPLACx nil 'kablooey)
1649 (defun make-nil-descriptor ()
1650 (let* ((des (allocate-header+object
*static
* sb
!vm
:symbol-size
0))
1651 (result (make-descriptor (+ (descriptor-bits des
)
1652 (* 2 sb
!vm
:n-word-bytes
)
1653 (- sb
!vm
:list-pointer-lowtag
1654 sb
!vm
:other-pointer-lowtag
)))))
1655 (write-wordindexed des
1657 (make-other-immediate-descriptor
1659 sb
!vm
:symbol-header-widetag
))
1660 (write-wordindexed des
1661 (+ 1 sb
!vm
:symbol-value-slot
)
1663 (write-wordindexed des
1664 (+ 2 sb
!vm
:symbol-value-slot
) ; = 1 + symbol-hash-slot
1666 (write-wordindexed des
1667 (+ 1 sb
!vm
:symbol-info-slot
)
1668 (cold-cons result result
)) ; NIL's info is (nil . nil)
1669 (write-wordindexed des
1670 (+ 1 sb
!vm
:symbol-name-slot
)
1671 ;; NIL's name is in dynamic space because any extra
1672 ;; bytes allocated in static space would need to
1673 ;; be accounted for by STATIC-SYMBOL-OFFSET.
1674 (base-string-to-core "NIL" *dynamic
*))
1675 (setf (gethash (descriptor-bits result
) *cold-symbols
*) nil
1676 (get nil
'cold-intern-info
) result
)))
1678 ;;; Since the initial symbols must be allocated before we can intern
1679 ;;; anything else, we intern those here. We also set the value of T.
1680 (defun initialize-static-symbols ()
1681 "Initialize the cold load symbol-hacking data structures."
1682 ;; NIL did not have its package assigned. Do that now.
1683 (let ((target-cl-pkg-info (gethash "COMMON-LISP" *cold-package-symbols
*)))
1684 ;; -1 is magic having to do with nil-as-cons vs. nil-as-symbol
1685 (write-wordindexed *nil-descriptor
* (- sb
!vm
:symbol-package-slot
1)
1686 (car target-cl-pkg-info
))
1687 (record-accessibility :external target-cl-pkg-info
*nil-descriptor
*))
1688 ;; Intern the others.
1689 (dolist (symbol sb
!vm
:*static-symbols
*)
1690 (let* ((des (cold-intern symbol
:gspace
*static
*))
1691 (offset-wanted (sb!vm
:static-symbol-offset symbol
))
1692 (offset-found (- (descriptor-bits des
)
1693 (descriptor-bits *nil-descriptor
*))))
1694 (unless (= offset-wanted offset-found
)
1695 (error "Offset from ~S to ~S is ~W, not ~W"
1700 ;; Establish the value of T.
1701 (let ((t-symbol (cold-intern t
:gspace
*static
*)))
1702 (cold-set t-symbol t-symbol
))
1703 ;; Establish the value of *PSEUDO-ATOMIC-BITS* so that the
1704 ;; allocation sequences that expect it to be zero upon entrance
1705 ;; actually find it to be so.
1707 (let ((p-a-a-symbol (cold-intern '*pseudo-atomic-bits
*
1709 (cold-set p-a-a-symbol
(make-fixnum-descriptor 0))))
1711 ;;; Sort *COLD-LAYOUTS* to return them in a deterministic order.
1712 (defun sort-cold-layouts ()
1713 (sort (%hash-table-alist
*cold-layouts
*) #'<
1714 :key
(lambda (x) (descriptor-bits (cdr x
)))))
1716 ;;; a helper function for FINISH-SYMBOLS: Return a cold alist suitable
1717 ;;; to be stored in *!INITIAL-LAYOUTS*.
1718 (defun cold-list-all-layouts ()
1719 (let ((result *nil-descriptor
*))
1720 (dolist (layout (sort-cold-layouts) result
)
1721 (cold-push (cold-cons (cold-intern (car layout
)) (cdr layout
))
1724 ;;; Establish initial values for magic symbols.
1726 (defun finish-symbols ()
1728 ;; Everything between this preserved-for-posterity comment down to
1729 ;; the assignment of *CURRENT-CATCH-BLOCK* could be entirely deleted,
1730 ;; including the list of *C-CALLABLE-STATIC-SYMBOLS* itself,
1731 ;; if it is GC-safe for the C runtime to have its own implementation
1732 ;; of the INFO-VECTOR-FDEFN function in a multi-threaded build.
1734 ;; "I think the point of setting these functions into SYMBOL-VALUEs
1735 ;; here, instead of using SYMBOL-FUNCTION, is that in CMU CL
1736 ;; SYMBOL-FUNCTION reduces to FDEFINITION, which is a pretty
1737 ;; hairy operation (involving globaldb.lisp etc.) which we don't
1738 ;; want to invoke early in cold init. -- WHN 2001-12-05"
1740 ;; So... that's no longer true. We _do_ associate symbol -> fdefn in genesis.
1741 ;; Additionally, the INFO-VECTOR-FDEFN function is extremely simple and could
1742 ;; easily be implemented in C. However, info-vectors are inevitably
1743 ;; reallocated when new info is attached to a symbol, so the vectors can't be
1744 ;; in static space; they'd gradually become permanent garbage if they did.
1745 ;; That's the real reason for preserving the approach of storing an #<fdefn>
1746 ;; in a symbol's value cell - that location is static, the symbol-info is not.
1748 ;; FIXME: So OK, that's a reasonable reason to do something weird like
1749 ;; this, but this is still a weird thing to do, and we should change
1750 ;; the names to highlight that something weird is going on. Perhaps
1751 ;; *MAYBE-GC-FUN*, *INTERNAL-ERROR-FUN*, *HANDLE-BREAKPOINT-FUN*,
1752 ;; and *HANDLE-FUN-END-BREAKPOINT-FUN*...
1753 (dolist (symbol sb
!vm
::*c-callable-static-symbols
*)
1754 (cold-set symbol
(cold-fdefinition-object (cold-intern symbol
))))
1756 (cold-set 'sb
!vm
::*current-catch-block
* (make-fixnum-descriptor 0))
1757 (cold-set 'sb
!vm
::*current-unwind-protect-block
* (make-fixnum-descriptor 0))
1759 (cold-set '*free-interrupt-context-index
* (make-fixnum-descriptor 0))
1761 (cold-set '*!initial-layouts
* (cold-list-all-layouts))
1764 (cold-set 'sb
!vm
::*free-tls-index
*
1765 (make-descriptor (ash *genesis-tls-counter
* sb
!vm
:word-shift
)))
1767 (dolist (symbol sb
!impl
::*cache-vector-symbols
*)
1768 (cold-set symbol
*nil-descriptor
*))
1770 ;; Symbols for which no call to COLD-INTERN would occur - due to not being
1771 ;; referenced until warm init - must be artificially cold-interned.
1772 ;; Inasmuch as the "offending" things are compiled by ordinary target code
1773 ;; and not cold-init, I think we should use an ordinary DEFPACKAGE for
1774 ;; the added-on bits. What I've done is somewhat of a fragile kludge.
1776 (with-package-iterator (iter '("SB!PCL" "SB!MOP" "SB!GRAY" "SB!SEQUENCE"
1777 "SB!PROFILE" "SB!EXT" "SB!VM"
1778 "SB!C" "SB!FASL" "SB!DEBUG")
1781 (multiple-value-bind (foundp sym accessibility package
) (iter)
1782 (declare (ignore accessibility
))
1783 (cond ((not foundp
) (return))
1784 ((eq (symbol-package sym
) package
) (push sym syms
))))))
1785 (setf syms
(stable-sort syms
#'string
<))
1789 (let ((cold-pkg-inits *nil-descriptor
*)
1790 cold-package-symbols-list
)
1791 (maphash (lambda (name info
)
1792 (push (cons name info
) cold-package-symbols-list
))
1793 *cold-package-symbols
*)
1794 (setf cold-package-symbols-list
1795 (sort cold-package-symbols-list
#'string
< :key
#'car
))
1796 (dolist (pkgcons cold-package-symbols-list
)
1797 (destructuring-bind (pkg-name . pkg-info
) pkgcons
1799 ;; Record shadowing symbols (except from SB-XC) in SB! packages.
1800 (when (eql (mismatch pkg-name
"SB!") 3)
1801 ;; Be insensitive to the host's ordering.
1802 (sort (remove (find-package "SB-XC")
1803 (package-shadowing-symbols (find-package pkg-name
))
1804 :key
#'symbol-package
) #'string
<))))
1805 (write-slots (car (gethash pkg-name
*cold-package-symbols
*)) ; package
1806 (find-layout 'package
)
1807 :%shadowing-symbols
(list-to-core
1808 (mapcar 'cold-intern shadow
))))
1809 (unless (member pkg-name
'("COMMON-LISP" "KEYWORD") :test
'string
=)
1810 (let ((host-pkg (find-package pkg-name
))
1811 (sb-xc-pkg (find-package "SB-XC"))
1813 ;; Now for each symbol directly present in this host-pkg,
1814 ;; i.e. accessible but not :INHERITED, figure out if the symbol
1815 ;; came from a different package, and if so, make a note of it.
1816 (with-package-iterator (iter host-pkg
:internal
:external
)
1817 (loop (multiple-value-bind (foundp sym accessibility
) (iter)
1818 (unless foundp
(return))
1819 (unless (or (eq (symbol-package sym
) host-pkg
)
1820 (eq (symbol-package sym
) sb-xc-pkg
))
1821 (push (cons sym accessibility
) syms
)))))
1822 (dolist (symcons (sort syms
#'string
< :key
#'car
))
1823 (destructuring-bind (sym . accessibility
) symcons
1824 (record-accessibility accessibility pkg-info
(cold-intern sym
)
1826 (cold-push (cold-cons (car pkg-info
)
1827 (cold-cons (vector-in-core (cadr pkg-info
))
1828 (vector-in-core (cddr pkg-info
))))
1830 (cold-set 'sb
!impl
::*!initial-symbols
* cold-pkg-inits
))
1832 (dump-symbol-info-vectors
1833 (attach-fdefinitions-to-symbols
1834 (attach-classoid-cells-to-symbols (make-hash-table :test
#'eq
))))
1836 (cold-set '*!initial-debug-sources
* *current-debug-sources
*)
1840 (cold-set 'sb
!vm
::*fp-constant-0d0
* (number-to-core 0d0
))
1841 (cold-set 'sb
!vm
::*fp-constant-1d0
* (number-to-core 1d0
))
1842 (cold-set 'sb
!vm
::*fp-constant-0f0
* (number-to-core 0f0
))
1843 (cold-set 'sb
!vm
::*fp-constant-1f0
* (number-to-core 1f0
))))
1845 ;;;; functions and fdefinition objects
1847 ;;; a hash table mapping from fdefinition names to descriptors of cold
1850 ;;; Note: Since fdefinition names can be lists like '(SETF FOO), and
1851 ;;; we want to have only one entry per name, this must be an 'EQUAL
1852 ;;; hash table, not the default 'EQL.
1853 (defvar *cold-fdefn-objects
*)
1855 (defvar *cold-fdefn-gspace
* nil
)
1857 ;;; Given a cold representation of a symbol, return a warm
1859 (defun warm-symbol (des)
1860 ;; Note that COLD-INTERN is responsible for keeping the
1861 ;; *COLD-SYMBOLS* table up to date, so if DES happens to refer to an
1862 ;; uninterned symbol, the code below will fail. But as long as we
1863 ;; don't need to look up uninterned symbols during bootstrapping,
1865 (multiple-value-bind (symbol found-p
)
1866 (gethash (descriptor-bits des
) *cold-symbols
*)
1867 (declare (type symbol symbol
))
1869 (error "no warm symbol"))
1872 ;;; like CL:CAR, CL:CDR, and CL:NULL but for cold values
1873 (defun cold-car (des)
1874 (aver (= (descriptor-lowtag des
) sb
!vm
:list-pointer-lowtag
))
1875 (read-wordindexed des sb
!vm
:cons-car-slot
))
1876 (defun cold-cdr (des)
1877 (aver (= (descriptor-lowtag des
) sb
!vm
:list-pointer-lowtag
))
1878 (read-wordindexed des sb
!vm
:cons-cdr-slot
))
1879 (defun cold-rplacd (des newval
)
1880 (aver (= (descriptor-lowtag des
) sb
!vm
:list-pointer-lowtag
))
1881 (write-wordindexed des sb
!vm
:cons-cdr-slot newval
)
1883 (defun cold-null (des)
1884 (= (descriptor-bits des
)
1885 (descriptor-bits *nil-descriptor
*)))
1887 ;;; Given a cold representation of a function name, return a warm
1889 (declaim (ftype (function ((or symbol descriptor
)) (or symbol list
)) warm-fun-name
))
1890 (defun warm-fun-name (des)
1893 ;; This parallels the logic at the start of COLD-INTERN
1894 ;; which re-homes symbols in SB-XC to COMMON-LISP.
1895 (if (eq (symbol-package des
) (find-package "SB-XC"))
1896 (intern (symbol-name des
) *cl-package
*)
1898 (ecase (descriptor-lowtag des
)
1899 (#.sb
!vm
:list-pointer-lowtag
1900 (aver (not (cold-null des
))) ; function named NIL? please no..
1901 ;; Do cold (DESTRUCTURING-BIND (COLD-CAR COLD-CADR) DES ..).
1902 (let* ((car-des (cold-car des
))
1903 (cdr-des (cold-cdr des
))
1904 (cadr-des (cold-car cdr-des
))
1905 (cddr-des (cold-cdr cdr-des
)))
1906 (aver (cold-null cddr-des
))
1907 (list (warm-symbol car-des
)
1908 (warm-symbol cadr-des
))))
1909 (#.sb
!vm
:other-pointer-lowtag
1910 (warm-symbol des
))))))
1911 (legal-fun-name-or-type-error result
)
1914 (defun cold-fdefinition-object (cold-name &optional leave-fn-raw
)
1915 (declare (type (or symbol descriptor
) cold-name
))
1916 (declare (special core-file-name
))
1917 (/noshow0
"/cold-fdefinition-object")
1918 (let ((warm-name (warm-fun-name cold-name
)))
1919 (or (gethash warm-name
*cold-fdefn-objects
*)
1920 (let ((fdefn (allocate-header+object
(or *cold-fdefn-gspace
*
1921 #!+immobile-space
*immobile-fixedobj
*
1922 #!-immobile-space
*dynamic
*)
1923 (1- sb
!vm
:fdefn-size
)
1924 sb
!vm
:fdefn-widetag
)))
1925 (setf (gethash warm-name
*cold-fdefn-objects
*) fdefn
)
1926 (write-wordindexed fdefn sb
!vm
:fdefn-name-slot cold-name
)
1927 (unless leave-fn-raw
1928 (write-wordindexed fdefn sb
!vm
:fdefn-fun-slot
*nil-descriptor
*)
1929 (write-wordindexed/raw fdefn
1930 sb
!vm
:fdefn-raw-addr-slot
1931 (or (lookup-assembler-reference
1932 'sb
!vm
::undefined-tramp core-file-name
)
1933 ;; Our preload for the tramps
1934 ;; doesn't happen during host-1,
1935 ;; so substitute a usable value.
1939 (defun cold-functionp (descriptor)
1940 (eql (descriptor-lowtag descriptor
) sb
!vm
:fun-pointer-lowtag
))
1942 (defun cold-fun-entry-addr (fun)
1943 (aver (= (descriptor-lowtag fun
) sb
!vm
:fun-pointer-lowtag
))
1944 (+ (descriptor-bits fun
)
1945 (- sb
!vm
:fun-pointer-lowtag
)
1946 (ash sb
!vm
:simple-fun-code-offset sb
!vm
:word-shift
)))
1948 ;;; Handle a DEFUN in cold-load.
1949 (defun cold-fset (name defn source-loc
&optional inline-expansion
)
1950 ;; SOURCE-LOC can be ignored, because functions intrinsically store
1951 ;; their location as part of the code component.
1952 ;; The argument is supplied here only to provide context for
1953 ;; a redefinition warning, which can't happen in cold load.
1954 (declare (ignore source-loc
))
1955 (sb!int
:binding
* (((cold-name warm-name
)
1956 ;; (SETF f) was descriptorized when dumped, symbols were not.
1958 (values (cold-intern name
) name
)
1959 (values name
(warm-fun-name name
))))
1960 (fdefn (cold-fdefinition-object cold-name t
)))
1961 (when (cold-functionp (cold-fdefn-fun fdefn
))
1962 (error "Duplicate DEFUN for ~S" warm-name
))
1963 ;; There can't be any closures or funcallable instances.
1964 (aver (= (logand (descriptor-bits (read-memory defn
)) sb
!vm
:widetag-mask
)
1965 sb
!vm
:simple-fun-header-widetag
))
1966 (push (cold-cons cold-name inline-expansion
) *!cold-defuns
*)
1967 (write-wordindexed fdefn sb
!vm
:fdefn-fun-slot defn
)
1968 (write-wordindexed fdefn
1969 sb
!vm
:fdefn-raw-addr-slot
1970 #!+(or sparc arm
) defn
1972 (make-random-descriptor
1973 (+ (logandc2 (descriptor-bits defn
)
1975 (ash sb
!vm
:simple-fun-code-offset
1976 sb
!vm
:word-shift
))))
1979 ;;; Handle a DEFMETHOD in cold-load. "Very easily done". Right.
1980 (defun cold-defmethod (name &rest stuff
)
1981 (let ((gf (assoc name
*cold-methods
*)))
1983 (setq gf
(cons name nil
))
1984 (push gf
*cold-methods
*))
1985 (push stuff
(cdr gf
))))
1987 (defun initialize-static-fns ()
1988 (let ((*cold-fdefn-gspace
* *static
*))
1989 (dolist (sym sb
!vm
:*static-funs
*)
1990 (let* ((fdefn (cold-fdefinition-object (cold-intern sym
)))
1991 (offset (- (+ (- (descriptor-bits fdefn
)
1992 sb
!vm
:other-pointer-lowtag
)
1993 (* sb
!vm
:fdefn-raw-addr-slot sb
!vm
:n-word-bytes
))
1994 (descriptor-bits *nil-descriptor
*)))
1995 (desired (sb!vm
:static-fun-offset sym
)))
1996 (unless (= offset desired
)
1997 (error "Offset from FDEFN ~S to ~S is ~W, not ~W."
1998 sym nil offset desired
))))))
2000 (defun attach-classoid-cells-to-symbols (hashtable)
2001 (let ((num (sb!c
::meta-info-number
(sb!c
::meta-info
:type
:classoid-cell
)))
2002 (layout (gethash 'sb
!kernel
::classoid-cell
*cold-layouts
*)))
2003 (when (plusp (hash-table-count *classoid-cells
*))
2005 ;; Iteration order is immaterial. The symbols will get sorted later.
2006 (maphash (lambda (symbol cold-classoid-cell
)
2007 ;; Some classoid-cells are dumped before the cold layout
2008 ;; of classoid-cell has been made, so fix those cases now.
2009 ;; Obviously it would be better if, in general, ALLOCATE-STRUCT
2010 ;; knew when something later must backpatch a cold layout
2011 ;; so that it could make a note to itself to do those ASAP
2012 ;; after the cold layout became known.
2013 (when (cold-null (cold-layout-of cold-classoid-cell
))
2014 (set-instance-layout cold-classoid-cell layout
))
2015 (setf (gethash symbol hashtable
)
2017 (gethash symbol hashtable
+nil-packed-infos
+)
2018 sb
!c
::+no-auxilliary-key
+ num cold-classoid-cell
)))
2022 ;; Create pointer from SYMBOL and/or (SETF SYMBOL) to respective fdefinition
2024 (defun attach-fdefinitions-to-symbols (hashtable)
2025 ;; Collect fdefinitions that go with one symbol, e.g. CAR and (SETF CAR),
2026 ;; using the host's code for manipulating a packed info-vector.
2027 (maphash (lambda (warm-name cold-fdefn
)
2028 (with-globaldb-name (key1 key2
) warm-name
2029 :hairy
(error "Hairy fdefn name in genesis: ~S" warm-name
)
2031 (setf (gethash key1 hashtable
)
2033 (gethash key1 hashtable
+nil-packed-infos
+)
2034 key2
+fdefn-info-num
+ cold-fdefn
))))
2035 *cold-fdefn-objects
*)
2038 (defun dump-symbol-info-vectors (hashtable)
2039 ;; Emit in the same order symbols reside in core to avoid
2040 ;; sensitivity to the iteration order of host's maphash.
2041 (loop for
(warm-sym . info
)
2042 in
(sort (%hash-table-alist hashtable
) #'<
2043 :key
(lambda (x) (descriptor-bits (cold-intern (car x
)))))
2044 do
(write-wordindexed
2045 (cold-intern warm-sym
) sb
!vm
:symbol-info-slot
2046 ;; Each vector will have one fixnum, possibly the symbol SETF,
2047 ;; and one or two #<fdefn> objects in it, and/or a classoid-cell.
2049 (map 'list
(lambda (elt)
2051 (symbol (cold-intern elt
))
2052 (fixnum (make-fixnum-descriptor elt
))
2057 ;;;; fixups and related stuff
2059 ;;; an EQUAL hash table
2060 (defvar *cold-foreign-symbol-table
*)
2061 (declaim (type hash-table
*cold-foreign-symbol-table
*))
2063 ;; Read the sbcl.nm file to find the addresses for foreign-symbols in
2065 (defun load-cold-foreign-symbol-table (filename)
2066 (/show
"load-cold-foreign-symbol-table" filename
)
2067 (with-open-file (file filename
)
2068 (loop for line
= (read-line file nil nil
)
2070 ;; UNIX symbol tables might have tabs in them, and tabs are
2071 ;; not in Common Lisp STANDARD-CHAR, so there seems to be no
2072 ;; nice portable way to deal with them within Lisp, alas.
2073 ;; Fortunately, it's easy to use UNIX command line tools like
2074 ;; sed to remove the problem, so it's not too painful for us
2075 ;; to push responsibility for converting tabs to spaces out to
2078 ;; Other non-STANDARD-CHARs are problematic for the same reason.
2079 ;; Make sure that there aren't any..
2080 (let ((ch (find-if (lambda (char)
2081 (not (typep char
'standard-char
)))
2084 (error "non-STANDARD-CHAR ~S found in foreign symbol table:~%~S"
2087 (setf line
(string-trim '(#\space
) line
))
2088 (let ((p1 (position #\space line
:from-end nil
))
2089 (p2 (position #\space line
:from-end t
)))
2090 (if (not (and p1 p2
(< p1 p2
)))
2091 ;; KLUDGE: It's too messy to try to understand all
2092 ;; possible output from nm, so we just punt the lines we
2093 ;; don't recognize. We realize that there's some chance
2094 ;; that might get us in trouble someday, so we warn
2096 (warn "ignoring unrecognized line ~S in ~A" line filename
)
2097 (multiple-value-bind (value name
)
2098 (if (string= "0x" line
:end2
2)
2099 (values (parse-integer line
:start
2 :end p1
:radix
16)
2100 (subseq line
(1+ p2
)))
2101 (values (parse-integer line
:end p1
:radix
16)
2102 (subseq line
(1+ p2
))))
2103 ;; KLUDGE CLH 2010-05-31: on darwin, nm gives us
2104 ;; _function but dlsym expects us to look up
2105 ;; function, without the leading _ . Therefore, we
2106 ;; strip it off here.
2108 (when (equal (char name
0) #\_
)
2109 (setf name
(subseq name
1)))
2110 (multiple-value-bind (old-value found
)
2111 (gethash name
*cold-foreign-symbol-table
*)
2113 (not (= old-value value
)))
2114 (warn "redefining ~S from #X~X to #X~X"
2115 name old-value value
)))
2116 (/show
"adding to *cold-foreign-symbol-table*:" name value
)
2117 (setf (gethash name
*cold-foreign-symbol-table
*) value
)
2119 (let ((at-position (position #\
@ name
)))
2121 (let ((name (subseq name
0 at-position
)))
2122 (multiple-value-bind (old-value found
)
2123 (gethash name
*cold-foreign-symbol-table
*)
2125 (not (= old-value value
)))
2126 (warn "redefining ~S from #X~X to #X~X"
2127 name old-value value
)))
2128 (setf (gethash name
*cold-foreign-symbol-table
*)
2132 (defun cold-foreign-symbol-address (name)
2133 (or (find-foreign-symbol-in-table name
*cold-foreign-symbol-table
*)
2134 *foreign-symbol-placeholder-value
*
2136 (format *error-output
* "~&The foreign symbol table is:~%")
2137 (maphash (lambda (k v
)
2138 (format *error-output
* "~&~S = #X~8X~%" k v
))
2139 *cold-foreign-symbol-table
*)
2140 (error "The foreign symbol ~S is undefined." name
))))
2142 (defvar *cold-assembler-routines
*)
2144 (defvar *cold-assembler-fixups
*)
2145 (defvar *cold-static-call-fixups
*)
2147 (defun record-cold-assembler-routine (name address
)
2148 (/xhow
"in RECORD-COLD-ASSEMBLER-ROUTINE" name address
)
2149 (push (cons name address
)
2150 *cold-assembler-routines
*))
2152 (defun record-cold-assembler-fixup (routine
2157 (push (list routine code-object offset kind
)
2158 *cold-assembler-fixups
*))
2160 (defun lookup-assembler-reference (symbol &optional
(errorp t
))
2161 (let ((value (cdr (assoc symbol
*cold-assembler-routines
*))))
2164 (error "Assembler routine ~S not defined." symbol
)))
2167 ;;; Unlike in the target, FOP-KNOWN-FUN sometimes has to backpatch.
2168 (defvar *deferred-known-fun-refs
*)
2170 ;;; The x86 port needs to store code fixups along with code objects if
2171 ;;; they are to be moved, so fixups for code objects in the dynamic
2172 ;;; heap need to be noted.
2174 (defvar *load-time-code-fixups
*)
2177 (defun note-load-time-code-fixup (code-object offset
)
2178 ;; If CODE-OBJECT might be moved
2179 (when (= (gspace-identifier (descriptor-intuit-gspace code-object
))
2180 dynamic-core-space-id
)
2181 (push offset
(gethash (descriptor-bits code-object
)
2182 *load-time-code-fixups
*
2187 (defun output-load-time-code-fixups ()
2188 (let ((fixup-infos nil
))
2190 (lambda (code-object-address fixup-offsets
)
2191 (push (cons code-object-address fixup-offsets
) fixup-infos
))
2192 *load-time-code-fixups
*)
2193 (setq fixup-infos
(sort fixup-infos
#'< :key
#'car
))
2194 (dolist (fixup-info fixup-infos
)
2195 (let ((code-object-address (car fixup-info
))
2196 (fixup-offsets (cdr fixup-info
)))
2198 (allocate-vector-object
2199 *dynamic
* sb
!vm
:n-word-bits
(length fixup-offsets
)
2200 sb
!vm
:simple-array-unsigned-byte-32-widetag
)))
2201 (do ((index sb
!vm
:vector-data-offset
(1+ index
))
2202 (fixups fixup-offsets
(cdr fixups
)))
2204 (write-wordindexed/raw fixup-vector index
(car fixups
)))
2205 ;; KLUDGE: The fixup vector is stored as the first constant,
2206 ;; not as a separately-named slot.
2207 (write-wordindexed (make-random-descriptor code-object-address
)
2208 sb
!vm
:code-constants-offset
2211 ;;; Given a pointer to a code object and a byte offset relative to the
2212 ;;; tail of the code object's header, return a byte offset relative to the
2213 ;;; (beginning of the) code object.
2215 (declaim (ftype (function (descriptor sb
!vm
:word
)) calc-offset
))
2216 (defun calc-offset (code-object insts-offset-bytes
)
2217 (+ (ash (logand (get-header-data code-object
) sb
!vm
:short-header-max-words
)
2219 insts-offset-bytes
))
2221 (declaim (ftype (function (descriptor sb
!vm
:word sb
!vm
:word keyword
))
2223 (defun do-cold-fixup (code-object after-header value kind
)
2224 (let* ((offset-within-code-object (calc-offset code-object after-header
))
2225 (gspace-bytes (descriptor-mem code-object
))
2226 (gspace-byte-offset (+ (descriptor-byte-offset code-object
)
2227 offset-within-code-object
))
2228 (gspace-byte-address (gspace-byte-address
2229 (descriptor-gspace code-object
))))
2230 ;; There's just a ton of code here that gets deleted,
2231 ;; inhibiting the view of the the forest through the trees.
2232 ;; Use of #+sbcl would say "probable bug in read-time conditional"
2233 #+#.
(cl:if
(cl:member
:sbcl cl
:*features
*) '(and) '(or))
2234 (declare (sb-ext:muffle-conditions sb-ext
:code-deletion-note
))
2235 (ecase +backend-fasl-file-implementation
+
2236 ;; See CMU CL source for other formerly-supported architectures
2237 ;; (and note that you have to rewrite them to use BVREF-X
2238 ;; instead of SAP-REF).
2242 (assert (zerop (ldb (byte 2 0) value
))))
2244 (let* ((value (if (logbitp 15 value
) (+ value
(ash 1 16)) value
))
2245 (value (if (logbitp 31 value
) (+ value
(ash 1 32)) value
))
2246 (value (if (logbitp 47 value
) (+ value
(ash 1 48)) value
)))
2247 (setf (bvref-8 gspace-bytes gspace-byte-offset
)
2248 (ldb (byte 8 48) value
)
2249 (bvref-8 gspace-bytes
(1+ gspace-byte-offset
))
2250 (ldb (byte 8 56) value
))))
2252 (let* ((value (if (logbitp 15 value
) (+ value
(ash 1 16)) value
))
2253 (value (if (logbitp 31 value
) (+ value
(ash 1 32)) value
)))
2254 (setf (bvref-8 gspace-bytes gspace-byte-offset
)
2255 (ldb (byte 8 32) value
)
2256 (bvref-8 gspace-bytes
(1+ gspace-byte-offset
))
2257 (ldb (byte 8 40) value
))))
2259 (let ((value (if (logbitp 15 value
) (+ value
(ash 1 16)) value
)))
2260 (setf (bvref-8 gspace-bytes gspace-byte-offset
)
2261 (ldb (byte 8 16) value
)
2262 (bvref-8 gspace-bytes
(1+ gspace-byte-offset
))
2263 (ldb (byte 8 24) value
))))
2265 (setf (bvref-8 gspace-bytes gspace-byte-offset
)
2266 (ldb (byte 8 0) value
)
2267 (bvref-8 gspace-bytes
(1+ gspace-byte-offset
))
2268 (ldb (byte 8 8) value
)))
2270 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))))
2274 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))))
2278 (setf (bvref-64 gspace-bytes gspace-byte-offset
) value
))
2280 (setf (ldb (byte 19 5)
2281 (bvref-32 gspace-bytes gspace-byte-offset
))
2282 (ash (- value
(+ gspace-byte-address gspace-byte-offset
))
2285 (setf (ldb (byte 26 0)
2286 (bvref-32 gspace-bytes gspace-byte-offset
))
2287 (ash (- value
(+ gspace-byte-address gspace-byte-offset
))
2292 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))
2294 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2295 (logior (mask-field (byte 18 14)
2296 (bvref-32 gspace-bytes gspace-byte-offset
))
2298 (1+ (ash (ldb (byte 13 0) value
) 1))
2299 (ash (ldb (byte 13 0) value
) 1)))))
2301 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2302 (logior (mask-field (byte 18 14)
2303 (bvref-32 gspace-bytes gspace-byte-offset
))
2305 (1+ (ash (ldb (byte 10 0) value
) 1))
2306 (ash (ldb (byte 11 0) value
) 1)))))
2308 (let ((low-bits (ldb (byte 11 0) value
)))
2309 (assert (<= 0 low-bits
(1- (ash 1 4)))))
2310 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2311 (logior (ash (dpb (ldb (byte 4 0) value
)
2313 (ldb (byte 1 4) value
)) 17)
2314 (logand (bvref-32 gspace-bytes gspace-byte-offset
)
2317 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2318 (logior (mask-field (byte 11 21)
2319 (bvref-32 gspace-bytes gspace-byte-offset
))
2320 (ash (ldb (byte 5 13) value
) 16)
2321 (ash (ldb (byte 2 18) value
) 14)
2322 (ash (ldb (byte 2 11) value
) 12)
2323 (ash (ldb (byte 11 20) value
) 1)
2324 (ldb (byte 1 31) value
))))
2326 (let ((bits (ldb (byte 9 2) value
)))
2327 (assert (zerop (ldb (byte 2 0) value
)))
2328 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2329 (logior (ash bits
3)
2330 (mask-field (byte 1 1) (bvref-32 gspace-bytes gspace-byte-offset
))
2331 (mask-field (byte 3 13) (bvref-32 gspace-bytes gspace-byte-offset
))
2332 (mask-field (byte 11 21) (bvref-32 gspace-bytes gspace-byte-offset
))))))))
2336 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))
2338 (assert (zerop (ash value -
28)))
2339 (setf (ldb (byte 26 0)
2340 (bvref-32 gspace-bytes gspace-byte-offset
))
2343 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2344 (logior (mask-field (byte 16 16)
2345 (bvref-32 gspace-bytes gspace-byte-offset
))
2346 (ash (1+ (ldb (byte 17 15) value
)) -
1))))
2348 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2349 (logior (mask-field (byte 16 16)
2350 (bvref-32 gspace-bytes gspace-byte-offset
))
2351 (ldb (byte 16 0) value
))))))
2352 ;; FIXME: PowerPC Fixups are not fully implemented. The bit
2353 ;; here starts to set things up to work properly, but there
2354 ;; needs to be corresponding code in ppc-vm.lisp
2358 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))
2360 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2361 (dpb (ash value -
2) (byte 24 2)
2362 (bvref-32 gspace-bytes gspace-byte-offset
))))
2364 (let* ((un-fixed-up (bvref-16 gspace-bytes
2365 (+ gspace-byte-offset
2)))
2366 (fixed-up (+ un-fixed-up value
))
2367 (h (ldb (byte 16 16) fixed-up
))
2368 (l (ldb (byte 16 0) fixed-up
)))
2369 (setf (bvref-16 gspace-bytes
(+ gspace-byte-offset
2))
2370 (if (logbitp 15 l
) (ldb (byte 16 0) (1+ h
)) h
))))
2372 (let* ((un-fixed-up (bvref-16 gspace-bytes
2373 (+ gspace-byte-offset
2)))
2374 (fixed-up (+ un-fixed-up value
)))
2375 (setf (bvref-16 gspace-bytes
(+ gspace-byte-offset
2))
2376 (ldb (byte 16 0) fixed-up
))))))
2380 (error "can't deal with call fixups yet"))
2382 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2383 (dpb (ldb (byte 22 10) value
)
2385 (bvref-32 gspace-bytes gspace-byte-offset
))))
2387 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2388 (dpb (ldb (byte 10 0) value
)
2390 (bvref-32 gspace-bytes gspace-byte-offset
))))
2392 (setf (bvref-32 gspace-bytes gspace-byte-offset
) value
))))
2394 ;; XXX: Note that un-fixed-up is read via bvref-word, which is
2395 ;; 64 bits wide on x86-64, but the fixed-up value is written
2396 ;; via bvref-32. This would make more sense if we supported
2397 ;; :absolute64 fixups, but apparently the cross-compiler
2398 ;; doesn't dump them.
2399 (let* ((un-fixed-up (bvref-word gspace-bytes
2400 gspace-byte-offset
))
2401 (code-object-start-addr (logandc2 (descriptor-bits code-object
)
2402 sb
!vm
:lowtag-mask
)))
2403 (assert (= code-object-start-addr
2404 (+ gspace-byte-address
2405 (descriptor-byte-offset code-object
))))
2408 (let ((fixed-up (+ value un-fixed-up
)))
2409 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2411 ;; comment from CMU CL sources:
2413 ;; Note absolute fixups that point within the object.
2414 ;; KLUDGE: There seems to be an implicit assumption in
2415 ;; the old CMU CL code here, that if it doesn't point
2416 ;; before the object, it must point within the object
2417 ;; (not beyond it). It would be good to add an
2418 ;; explanation of why that's true, or an assertion that
2419 ;; it's really true, or both.
2421 ;; One possible explanation is that all absolute fixups
2422 ;; point either within the code object, within the
2423 ;; runtime, within read-only or static-space, or within
2424 ;; the linkage-table space. In all x86 configurations,
2425 ;; these areas are prior to the start of dynamic space,
2426 ;; where all the code-objects are loaded.
2428 (unless (< fixed-up code-object-start-addr
)
2429 (note-load-time-code-fixup code-object
2431 (:relative
; (used for arguments to X86 relative CALL instruction)
2432 (let ((fixed-up (- (+ value un-fixed-up
)
2435 4))) ; "length of CALL argument"
2436 (setf (bvref-32 gspace-bytes gspace-byte-offset
)
2438 ;; Note relative fixups that point outside the code
2439 ;; object, which is to say all relative fixups, since
2440 ;; relative addressing within a code object never needs
2443 (note-load-time-code-fixup code-object
2444 after-header
))))))))
2447 (defun resolve-assembler-fixups ()
2448 (dolist (fixup *cold-assembler-fixups
*)
2449 (let* ((routine (car fixup
))
2450 (value (lookup-assembler-reference routine
)))
2452 (do-cold-fixup (second fixup
) (third fixup
) value
(fourth fixup
)))))
2453 ;; Static calls are very similar to assembler routine calls,
2454 ;; so take care of those too.
2455 (dolist (fixup *cold-static-call-fixups
*)
2456 (destructuring-bind (name kind code offset
) fixup
2457 (do-cold-fixup code offset
2458 (cold-fun-entry-addr
2459 (cold-fdefn-fun (cold-fdefinition-object name
)))
2464 (defparameter *dyncore-address
* sb
!vm
::linkage-table-space-start
)
2465 (defparameter *dyncore-linkage-keys
* nil
)
2466 (defparameter *dyncore-table
* (make-hash-table :test
'equal
))
2468 (defun dyncore-note-symbol (symbol-name datap
)
2469 "Register a symbol and return its address in proto-linkage-table."
2470 (let ((key (cons symbol-name datap
)))
2471 (symbol-macrolet ((entry (gethash key
*dyncore-table
*)))
2474 (prog1 *dyncore-address
*
2475 (push key
*dyncore-linkage-keys
*)
2476 (incf *dyncore-address
* sb
!vm
::linkage-table-entry-size
))))))))
2478 ;;; *COLD-FOREIGN-SYMBOL-TABLE* becomes *!INITIAL-FOREIGN-SYMBOLS* in
2479 ;;; the core. When the core is loaded, !LOADER-COLD-INIT uses this to
2480 ;;; create *STATIC-FOREIGN-SYMBOLS*, which the code in
2481 ;;; target-load.lisp refers to.
2482 (defun foreign-symbols-to-core ()
2483 (let ((result *nil-descriptor
*))
2485 (dolist (symbol (sort (%hash-table-alist
*cold-foreign-symbol-table
*)
2486 #'string
< :key
#'car
))
2487 (cold-push (cold-cons (base-string-to-core (car symbol
))
2488 (number-to-core (cdr symbol
)))
2490 (cold-set '*!initial-foreign-symbols
* result
)
2492 (let ((runtime-linking-list *nil-descriptor
*))
2493 (dolist (symbol *dyncore-linkage-keys
*)
2494 (cold-push (cold-cons (base-string-to-core (car symbol
))
2496 runtime-linking-list
))
2497 (cold-set 'sb
!vm
::*required-runtime-c-symbols
*
2498 runtime-linking-list
)))
2499 (let ((result *nil-descriptor
*))
2500 (dolist (rtn (sort (copy-list *cold-assembler-routines
*) #'string
< :key
#'car
))
2501 (cold-push (cold-cons (cold-intern (car rtn
))
2502 (number-to-core (cdr rtn
)))
2504 (cold-set '*!initial-assembler-routines
* result
)))
2507 ;;;; general machinery for cold-loading FASL files
2509 (defun pop-fop-stack (stack)
2510 (let ((top (svref stack
0)))
2511 (declare (type index top
))
2513 (error "FOP stack empty"))
2514 (setf (svref stack
0) (1- top
))
2517 ;;; Cause a fop to have a special definition for cold load.
2519 ;;; This is similar to DEFINE-FOP, but unlike DEFINE-FOP, this version
2520 ;;; looks up the encoding for this name (created by a previous DEFINE-FOP)
2521 ;;; instead of creating a new encoding.
2522 (defmacro define-cold-fop
((name &optional arglist
) &rest forms
)
2523 (let* ((code (get name
'opcode
))
2524 (argc (aref (car **fop-signatures
**) code
))
2525 (fname (symbolicate "COLD-" name
)))
2527 (error "~S is not a defined FOP." name
))
2528 (when (and (plusp argc
) (not (singleton-p arglist
)))
2529 (error "~S must take one argument" name
))
2531 (defun ,fname
(.fasl-input.
,@arglist
)
2532 (declare (ignorable .fasl-input.
))
2533 (macrolet ((fasl-input () '(the fasl-input .fasl-input.
))
2534 (fasl-input-stream () '(%fasl-input-stream
(fasl-input)))
2536 '(pop-fop-stack (%fasl-input-stack
(fasl-input)))))
2538 ;; We simply overwrite elements of **FOP-FUNS** since the contents
2539 ;; of the host are never propagated directly into the target core.
2540 ,@(loop for i from code to
(logior code
(if (plusp argc
) 3 0))
2541 collect
`(setf (svref **fop-funs
** ,i
) #',fname
)))))
2543 ;;; Cause a fop to be undefined in cold load.
2544 (defmacro not-cold-fop
(name)
2545 `(define-cold-fop (,name
)
2546 (error "The fop ~S is not supported in cold load." ',name
)))
2548 ;;; COLD-LOAD loads stuff into the core image being built by calling
2549 ;;; LOAD-AS-FASL with the fop function table rebound to a table of cold
2550 ;;; loading functions.
2551 (defun cold-load (filename)
2552 "Load the file named by FILENAME into the cold load image being built."
2553 (write-line (namestring filename
))
2554 (with-open-file (s filename
:element-type
'(unsigned-byte 8))
2555 (load-as-fasl s nil nil
)))
2557 ;;;; miscellaneous cold fops
2559 (define-cold-fop (fop-misc-trap) *unbound-marker
*)
2561 (define-cold-fop (fop-character (c))
2562 (make-character-descriptor c
))
2564 (define-cold-fop (fop-empty-list) nil
)
2565 (define-cold-fop (fop-truth) t
)
2567 (define-cold-fop (fop-struct (size)) ; n-words incl. layout, excluding header
2568 (let* ((layout (pop-stack))
2569 (result (allocate-struct *dynamic
* layout size
))
2570 (bitmap (descriptor-fixnum
2571 (read-slot layout
*host-layout-of-layout
* :bitmap
))))
2572 ;; Raw slots can not possibly work because dump-struct uses
2573 ;; %RAW-INSTANCE-REF/WORD which does not exist in the cross-compiler.
2574 ;; Remove this assertion if that problem is somehow circumvented.
2575 (unless (eql bitmap sb
!kernel
::+layout-all-tagged
+)
2576 (error "Raw slots not working in genesis."))
2577 (loop for index downfrom
(1- size
) to sb
!vm
:instance-data-start
2578 for val
= (pop-stack) then
(pop-stack)
2579 do
(write-wordindexed result
2580 (+ index sb
!vm
:instance-slots-offset
)
2581 (if (logbitp index bitmap
)
2583 (descriptor-word-sized-integer val
))))
2586 (define-cold-fop (fop-layout)
2587 (let* ((bitmap-des (pop-stack))
2588 (length-des (pop-stack))
2589 (depthoid-des (pop-stack))
2590 (cold-inherits (pop-stack))
2592 (old-layout-descriptor (gethash name
*cold-layouts
*)))
2593 (declare (type descriptor length-des depthoid-des cold-inherits
))
2594 (declare (type symbol name
))
2595 ;; If a layout of this name has been defined already
2596 (if old-layout-descriptor
2597 ;; Enforce consistency between the previous definition and the
2598 ;; current definition, then return the previous definition.
2599 (flet ((get-slot (keyword)
2600 (read-slot old-layout-descriptor
*host-layout-of-layout
* keyword
)))
2601 (let ((old-length (descriptor-fixnum (get-slot :length
)))
2602 (old-depthoid (descriptor-fixnum (get-slot :depthoid
)))
2603 (old-bitmap (host-object-from-core (get-slot :bitmap
)))
2604 (length (descriptor-fixnum length-des
))
2605 (depthoid (descriptor-fixnum depthoid-des
))
2606 (bitmap (host-object-from-core bitmap-des
)))
2607 (unless (= length old-length
)
2608 (error "cold loading a reference to class ~S when the compile~%~
2609 time length was ~S and current length is ~S"
2613 (unless (cold-vector-elements-eq cold-inherits
(get-slot :inherits
))
2614 (error "cold loading a reference to class ~S when the compile~%~
2615 time inherits were ~S~%~
2616 and current inherits are ~S"
2618 (listify-cold-inherits cold-inherits
)
2619 (listify-cold-inherits (get-slot :inherits
))))
2620 (unless (= depthoid old-depthoid
)
2621 (error "cold loading a reference to class ~S when the compile~%~
2622 time inheritance depthoid was ~S and current inheritance~%~
2627 (unless (= bitmap old-bitmap
)
2628 (error "cold loading a reference to class ~S when the compile~%~
2629 time raw-slot-bitmap was ~S and is currently ~S"
2630 name bitmap old-bitmap
)))
2631 old-layout-descriptor
)
2632 ;; Make a new definition from scratch.
2633 (make-cold-layout name length-des cold-inherits depthoid-des bitmap-des
))))
2635 ;;;; cold fops for loading symbols
2637 ;;; Load a symbol SIZE characters long from FASL-INPUT, and
2638 ;;; intern that symbol in PACKAGE.
2639 (defun cold-load-symbol (length+flag package fasl-input
)
2640 (let ((string (make-string (ash length
+flag -
1))))
2641 (read-string-as-bytes (%fasl-input-stream fasl-input
) string
)
2642 (push-fop-table (intern string package
) fasl-input
)))
2644 ;; I don't feel like hacking up DEFINE-COLD-FOP any more than necessary,
2645 ;; so this code is handcrafted to accept two operands.
2646 (flet ((fop-cold-symbol-in-package-save (fasl-input length
+flag pkg-index
)
2647 (cold-load-symbol length
+flag
(ref-fop-table fasl-input pkg-index
)
2649 (let ((i (get 'fop-symbol-in-package-save
'opcode
)))
2650 (fill **fop-funs
** #'fop-cold-symbol-in-package-save
:start i
:end
(+ i
4))))
2652 (define-cold-fop (fop-lisp-symbol-save (length+flag
))
2653 (cold-load-symbol length
+flag
*cl-package
* (fasl-input)))
2655 (define-cold-fop (fop-keyword-symbol-save (length+flag
))
2656 (cold-load-symbol length
+flag
*keyword-package
* (fasl-input)))
2658 (define-cold-fop (fop-uninterned-symbol-save (length+flag
))
2659 (let ((name (make-string (ash length
+flag -
1))))
2660 (read-string-as-bytes (fasl-input-stream) name
)
2661 (push-fop-table (get-uninterned-symbol name
) (fasl-input))))
2663 (define-cold-fop (fop-copy-symbol-save (index))
2664 (let* ((symbol (ref-fop-table (fasl-input) index
))
2666 (if (symbolp symbol
)
2667 (symbol-name symbol
)
2668 (base-string-from-core
2669 (read-wordindexed symbol sb
!vm
:symbol-name-slot
)))))
2670 ;; Genesis performs additional coalescing of uninterned symbols
2671 (push-fop-table (get-uninterned-symbol name
) (fasl-input))))
2673 ;;;; cold fops for loading packages
2675 (define-cold-fop (fop-named-package-save (namelen))
2676 (let ((name (make-string namelen
)))
2677 (read-string-as-bytes (fasl-input-stream) name
)
2678 (push-fop-table (find-package name
) (fasl-input))))
2680 ;;;; cold fops for loading lists
2682 ;;; Make a list of the top LENGTH things on the fop stack. The last
2683 ;;; cdr of the list is set to LAST.
2684 (defmacro cold-stack-list
(length last
)
2685 `(do* ((index ,length
(1- index
))
2686 (result ,last
(cold-cons (pop-stack) result
)))
2687 ((= index
0) result
)
2688 (declare (fixnum index
))))
2690 (define-cold-fop (fop-list)
2691 (cold-stack-list (read-byte-arg (fasl-input-stream)) *nil-descriptor
*))
2692 (define-cold-fop (fop-list*)
2693 (cold-stack-list (read-byte-arg (fasl-input-stream)) (pop-stack)))
2694 (define-cold-fop (fop-list-1)
2695 (cold-stack-list 1 *nil-descriptor
*))
2696 (define-cold-fop (fop-list-2)
2697 (cold-stack-list 2 *nil-descriptor
*))
2698 (define-cold-fop (fop-list-3)
2699 (cold-stack-list 3 *nil-descriptor
*))
2700 (define-cold-fop (fop-list-4)
2701 (cold-stack-list 4 *nil-descriptor
*))
2702 (define-cold-fop (fop-list-5)
2703 (cold-stack-list 5 *nil-descriptor
*))
2704 (define-cold-fop (fop-list-6)
2705 (cold-stack-list 6 *nil-descriptor
*))
2706 (define-cold-fop (fop-list-7)
2707 (cold-stack-list 7 *nil-descriptor
*))
2708 (define-cold-fop (fop-list-8)
2709 (cold-stack-list 8 *nil-descriptor
*))
2710 (define-cold-fop (fop-list*-
1)
2711 (cold-stack-list 1 (pop-stack)))
2712 (define-cold-fop (fop-list*-
2)
2713 (cold-stack-list 2 (pop-stack)))
2714 (define-cold-fop (fop-list*-
3)
2715 (cold-stack-list 3 (pop-stack)))
2716 (define-cold-fop (fop-list*-
4)
2717 (cold-stack-list 4 (pop-stack)))
2718 (define-cold-fop (fop-list*-
5)
2719 (cold-stack-list 5 (pop-stack)))
2720 (define-cold-fop (fop-list*-
6)
2721 (cold-stack-list 6 (pop-stack)))
2722 (define-cold-fop (fop-list*-
7)
2723 (cold-stack-list 7 (pop-stack)))
2724 (define-cold-fop (fop-list*-
8)
2725 (cold-stack-list 8 (pop-stack)))
2727 ;;;; cold fops for loading vectors
2729 (define-cold-fop (fop-base-string (len))
2730 (let ((string (make-string len
)))
2731 (read-string-as-bytes (fasl-input-stream) string
)
2732 (base-string-to-core string
)))
2735 (define-cold-fop (fop-character-string (len))
2736 (bug "CHARACTER-STRING[~D] dumped by cross-compiler." len
))
2738 (define-cold-fop (fop-vector (size))
2739 (let* ((result (allocate-vector-object *dynamic
*
2742 sb
!vm
:simple-vector-widetag
)))
2743 (do ((index (1- size
) (1- index
)))
2745 (declare (fixnum index
))
2746 (write-wordindexed result
2747 (+ index sb
!vm
:vector-data-offset
)
2751 (define-cold-fop (fop-spec-vector)
2752 (let* ((len (read-word-arg (fasl-input-stream)))
2753 (type (read-byte-arg (fasl-input-stream)))
2754 (sizebits (aref **saetp-bits-per-length
** type
))
2755 (result (progn (aver (< sizebits
255))
2756 (allocate-vector-object *dynamic
* sizebits len type
)))
2757 (start (+ (descriptor-byte-offset result
)
2758 (ash sb
!vm
:vector-data-offset sb
!vm
:word-shift
)))
2760 (ceiling (* len sizebits
)
2761 sb
!vm
:n-byte-bits
))))
2762 (read-bigvec-as-sequence-or-die (descriptor-mem result
)
2768 (not-cold-fop fop-array
)
2770 ;; This code is unexercised. The only use of FOP-ARRAY is from target-dump.
2771 ;; It would be a shame to delete it though, as it might come in handy.
2772 (define-cold-fop (fop-array)
2773 (let* ((rank (read-word-arg (fasl-input-stream)))
2774 (data-vector (pop-stack))
2775 (result (allocate-object *dynamic
*
2776 (+ sb
!vm
:array-dimensions-offset rank
)
2777 sb
!vm
:other-pointer-lowtag
)))
2778 (write-header-word result rank sb
!vm
:simple-array-widetag
)
2779 (write-wordindexed result sb
!vm
:array-fill-pointer-slot
*nil-descriptor
*)
2780 (write-wordindexed result sb
!vm
:array-data-slot data-vector
)
2781 (write-wordindexed result sb
!vm
:array-displacement-slot
*nil-descriptor
*)
2782 (write-wordindexed result sb
!vm
:array-displaced-p-slot
*nil-descriptor
*)
2783 (write-wordindexed result sb
!vm
:array-displaced-from-slot
*nil-descriptor
*)
2784 (let ((total-elements 1))
2785 (dotimes (axis rank
)
2786 (let ((dim (pop-stack)))
2787 (unless (is-fixnum-lowtag (descriptor-lowtag dim
))
2788 (error "non-fixnum dimension? (~S)" dim
))
2789 (setf total-elements
(* total-elements
(descriptor-fixnum dim
)))
2790 (write-wordindexed result
2791 (+ sb
!vm
:array-dimensions-offset axis
)
2793 (write-wordindexed result
2794 sb
!vm
:array-elements-slot
2795 (make-fixnum-descriptor total-elements
)))
2799 ;;;; cold fops for loading numbers
2801 (defmacro define-cold-number-fop
(fop &optional arglist
)
2802 ;; Invoke the ordinary warm version of this fop to cons the number.
2803 `(define-cold-fop (,fop
,arglist
)
2804 (number-to-core (,fop
(fasl-input) ,@arglist
))))
2806 (define-cold-number-fop fop-single-float
)
2807 (define-cold-number-fop fop-double-float
)
2808 (define-cold-number-fop fop-word-integer
)
2809 (define-cold-number-fop fop-byte-integer
)
2810 (define-cold-number-fop fop-complex-single-float
)
2811 (define-cold-number-fop fop-complex-double-float
)
2812 (define-cold-number-fop fop-integer
(n-bytes))
2814 (define-cold-fop (fop-ratio)
2815 (let ((den (pop-stack)))
2816 (number-pair-to-core (pop-stack) den sb
!vm
:ratio-widetag
)))
2818 (define-cold-fop (fop-complex)
2819 (let ((im (pop-stack)))
2820 (number-pair-to-core (pop-stack) im sb
!vm
:complex-widetag
)))
2822 ;;;; cold fops for calling (or not calling)
2824 (not-cold-fop fop-eval
)
2825 (not-cold-fop fop-eval-for-effect
)
2827 (defvar *load-time-value-counter
*)
2829 (flet ((pop-args (fasl-input)
2831 (stack (%fasl-input-stack fasl-input
)))
2832 (dotimes (i (read-byte-arg (%fasl-input-stream fasl-input
))
2833 (values (pop-fop-stack stack
) args
))
2834 (push (pop-fop-stack stack
) args
))))
2835 (call (fun-name handler-name args
)
2836 (acond ((get fun-name handler-name
) (apply it args
))
2837 (t (error "Can't ~S ~S in cold load" handler-name fun-name
)))))
2839 (define-cold-fop (fop-funcall)
2840 (multiple-value-bind (fun args
) (pop-args (fasl-input))
2844 ;; Special form #'F fopcompiles into `(FDEFINITION ,f)
2845 (aver (and (singleton-p args
) (symbolp (car args
))))
2846 (target-symbol-function (car args
)))
2847 (cons (cold-cons (first args
) (second args
)))
2848 (symbol-global-value (cold-symbol-value (first args
)))
2849 (t (call fun
:sb-cold-funcall-handler
/for-value args
)))
2850 (let ((counter *load-time-value-counter
*))
2851 (push (cold-list (cold-intern :load-time-value
) fun
2852 (number-to-core counter
)) *!cold-toplevels
*)
2853 (setf *load-time-value-counter
* (1+ counter
))
2854 (make-descriptor 0 :load-time-value counter
)))))
2856 (define-cold-fop (fop-funcall-for-effect)
2857 (multiple-value-bind (fun args
) (pop-args (fasl-input))
2859 (push fun
*!cold-toplevels
*)
2861 (sb!impl
::%defun
(apply #'cold-fset args
))
2862 (sb!pcl
::!trivial-defmethod
(apply #'cold-defmethod
args))
2863 (sb!kernel
::%defstruct
2864 (push args
*known-structure-classoids
*)
2865 (push (apply #'cold-list
(cold-intern 'defstruct
) args
)
2868 (destructuring-bind (name val . rest
) args
2869 (cold-set name
(if (symbolp val
) (cold-intern val
) val
))
2870 (push (cold-cons (cold-intern name
) (list-to-core rest
))
2871 *!cold-defconstants
*)))
2873 (aver (= (length args
) 2))
2874 (cold-set (first args
)
2875 (let ((val (second args
)))
2876 (if (symbolp val
) (cold-intern val
) val
))))
2877 (%svset
(apply 'cold-svset args
))
2878 (t (call fun
:sb-cold-funcall-handler
/for-effect args
)))))))
2880 (defun finalize-load-time-value-noise ()
2881 (cold-set '*!load-time-values
*
2882 (allocate-vector-object *dynamic
*
2884 *load-time-value-counter
*
2885 sb
!vm
:simple-vector-widetag
)))
2888 ;;;; cold fops for fixing up circularities
2890 (define-cold-fop (fop-rplaca)
2891 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2892 (idx (read-word-arg (fasl-input-stream))))
2893 (write-memory (cold-nthcdr idx obj
) (pop-stack))))
2895 (define-cold-fop (fop-rplacd)
2896 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2897 (idx (read-word-arg (fasl-input-stream))))
2898 (write-wordindexed (cold-nthcdr idx obj
) 1 (pop-stack))))
2900 (define-cold-fop (fop-svset)
2901 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2902 (idx (read-word-arg (fasl-input-stream))))
2903 (write-wordindexed obj
2905 (ecase (descriptor-lowtag obj
)
2906 (#.sb
!vm
:instance-pointer-lowtag
1)
2907 (#.sb
!vm
:other-pointer-lowtag
2)))
2910 (define-cold-fop (fop-structset)
2911 (let ((obj (ref-fop-table (fasl-input) (read-word-arg (fasl-input-stream))))
2912 (idx (read-word-arg (fasl-input-stream))))
2913 (write-wordindexed obj
(+ idx sb
!vm
:instance-slots-offset
) (pop-stack))))
2915 (define-cold-fop (fop-nthcdr)
2916 (cold-nthcdr (read-word-arg (fasl-input-stream)) (pop-stack)))
2918 (defun cold-nthcdr (index obj
)
2920 (setq obj
(read-wordindexed obj sb
!vm
:cons-cdr-slot
)))
2923 ;;;; cold fops for loading code objects and functions
2925 (define-cold-fop (fop-note-debug-source)
2926 (let ((debug-source (pop-stack)))
2927 (cold-push debug-source
*current-debug-sources
*)))
2929 (define-cold-fop (fop-fdefn)
2930 (cold-fdefinition-object (pop-stack)))
2932 (define-cold-fop (fop-known-fun)
2933 (let* ((name (pop-stack))
2934 (fun (cold-fdefn-fun (cold-fdefinition-object name
))))
2935 (if (cold-null fun
) `(:known-fun .
,name
) fun
)))
2938 (define-cold-fop (fop-sanctify-for-execution)
2941 ;;; Setting this variable shows what code looks like before any
2942 ;;; fixups (or function headers) are applied.
2943 #!+sb-show
(defvar *show-pre-fixup-code-p
* nil
)
2945 (defun cold-load-code (fasl-input code-size nconst nfuns
)
2946 (macrolet ((pop-stack () '(pop-fop-stack (%fasl-input-stack fasl-input
))))
2947 (let* ((raw-header-n-words (+ sb
!vm
:code-constants-offset nconst
))
2948 ;; Note that the number of constants is rounded up to ensure
2949 ;; that the code vector will be properly aligned.
2950 (header-n-words (round-up raw-header-n-words
2))
2951 (toplevel-p (pop-stack))
2952 (debug-info (pop-stack))
2953 (des (allocate-cold-descriptor
2954 #!-immobile-code
*dynamic
*
2955 ;; toplevel-p is an indicator of whether the code will
2956 ;; will become garbage. If so, put it in dynamic space,
2957 ;; otherwise immobile space.
2959 (if toplevel-p
*dynamic
* *immobile-varyobj
*)
2960 (+ (ash header-n-words sb
!vm
:word-shift
) code-size
)
2961 sb
!vm
:other-pointer-lowtag
)))
2962 (declare (ignorable toplevel-p
))
2963 (write-header-word des header-n-words sb
!vm
:code-header-widetag
)
2964 (write-wordindexed des sb
!vm
:code-code-size-slot
2965 (make-fixnum-descriptor code-size
))
2966 (write-wordindexed des sb
!vm
:code-debug-info-slot debug-info
)
2967 (do ((index (1- raw-header-n-words
) (1- index
)))
2968 ((< index sb
!vm
:code-constants-offset
))
2969 (let ((obj (pop-stack)))
2970 (if (and (consp obj
) (eq (car obj
) :known-fun
))
2971 (push (list* (cdr obj
) des index
) *deferred-known-fun-refs
*)
2972 (write-wordindexed des index obj
))))
2973 (let* ((start (+ (descriptor-byte-offset des
)
2974 (ash header-n-words sb
!vm
:word-shift
)))
2975 (end (+ start code-size
)))
2976 (read-bigvec-as-sequence-or-die (descriptor-mem des
)
2977 (%fasl-input-stream fasl-input
)
2981 ;; Emulate NEW-SIMPLE-FUN in target-core
2982 (loop for fun-index from
(1- nfuns
) downto
0
2983 do
(let ((offset (read-varint-arg fasl-input
)))
2985 (let ((bytes (descriptor-mem des
))
2986 (index (+ (descriptor-byte-offset des
)
2987 (calc-offset des
(ash (1- fun-index
) 2)))))
2988 (aver (eql (bvref-32 bytes index
) 0))
2989 (setf (bvref-32 bytes index
) offset
))
2991 (write-wordindexed/raw
2993 sb
!vm
::code-n-entries-slot
2994 (logior (ash offset
16)
2995 (ash nfuns sb
!vm
:n-fixnum-tag-bits
)))
2997 (write-wordindexed/raw
2999 (logior (ash (logior (ash offset
16) nfuns
) 32)
3000 (read-bits-wordindexed des
0))))))
3003 (when *show-pre-fixup-code-p
*
3004 (format *trace-output
*
3005 "~&/raw code from code-fop ~W ~W:~%"
3008 (do ((i start
(+ i sb
!vm
:n-word-bytes
)))
3010 (format *trace-output
*
3011 "/#X~8,'0x: #X~8,'0x~%"
3012 (+ i
(gspace-byte-address (descriptor-gspace des
)))
3013 (bvref-32 (descriptor-mem des
) i
)))))
3016 (let ((i (get 'fop-code
'opcode
)))
3017 (fill **fop-funs
** #'cold-load-code
:start i
:end
(+ i
4)))
3019 (defun resolve-deferred-known-funs ()
3020 (dolist (item *deferred-known-fun-refs
*)
3021 (let ((fun (cold-fdefn-fun (cold-fdefinition-object (car item
)))))
3022 (aver (not (cold-null fun
)))
3023 (let ((place (cdr item
)))
3024 (write-wordindexed (car place
) (cdr place
) fun
)))))
3026 (define-cold-fop (fop-alter-code (slot))
3027 (let ((value (pop-stack))
3029 (write-wordindexed code slot value
)))
3031 (defvar *simple-fun-metadata
* (make-hash-table :test
'equalp
))
3033 ;; Return an expression that can be used to coalesce type-specifiers
3034 ;; and lambda lists attached to simple-funs. It doesn't have to be
3035 ;; a "correct" host representation, just something that preserves EQUAL-ness.
3036 (defun make-equal-comparable-thing (descriptor)
3037 (labels ((recurse (x)
3038 (cond ((cold-null x
) (return-from recurse nil
))
3039 ((is-fixnum-lowtag (descriptor-lowtag x
))
3040 (return-from recurse
(descriptor-fixnum x
)))
3042 ((is-other-immediate-lowtag (descriptor-lowtag x
))
3043 (let ((bits (descriptor-bits x
)))
3044 (when (= (logand bits sb
!vm
:widetag-mask
)
3045 sb
!vm
:single-float-widetag
)
3046 (return-from recurse
`(:ffloat-bits
,bits
))))))
3047 (ecase (descriptor-lowtag x
)
3048 (#.sb
!vm
:list-pointer-lowtag
3049 (cons (recurse (cold-car x
)) (recurse (cold-cdr x
))))
3050 (#.sb
!vm
:other-pointer-lowtag
3051 (ecase (logand (descriptor-bits (read-memory x
)) sb
!vm
:widetag-mask
)
3052 (#.sb
!vm
:symbol-header-widetag
3053 (if (cold-null (read-wordindexed x sb
!vm
:symbol-package-slot
))
3054 (get-or-make-uninterned-symbol
3055 (base-string-from-core
3056 (read-wordindexed x sb
!vm
:symbol-name-slot
)))
3059 (#.sb
!vm
:single-float-widetag
3061 ,(read-bits-wordindexed x sb
!vm
:single-float-value-slot
)))
3062 (#.sb
!vm
:double-float-widetag
3064 ,(read-bits-wordindexed x sb
!vm
:double-float-value-slot
)
3066 ,(read-bits-wordindexed
3067 x
(1+ sb
!vm
:double-float-value-slot
))))
3068 (#.sb
!vm
:bignum-widetag
3069 (bignum-from-core x
))
3070 (#.sb
!vm
:simple-base-string-widetag
3071 (base-string-from-core x
))
3072 ;; Why do function lambda lists have simple-vectors in them?
3073 ;; Because we expose all &OPTIONAL and &KEY default forms.
3074 ;; I think this is abstraction leakage, except possibly for
3075 ;; advertised constant defaults of NIL and such.
3076 ;; How one expresses a value as a sexpr should otherwise
3077 ;; be of no concern to a user of the code.
3078 (#.sb
!vm
:simple-vector-widetag
3079 (vector-from-core x
#'recurse
))))))
3080 ;; Return a warm symbol whose name is similar to NAME, coaelescing
3081 ;; all occurrences of #:.WHOLE. across all files, e.g.
3082 (get-or-make-uninterned-symbol (name)
3083 (let ((key `(:uninterned-symbol
,name
)))
3084 (or (gethash key
*simple-fun-metadata
*)
3085 (let ((symbol (make-symbol name
)))
3086 (setf (gethash key
*simple-fun-metadata
*) symbol
))))))
3087 (recurse descriptor
)))
3089 (defun fun-offset (code-object fun-index
)
3091 (bvref-32 (descriptor-mem code-object
)
3092 (+ (descriptor-byte-offset code-object
)
3093 (calc-offset code-object
(ash (1- fun-index
) 2))))
3095 #!-
64-bit
(read-bits-wordindexed code-object sb
!vm
::code-n-entries-slot
)
3096 #!+64-bit
(ldb (byte 32 32) (read-bits-wordindexed code-object
0)))))
3098 (defun compute-fun (code-object fun-index
)
3099 (let* ((offset-from-insns-start (fun-offset code-object fun-index
))
3100 (offset-from-code-start (calc-offset code-object offset-from-insns-start
)))
3101 (unless (zerop (logand offset-from-code-start sb
!vm
:lowtag-mask
))
3102 (error "unaligned function entry ~S ~S" code-object fun-index
))
3103 (values (ash offset-from-code-start
(- sb
!vm
:word-shift
))
3105 (logior (+ (logandc2 (descriptor-bits code-object
) sb
!vm
:lowtag-mask
)
3106 offset-from-code-start
)
3107 sb
!vm
:fun-pointer-lowtag
)))))
3109 (defun cold-fop-fun-entry (fasl-input fun-index
)
3110 (binding* (((info type arglist name code-object
)
3111 (macrolet ((pop-stack ()
3112 '(pop-fop-stack (%fasl-input-stack fasl-input
))))
3113 (values (pop-stack) (pop-stack) (pop-stack) (pop-stack) (pop-stack))))
3115 (compute-fun code-object fun-index
)))
3116 (write-memory fn
(make-other-immediate-descriptor
3117 word-offset sb
!vm
:simple-fun-header-widetag
))
3118 #!+(or x86 x86-64
) ; store a machine-native pointer to the function entry
3119 ;; note that the bit pattern looks like fixnum due to alignment
3120 (write-wordindexed/raw fn sb
!vm
:simple-fun-self-slot
3121 (+ (- (descriptor-bits fn
) sb
!vm
:fun-pointer-lowtag
)
3122 (ash sb
!vm
:simple-fun-code-offset sb
!vm
:word-shift
)))
3123 #!-
(or x86 x86-64
) ; store a pointer back to the function itself in 'self'
3124 (write-wordindexed fn sb
!vm
:simple-fun-self-slot fn
)
3125 (write-wordindexed fn sb
!vm
:simple-fun-name-slot name
)
3126 (flet ((coalesce (sexpr) ; a warm symbol or a cold cons tree
3127 (if (symbolp sexpr
) ; will be cold-interned automatically
3129 (let ((representation (make-equal-comparable-thing sexpr
)))
3130 (or (gethash representation
*simple-fun-metadata
*)
3131 (setf (gethash representation
*simple-fun-metadata
*)
3133 (write-wordindexed fn sb
!vm
:simple-fun-arglist-slot
(coalesce arglist
))
3134 (write-wordindexed fn sb
!vm
:simple-fun-type-slot
(coalesce type
)))
3135 (write-wordindexed fn sb
!vm
::simple-fun-info-slot info
)
3138 (let ((i (get 'fop-fun-entry
'opcode
)))
3139 (fill **fop-funs
** #'cold-fop-fun-entry
:start i
:end
(+ i
4)))
3142 (define-cold-fop (fop-symbol-tls-fixup)
3143 (let* ((symbol (pop-stack))
3145 (code-object (pop-stack)))
3146 (do-cold-fixup code-object
3147 (read-word-arg (fasl-input-stream))
3148 (ensure-symbol-tls-index symbol
) kind
)
3151 (define-cold-fop (fop-foreign-fixup)
3152 (let* ((kind (pop-stack))
3153 (code-object (pop-stack))
3154 (len (read-byte-arg (fasl-input-stream)))
3155 (sym (make-string len
)))
3156 (read-string-as-bytes (fasl-input-stream) sym
)
3158 (let ((offset (read-word-arg (fasl-input-stream)))
3159 (value (dyncore-note-symbol sym nil
)))
3160 (do-cold-fixup code-object offset value kind
))
3161 #!-
(and) (format t
"Bad non-plt fixup: ~S~S~%" sym code-object
)
3163 (let ((offset (read-word-arg (fasl-input-stream)))
3164 (value (cold-foreign-symbol-address sym
)))
3165 (do-cold-fixup code-object offset value kind
))
3169 (define-cold-fop (fop-foreign-dataref-fixup)
3170 (let* ((kind (pop-stack))
3171 (code-object (pop-stack))
3172 (len (read-byte-arg (fasl-input-stream)))
3173 (sym (make-string len
)))
3174 #!-sb-dynamic-core
(declare (ignore code-object
))
3175 (read-string-as-bytes (fasl-input-stream) sym
)
3177 (let ((offset (read-word-arg (fasl-input-stream)))
3178 (value (dyncore-note-symbol sym t
)))
3179 (do-cold-fixup code-object offset value kind
)
3183 (maphash (lambda (k v
)
3184 (format *error-output
* "~&~S = #X~8X~%" k v
))
3185 *cold-foreign-symbol-table
*)
3186 (error "shared foreign symbol in cold load: ~S (~S)" sym kind
))))
3188 (define-cold-fop (fop-assembler-code)
3189 (let* ((length (read-word-arg (fasl-input-stream)))
3191 ;; Note: we round the number of constants up to ensure that
3192 ;; the code vector will be properly aligned.
3193 (round-up sb
!vm
:code-constants-offset
2))
3194 (des (allocate-cold-descriptor *read-only
*
3195 (+ (ash header-n-words
3198 sb
!vm
:other-pointer-lowtag
)))
3199 (write-header-word des header-n-words sb
!vm
:code-header-widetag
)
3200 (write-wordindexed des
3201 sb
!vm
:code-code-size-slot
3202 (make-fixnum-descriptor length
))
3203 (write-wordindexed des sb
!vm
:code-debug-info-slot
*nil-descriptor
*)
3205 (let* ((start (+ (descriptor-byte-offset des
)
3206 (ash header-n-words sb
!vm
:word-shift
)))
3207 (end (+ start length
)))
3208 (read-bigvec-as-sequence-or-die (descriptor-mem des
)
3214 (define-cold-fop (fop-assembler-routine)
3215 (let* ((routine (pop-stack))
3217 (offset (calc-offset des
(read-word-arg (fasl-input-stream)))))
3218 (record-cold-assembler-routine
3220 (+ (logandc2 (descriptor-bits des
) sb
!vm
:lowtag-mask
) offset
))
3223 (define-cold-fop (fop-assembler-fixup)
3224 (let* ((routine (pop-stack))
3226 (code-object (pop-stack))
3227 (offset (read-word-arg (fasl-input-stream))))
3228 (record-cold-assembler-fixup routine code-object offset kind
)
3231 (define-cold-fop (fop-code-object-fixup)
3232 (let* ((kind (pop-stack))
3233 (code-object (pop-stack))
3234 (offset (read-word-arg (fasl-input-stream)))
3235 (value (descriptor-bits code-object
)))
3236 (do-cold-fixup code-object offset value kind
)
3240 (define-cold-fop (fop-static-call-fixup)
3241 (let ((name (pop-stack))
3243 (code-object (pop-stack))
3244 (offset (read-word-arg (fasl-input-stream))))
3245 (push (list name kind code-object offset
) *cold-static-call-fixups
*)
3249 ;;;; sanity checking space layouts
3251 (defun check-spaces ()
3252 ;;; Co-opt type machinery to check for intersections...
3254 (flet ((check (start end space
)
3255 (unless (< start end
)
3256 (error "Bogus space: ~A" space
))
3257 (let ((type (specifier-type `(integer ,start
,end
))))
3258 (dolist (other types
)
3259 (unless (eq *empty-type
* (type-intersection (cdr other
) type
))
3260 (error "Space overlap: ~A with ~A" space
(car other
))))
3261 (push (cons space type
) types
))))
3262 (check sb
!vm
:read-only-space-start sb
!vm
:read-only-space-end
:read-only
)
3263 (check sb
!vm
:static-space-start sb
!vm
:static-space-end
:static
)
3265 (check sb
!vm
:dynamic-space-start sb
!vm
:dynamic-space-end
:dynamic
)
3267 ;; Must be a multiple of 32 because it makes the math a nicer
3268 ;; when computing word and bit index into the 'touched' bitmap.
3269 (assert (zerop (rem sb
!vm
:immobile-fixedobj-subspace-size
3270 (* 32 sb
!vm
:immobile-card-bytes
))))
3273 (check sb
!vm
:dynamic-0-space-start sb
!vm
:dynamic-0-space-end
:dynamic-0
)
3274 (check sb
!vm
:dynamic-1-space-start sb
!vm
:dynamic-1-space-end
:dynamic-1
))
3276 (check sb
!vm
:linkage-table-space-start sb
!vm
:linkage-table-space-end
:linkage-table
))))
3278 ;;;; emitting C header file
3280 (defun tailwise-equal (string tail
)
3281 (and (>= (length string
) (length tail
))
3282 (string= string tail
:start1
(- (length string
) (length tail
)))))
3284 (defun write-boilerplate (*standard-output
*)
3287 '("This is a machine-generated file. Please do not edit it by hand."
3288 "(As of sbcl-0.8.14, it came from WRITE-CONFIG-H in genesis.lisp.)"
3290 "This file contains low-level information about the"
3291 "internals of a particular version and configuration"
3292 "of SBCL. It is used by the C compiler to create a runtime"
3293 "support environment, an executable program in the host"
3294 "operating system's native format, which can then be used to"
3295 "load and run 'core' files, which are basically programs"
3296 "in SBCL's own format."))
3297 (format t
" *~@[ ~A~]~%" line
))
3300 (defun c-name (string &optional strip
)
3302 (substitute-if #\_
(lambda (c) (member c
'(#\-
#\
/ #\%
)))
3303 (remove-if (lambda (c) (position c strip
))
3306 (defun c-symbol-name (symbol &optional strip
)
3307 (c-name (symbol-name symbol
) strip
))
3309 (defun write-makefile-features (*standard-output
*)
3310 ;; propagating *SHEBANG-FEATURES* into the Makefiles
3311 (dolist (shebang-feature-name (sort (mapcar #'c-symbol-name
3312 sb-cold
:*shebang-features
*)
3314 (format t
"LISP_FEATURE_~A=1~%" shebang-feature-name
)))
3316 (defun write-config-h (*standard-output
*)
3317 ;; propagating *SHEBANG-FEATURES* into C-level #define's
3318 (dolist (shebang-feature-name (sort (mapcar #'c-symbol-name
3319 sb-cold
:*shebang-features
*)
3321 (format t
"#define LISP_FEATURE_~A~%" shebang-feature-name
))
3323 ;; and miscellaneous constants
3324 (format t
"#define SBCL_VERSION_STRING ~S~%"
3325 (sb!xc
:lisp-implementation-version
))
3326 (format t
"#define CORE_MAGIC 0x~X~%" core-magic
)
3327 (format t
"#ifndef LANGUAGE_ASSEMBLY~2%")
3328 (format t
"#define LISPOBJ(x) ((lispobj)x)~2%")
3329 (format t
"#else /* LANGUAGE_ASSEMBLY */~2%")
3330 (format t
"#define LISPOBJ(thing) thing~2%")
3331 (format t
"#endif /* LANGUAGE_ASSEMBLY */~2%")
3334 (defun write-constants-h (*standard-output
*)
3335 ;; writing entire families of named constants
3336 (let ((constants nil
))
3337 (dolist (package-name '( ;; Even in CMU CL, constants from VM
3338 ;; were automatically propagated
3339 ;; into the runtime.
3341 ;; In SBCL, we also propagate various
3342 ;; magic numbers related to file format,
3343 ;; which live here instead of SB!VM.
3345 (do-external-symbols (symbol (find-package package-name
))
3346 (when (constantp symbol
)
3347 (let ((name (symbol-name symbol
)))
3348 (labels ( ;; shared machinery
3349 (record (string priority suffix
)
3352 (symbol-value symbol
)
3354 (documentation symbol
'variable
))
3356 ;; machinery for old-style CMU CL Lisp-to-C
3357 ;; arbitrary renaming, being phased out in favor of
3358 ;; the newer systematic RECORD-WITH-TRANSLATED-NAME
3360 (record-with-munged-name (prefix string priority
)
3361 (record (concatenate
3364 (delete #\-
(string-capitalize string
)))
3367 (maybe-record-with-munged-name (tail prefix priority
)
3368 (when (tailwise-equal name tail
)
3369 (record-with-munged-name prefix
3374 ;; machinery for new-style SBCL Lisp-to-C naming
3375 (record-with-translated-name (priority large
)
3376 (record (c-name name
) priority
3378 #!+(and win32 x86-64
) "LLU"
3379 #!-
(and win32 x86-64
) "LU"
3381 (maybe-record-with-translated-name (suffixes priority
&key large
)
3382 (when (some (lambda (suffix)
3383 (tailwise-equal name suffix
))
3385 (record-with-translated-name priority large
))))
3386 (maybe-record-with-translated-name '("-LOWTAG") 0)
3387 (maybe-record-with-translated-name '("-WIDETAG" "-SHIFT") 1)
3388 (maybe-record-with-munged-name "-FLAG" "flag_" 2)
3389 (maybe-record-with-munged-name "-TRAP" "trap_" 3)
3390 (maybe-record-with-munged-name "-SUBTYPE" "subtype_" 4)
3391 (maybe-record-with-munged-name "-SC-NUMBER" "sc_" 5)
3392 (maybe-record-with-translated-name '("-SIZE" "-INTERRUPTS") 6)
3393 (maybe-record-with-translated-name '("-START" "-END" "-PAGE-BYTES"
3394 "-CARD-BYTES" "-GRANULARITY")
3396 (maybe-record-with-translated-name '("-CORE-ENTRY-TYPE-CODE") 8)
3397 (maybe-record-with-translated-name '("-CORE-SPACE-ID") 9)
3398 (maybe-record-with-translated-name '("-CORE-SPACE-ID-FLAG") 9)
3399 (maybe-record-with-translated-name '("-GENERATION+") 10))))))
3400 ;; KLUDGE: these constants are sort of important, but there's no
3401 ;; pleasing way to inform the code above about them. So we fake
3402 ;; it for now. nikodemus on #lisp (2004-08-09) suggested simply
3403 ;; exporting every numeric constant from SB!VM; that would work,
3404 ;; but the C runtime would have to be altered to use Lisp-like names
3405 ;; rather than the munged names currently exported. --njf, 2004-08-09
3406 (dolist (c '(sb!vm
:n-word-bits sb
!vm
:n-word-bytes
3407 sb
!vm
:n-lowtag-bits sb
!vm
:lowtag-mask
3408 sb
!vm
:n-widetag-bits sb
!vm
:widetag-mask
3409 sb
!vm
:n-fixnum-tag-bits sb
!vm
:fixnum-tag-mask
3410 sb
!vm
:short-header-max-words
))
3411 (push (list (c-symbol-name c
)
3412 -
1 ; invent a new priority
3417 ;; One more symbol that doesn't fit into the code above.
3418 (let ((c 'sb
!impl
::+magic-hash-vector-value
+))
3419 (push (list (c-symbol-name c
)
3422 #!+(and win32 x86-64
) "LLU"
3423 #!-
(and win32 x86-64
) "LU"
3428 (lambda (const1 const2
)
3429 (if (= (second const1
) (second const2
))
3430 (if (= (third const1
) (third const2
))
3431 (string< (first const1
) (first const2
))
3432 (< (third const1
) (third const2
)))
3433 (< (second const1
) (second const2
))))))
3434 (let ((prev-priority (second (car constants
))))
3435 (dolist (const constants
)
3436 (destructuring-bind (name priority value suffix doc
) const
3437 (unless (= prev-priority priority
)
3439 (setf prev-priority priority
))
3440 (when (minusp value
)
3441 (error "stub: negative values unsupported"))
3442 (format t
"#define ~A ~A~A /* 0x~X ~@[ -- ~A ~]*/~%" name value suffix value doc
))))
3445 ;; writing information about internal errors
3446 ;; Assembly code needs only the constants for UNDEFINED_[ALIEN_]FUN_ERROR
3447 ;; but to avoid imparting that knowledge here, we'll expose all error
3448 ;; number constants except for OBJECT-NOT-<x>-ERROR ones.
3449 (loop for
(description name
) across sb
!c
:+backend-internal-errors
+
3451 when
(stringp description
)
3452 do
(format t
"#define ~A ~D~%" (c-symbol-name name
) i
))
3453 ;; C code needs strings for describe_internal_error()
3454 (format t
"#define INTERNAL_ERROR_NAMES ~{\\~%~S~^, ~}~2%"
3455 (map 'list
'sb
!kernel
::!c-stringify-internal-error
3456 sb
!c
:+backend-internal-errors
+))
3457 (format t
"#define INTERNAL_ERROR_NARGS {~{~S~^, ~}}~2%"
3458 (map 'list
#'cddr sb
!c
:+backend-internal-errors
+))
3460 ;; I'm not really sure why this is in SB!C, since it seems
3461 ;; conceptually like something that belongs to SB!VM. In any case,
3462 ;; it's needed C-side.
3463 (format t
"#define BACKEND_PAGE_BYTES ~DLU~%" sb
!c
:*backend-page-bytes
*)
3467 ;; FIXME: The SPARC has a PSEUDO-ATOMIC-TRAP that differs between
3468 ;; platforms. If we export this from the SB!VM package, it gets
3469 ;; written out as #define trap_PseudoAtomic, which is confusing as
3470 ;; the runtime treats trap_ as the prefix for illegal instruction
3471 ;; type things. We therefore don't export it, but instead do
3473 (when (boundp 'sb
!vm
::pseudo-atomic-trap
)
3475 "#define PSEUDO_ATOMIC_TRAP ~D /* 0x~:*~X */~%"
3476 sb
!vm
::pseudo-atomic-trap
)
3478 ;; possibly this is another candidate for a rename (to
3479 ;; pseudo-atomic-trap-number or pseudo-atomic-magic-constant
3480 ;; [possibly applicable to other platforms])
3483 (format t
"#define GC_SAFEPOINT_PAGE_ADDR ((void*)0x~XUL) /* ~:*~A */~%"
3484 sb
!vm
:gc-safepoint-page-addr
)
3486 (dolist (symbol '(sb!vm
::float-traps-byte
3487 sb
!vm
::float-exceptions-byte
3488 sb
!vm
::float-sticky-bits
3489 sb
!vm
::float-rounding-mode
))
3490 (format t
"#define ~A_POSITION ~A /* ~:*0x~X */~%"
3491 (c-symbol-name symbol
)
3492 (sb!xc
:byte-position
(symbol-value symbol
)))
3493 (format t
"#define ~A_MASK 0x~X /* ~:*~A */~%"
3494 (c-symbol-name symbol
)
3495 (sb!xc
:mask-field
(symbol-value symbol
) -
1))))
3498 (defun write-tagnames-h (out)
3500 ((pretty-name (symbol strip
)
3501 (let ((name (string-downcase symbol
)))
3502 (substitute #\Space
#\-
3503 (subseq name
0 (- (length name
) (length strip
))))))
3504 (list-sorted-tags (tail)
3505 (loop for symbol being the external-symbols of
"SB!VM"
3506 when
(and (constantp symbol
)
3507 (tailwise-equal (string symbol
) tail
))
3508 collect symbol into tags
3509 finally
(return (sort tags
#'< :key
#'symbol-value
))))
3510 (write-tags (kind limit ash-count
)
3511 (format out
"~%static const char *~(~A~)_names[] = {~%"
3513 (let ((tags (list-sorted-tags kind
)))
3515 (if (eql i
(ash (or (symbol-value (first tags
)) -
1) ash-count
))
3516 (format out
" \"~A\"" (pretty-name (pop tags
) kind
))
3517 (format out
" \"unknown [~D]\"" i
))
3518 (unless (eql i
(1- limit
))
3519 (write-string "," out
))
3521 (write-line "};" out
)))
3522 (write-tags "-LOWTAG" sb
!vm
:lowtag-limit
0)
3523 ;; this -2 shift depends on every OTHER-IMMEDIATE-?-LOWTAG
3524 ;; ending with the same 2 bits. (#b10)
3525 (write-tags "-WIDETAG" (ash (1+ sb
!vm
:widetag-mask
) -
2) -
2))
3526 ;; Inform print_otherptr() of all array types that it's too dumb to print
3527 (let ((array-type-bits (make-array 32 :initial-element
0)))
3529 (multiple-value-bind (ofs bit
) (floor b
8)
3530 (setf (aref array-type-bits ofs
) (ash 1 bit
)))))
3531 (dovector (saetp sb
!vm
:*specialized-array-element-type-properties
*)
3532 (unless (or (typep (sb!vm
:saetp-ctype saetp
) 'character-set-type
)
3533 (eq (sb!vm
:saetp-specifier saetp
) t
))
3534 (toggle (sb!vm
:saetp-typecode saetp
))
3535 (awhen (sb!vm
:saetp-complex-typecode saetp
) (toggle it
)))))
3537 "~%static unsigned char unprintable_array_types[32] =~% {~{~d~^,~}};~%"
3538 (coerce array-type-bits
'list
)))
3541 (defun write-primitive-object (obj *standard-output
*)
3542 ;; writing primitive object layouts
3543 (format t
"#ifndef LANGUAGE_ASSEMBLY~2%")
3544 (format t
"struct ~A {~%" (c-name (string-downcase (sb!vm
:primitive-object-name obj
))))
3545 (when (sb!vm
:primitive-object-widetag obj
)
3546 (format t
" lispobj header;~%"))
3547 (dolist (slot (sb!vm
:primitive-object-slots obj
))
3548 (format t
" ~A ~A~@[[1]~];~%"
3549 (getf (sb!vm
:slot-options slot
) :c-type
"lispobj")
3550 (c-name (string-downcase (sb!vm
:slot-name slot
)))
3551 (sb!vm
:slot-rest-p slot
)))
3553 (format t
"#else /* LANGUAGE_ASSEMBLY */~2%")
3554 (format t
"/* These offsets are SLOT-OFFSET * N-WORD-BYTES - LOWTAG~%")
3555 (format t
" * so they work directly on tagged addresses. */~2%")
3556 (let ((name (sb!vm
:primitive-object-name obj
))
3557 (lowtag (or (symbol-value (sb!vm
:primitive-object-lowtag obj
))
3559 (dolist (slot (sb!vm
:primitive-object-slots obj
))
3560 (format t
"#define ~A_~A_OFFSET ~D~%"
3561 (c-symbol-name name
)
3562 (c-symbol-name (sb!vm
:slot-name slot
))
3563 (- (* (sb!vm
:slot-offset slot
) sb
!vm
:n-word-bytes
) lowtag
)))
3565 (format t
"#endif /* LANGUAGE_ASSEMBLY */~2%"))
3567 (defun write-structure-object (dd *standard-output
*)
3568 (flet ((cstring (designator) (c-name (string-downcase designator
))))
3569 (format t
"#ifndef LANGUAGE_ASSEMBLY~2%")
3570 (format t
"struct ~A {~%" (cstring (dd-name dd
)))
3571 (format t
" lispobj header; // = word_0_~%")
3572 ;; "self layout" slots are named '_layout' instead of 'layout' so that
3573 ;; classoid's expressly declared layout isn't renamed as a special-case.
3574 #!-compact-instance-header
(format t
" lispobj _layout;~%")
3575 ;; Output exactly the number of Lisp words consumed by the structure,
3576 ;; no more, no less. C code can always compute the padded length from
3577 ;; the precise length, but the other way doesn't work.
3579 (coerce (loop for i from sb
!vm
:instance-data-start below
(dd-length dd
)
3580 collect
(list (format nil
"word_~D_" (1+ i
))))
3582 (dolist (slot (dd-slots dd
))
3583 (let ((cell (aref names
(- (dsd-index slot
) sb
!vm
:instance-data-start
)))
3584 (name (cstring (dsd-name slot
))))
3585 (if (eq (dsd-raw-type slot
) t
)
3587 (rplacd cell name
))))
3588 (loop for slot across names
3589 do
(format t
" lispobj ~A;~@[ // ~A~]~%" (car slot
) (cdr slot
))))
3591 (format t
"#endif /* LANGUAGE_ASSEMBLY */~2%")))
3593 (defun write-static-symbols (stream)
3594 (dolist (symbol (cons nil sb
!vm
:*static-symbols
*))
3595 ;; FIXME: It would be nice to use longer names than NIL and
3596 ;; (particularly) T in #define statements.
3597 (format stream
"#define ~A LISPOBJ(0x~X)~%"
3598 ;; FIXME: It would be nice not to need to strip anything
3599 ;; that doesn't get stripped always by C-SYMBOL-NAME.
3600 (c-symbol-name symbol
"%*.!")
3601 (if *static
* ; if we ran GENESIS
3602 ;; We actually ran GENESIS, use the real value.
3603 (descriptor-bits (cold-intern symbol
))
3604 ;; We didn't run GENESIS, so guess at the address.
3605 (+ sb
!vm
:static-space-start
3607 sb
!vm
:other-pointer-lowtag
3608 (if symbol
(sb!vm
:static-symbol-offset symbol
) 0))))))
3610 (defun write-sc-offset-coding (stream)
3611 (flet ((write-array (name bytes
)
3612 (format stream
"static struct sc_offset_byte ~A[] = {~@
3613 ~{ {~{ ~2D, ~2D ~}}~^,~%~}~@
3616 (mapcar (lambda (byte)
3617 (list (byte-size byte
) (byte-position byte
)))
3619 (format stream
"struct sc_offset_byte {
3623 (write-array "sc_offset_sc_number_bytes" sb
!c
::+sc-offset-scn-bytes
+)
3624 (write-array "sc_offset_offset_bytes" sb
!c
::+sc-offset-offset-bytes
+)))
3626 ;;;; writing map file
3628 ;;; Write a map file describing the cold load. Some of this
3629 ;;; information is subject to change due to relocating GC, but even so
3630 ;;; it can be very handy when attempting to troubleshoot the early
3631 ;;; stages of cold load.
3632 (defun write-map (*standard-output
*)
3633 (let ((*print-pretty
* nil
)
3634 (*print-case
* :upcase
))
3635 (format t
"assembler routines defined in core image:~2%")
3636 (dolist (routine (sort (copy-list *cold-assembler-routines
*) #'<
3638 (format t
"~8,'0X: ~S~%" (cdr routine
) (car routine
)))
3642 (maphash (lambda (name fdefn
&aux
(fun (cold-fdefn-fun fdefn
)))
3643 (push (list (- (descriptor-bits fdefn
) (descriptor-lowtag fdefn
))
3647 (push (list (- (descriptor-bits fun
) (descriptor-lowtag fun
))
3649 *cold-fdefn-objects
*)
3650 (format t
"~%~|~%fdefns (native pointer):
3651 ~:{~%~8,'0X: ~S~}~%" (sort fdefns
#'< :key
#'car
))
3652 (format t
"~%~|~%initially defined functions (native pointer):
3653 ~:{~%~8,'0X: ~S~}~%" (sort funs
#'< :key
#'car
))
3656 (a note about initially undefined function references: These functions
3657 are referred to by code which is installed by GENESIS, but they are not
3658 installed by GENESIS. This is not necessarily a problem; functions can
3659 be defined later, by cold init toplevel forms, or in files compiled and
3660 loaded at warm init, or elsewhere. As long as they are defined before
3661 they are called, everything should be OK. Things are also OK if the
3662 cross-compiler knew their inline definition and used that everywhere
3663 that they were called before the out-of-line definition is installed,
3664 as is fairly common for structure accessors.)
3665 initially undefined function references:~2%")
3667 (setf undefs
(sort undefs
#'string
< :key
#'fun-name-block-name
))
3668 (dolist (name undefs
)
3669 (format t
"~8,'0X: ~S~%"
3670 (descriptor-bits (gethash name
*cold-fdefn-objects
*))
3673 (format t
"~%~|~%layout names:~2%")
3674 (dolist (x (sort-cold-layouts))
3675 (let* ((des (cdr x
))
3676 (inherits (read-slot des
*host-layout-of-layout
* :inherits
)))
3677 (format t
"~8,'0X: ~S[~D]~%~10T~:S~%" (descriptor-bits des
) (car x
)
3678 (cold-layout-length des
) (listify-cold-inherits inherits
))))
3680 (format t
"~%~|~%parsed type specifiers:~2%")
3681 (mapc (lambda (cell)
3682 (format t
"~X: ~S~%" (descriptor-bits (cdr cell
)) (car cell
)))
3683 (sort (%hash-table-alist
*ctype-cache
*) #'<
3684 :key
(lambda (x) (descriptor-bits (cdr x
))))))
3687 ;;;; writing core file
3689 (defvar *core-file
*)
3690 (defvar *data-page
*)
3692 ;;; magic numbers to identify entries in a core file
3694 ;;; (In case you were wondering: No, AFAIK there's no special magic about
3695 ;;; these which requires them to be in the 38xx range. They're just
3696 ;;; arbitrary words, tested not for being in a particular range but just
3697 ;;; for equality. However, if you ever need to look at a .core file and
3698 ;;; figure out what's going on, it's slightly convenient that they're
3699 ;;; all in an easily recognizable range, and displacing the range away from
3700 ;;; zero seems likely to reduce the chance that random garbage will be
3701 ;;; misinterpreted as a .core file.)
3702 (defconstant build-id-core-entry-type-code
3860)
3703 (defconstant new-directory-core-entry-type-code
3861)
3704 (defconstant initial-fun-core-entry-type-code
3863)
3705 (defconstant page-table-core-entry-type-code
3880)
3706 (defconstant end-core-entry-type-code
3840)
3708 (declaim (ftype (function (sb!vm
:word
) sb
!vm
:word
) write-word
))
3709 (defun write-word (num)
3710 (ecase sb
!c
:*backend-byte-order
*
3712 (dotimes (i sb
!vm
:n-word-bytes
)
3713 (write-byte (ldb (byte 8 (* i
8)) num
) *core-file
*)))
3715 (dotimes (i sb
!vm
:n-word-bytes
)
3716 (write-byte (ldb (byte 8 (* (- (1- sb
!vm
:n-word-bytes
) i
) 8)) num
)
3720 (defun output-gspace (gspace)
3721 (force-output *core-file
*)
3722 (let* ((posn (file-position *core-file
*))
3723 (bytes (* (gspace-free-word-index gspace
) sb
!vm
:n-word-bytes
))
3724 (pages (ceiling bytes sb
!c
:*backend-page-bytes
*))
3725 (total-bytes (* pages sb
!c
:*backend-page-bytes
*)))
3727 (file-position *core-file
*
3728 (* sb
!c
:*backend-page-bytes
* (1+ *data-page
*)))
3730 "writing ~S byte~:P [~S page~:P] from ~S~%"
3736 ;; Note: It is assumed that the GSPACE allocation routines always
3737 ;; allocate whole pages (of size *target-page-size*) and that any
3738 ;; empty gspace between the free pointer and the end of page will
3739 ;; be zero-filled. This will always be true under Mach on machines
3740 ;; where the page size is equal. (RT is 4K, PMAX is 4K, Sun 3 is
3742 (write-bigvec-as-sequence (gspace-bytes gspace
)
3746 (force-output *core-file
*)
3747 (file-position *core-file
* posn
)
3749 ;; Write part of a (new) directory entry which looks like this:
3750 ;; GSPACE IDENTIFIER
3755 (write-word (gspace-identifier gspace
))
3756 (write-word (gspace-free-word-index gspace
))
3757 (write-word *data-page
*)
3758 (multiple-value-bind (floor rem
)
3759 (floor (gspace-byte-address gspace
) sb
!c
:*backend-page-bytes
*)
3764 (incf *data-page
* pages
)))
3766 ;;; Create a core file created from the cold loaded image. (This is
3767 ;;; the "initial core file" because core files could be created later
3768 ;;; by executing SAVE-LISP in a running system, perhaps after we've
3769 ;;; added some functionality to the system.)
3770 (declaim (ftype (function (string)) write-initial-core-file
))
3771 (defun write-initial-core-file (filename)
3773 (let ((filenamestring (namestring filename
))
3776 (format t
"[building initial core file in ~S: ~%" filenamestring
)
3779 (with-open-file (*core-file
* filenamestring
3781 :element-type
'(unsigned-byte 8)
3782 :if-exists
:rename-and-delete
)
3784 ;; Write the magic number.
3785 (write-word core-magic
)
3787 ;; Write the build ID.
3788 (write-word build-id-core-entry-type-code
)
3789 (let ((build-id (with-open-file (s "output/build-id.tmp")
3791 (declare (type simple-string build-id
))
3792 (/show build-id
(length build-id
))
3793 ;; Write length of build ID record: BUILD-ID-CORE-ENTRY-TYPE-CODE
3794 ;; word, this length word, and one word for each char of BUILD-ID.
3795 (write-word (+ 2 (length build-id
)))
3796 (dovector (char build-id
)
3797 ;; (We write each character as a word in order to avoid
3798 ;; having to think about word alignment issues in the
3799 ;; sbcl-0.7.8 version of coreparse.c.)
3800 (write-word (sb!xc
:char-code char
))))
3802 ;; Write the New Directory entry header.
3803 (write-word new-directory-core-entry-type-code
)
3804 (let ((spaces (nconc (list *read-only
* *static
*)
3806 (list *immobile-fixedobj
* *immobile-varyobj
*)
3808 ;; length = (5 words/space) * N spaces + 2 for header.
3809 (write-word (+ (* (length spaces
) 5) 2))
3810 (mapc #'output-gspace spaces
))
3812 ;; Write the initial function.
3813 (write-word initial-fun-core-entry-type-code
)
3815 (let* ((cold-name (cold-intern '!cold-init
))
3817 (cold-fdefn-fun (cold-fdefinition-object cold-name
))))
3819 "~&/(DESCRIPTOR-BITS INITIAL-FUN)=#X~X~%"
3820 (descriptor-bits initial-fun
))
3821 (write-word (descriptor-bits initial-fun
)))
3823 ;; Write the End entry.
3824 (write-word end-core-entry-type-code
)
3827 (format t
"done]~%")
3829 (/show
"leaving WRITE-INITIAL-CORE-FILE")
3832 ;;;; the actual GENESIS function
3834 ;;; Read the FASL files in OBJECT-FILE-NAMES and produce a Lisp core,
3835 ;;; and/or information about a Lisp core, therefrom.
3837 ;;; input file arguments:
3838 ;;; SYMBOL-TABLE-FILE-NAME names a UNIX-style .nm file *with* *any*
3839 ;;; *tab* *characters* *converted* *to* *spaces*. (We push
3840 ;;; responsibility for removing tabs out to the caller it's
3841 ;;; trivial to remove them using UNIX command line tools like
3842 ;;; sed, whereas it's a headache to do it portably in Lisp because
3843 ;;; #\TAB is not a STANDARD-CHAR.) If this file is not supplied,
3844 ;;; a core file cannot be built (but a C header file can be).
3846 ;;; output files arguments (any of which may be NIL to suppress output):
3847 ;;; CORE-FILE-NAME gets a Lisp core.
3848 ;;; C-HEADER-DIR-NAME gets the path in which to place generated headers
3849 ;;; MAP-FILE-NAME gets the name of the textual 'cold-sbcl.map' file
3850 (defun sb-cold:genesis
(&key object-file-names preload-file
3851 core-file-name c-header-dir-name map-file-name
3852 symbol-table-file-name
)
3854 (declare (ignorable symbol-table-file-name
))
3855 (declare (special core-file-name
))
3858 "~&beginning GENESIS, ~A~%"
3860 ;; Note: This output summarizing what we're doing is
3861 ;; somewhat telegraphic in style, not meant to imply that
3862 ;; we're not e.g. also creating a header file when we
3864 (format nil
"creating core ~S" core-file-name
)
3865 (format nil
"creating headers in ~S" c-header-dir-name
)))
3867 (let ((*cold-foreign-symbol-table
* (make-hash-table :test
'equal
)))
3870 (when core-file-name
3871 (if symbol-table-file-name
3872 (load-cold-foreign-symbol-table symbol-table-file-name
)
3873 (error "can't output a core file without symbol table file input")))
3875 ;; Now that we've successfully read our only input file (by
3876 ;; loading the symbol table, if any), it's a good time to ensure
3877 ;; that there'll be someplace for our output files to go when
3879 (flet ((frob (filename)
3881 (ensure-directories-exist filename
:verbose t
))))
3882 (frob core-file-name
)
3883 (frob map-file-name
))
3885 ;; (This shouldn't matter in normal use, since GENESIS normally
3886 ;; only runs once in any given Lisp image, but it could reduce
3887 ;; confusion if we ever experiment with running, tweaking, and
3888 ;; rerunning genesis interactively.)
3889 (do-all-symbols (sym)
3890 (remprop sym
'cold-intern-info
))
3894 (let* ((*foreign-symbol-placeholder-value
* (if core-file-name nil
0))
3895 (*load-time-value-counter
* 0)
3896 (*cold-fdefn-objects
* (make-hash-table :test
'equal
))
3897 (*cold-symbols
* (make-hash-table :test
'eql
)) ; integer keys
3898 (*cold-package-symbols
* (make-hash-table :test
'equal
)) ; string keys
3899 (*read-only
* (make-gspace :read-only
3900 read-only-core-space-id
3901 sb
!vm
:read-only-space-start
))
3902 (*static
* (make-gspace :static
3903 static-core-space-id
3904 sb
!vm
:static-space-start
))
3906 (*immobile-fixedobj
* (make-gspace :immobile-fixedobj
3907 immobile-fixedobj-core-space-id
3908 sb
!vm
:immobile-space-start
))
3910 (*immobile-varyobj
* (make-gspace :immobile-varyobj
3911 immobile-varyobj-core-space-id
3912 (+ sb
!vm
:immobile-space-start
3913 sb
!vm
:immobile-fixedobj-subspace-size
)))
3914 (*dynamic
* (make-gspace :dynamic
3915 dynamic-core-space-id
3916 #!+gencgc sb
!vm
:dynamic-space-start
3917 #!-gencgc sb
!vm
:dynamic-0-space-start
))
3918 (*nil-descriptor
* (make-nil-descriptor))
3919 (*known-structure-classoids
* nil
)
3920 (*classoid-cells
* (make-hash-table :test
'eq
))
3921 (*ctype-cache
* (make-hash-table :test
'equal
))
3922 (*cold-layouts
* (make-hash-table :test
'eq
)) ; symbol -> cold-layout
3923 (*cold-layout-names
* (make-hash-table :test
'eql
)) ; addr -> symbol
3924 (*!cold-defconstants
* nil
)
3925 (*!cold-defuns
* nil
)
3926 ;; '*COLD-METHODS* is never seen in the target, so does not need
3927 ;; to adhere to the #\! convention for automatic uninterning.
3928 (*cold-methods
* nil
)
3929 (*!cold-toplevels
* nil
)
3930 (*current-debug-sources
* *nil-descriptor
*)
3931 *cold-static-call-fixups
*
3932 *cold-assembler-fixups
*
3933 *cold-assembler-routines
*
3934 (*deferred-known-fun-refs
* nil
)
3935 #!+x86
(*load-time-code-fixups
* (make-hash-table)))
3937 ;; If we're given a preload file, it contains tramps and whatnot
3938 ;; that must be loaded before we create any FDEFNs. It can in
3939 ;; theory be loaded any time between binding
3940 ;; *COLD-ASSEMBLER-ROUTINES* above and calling
3941 ;; INITIALIZE-STATIC-FNS below.
3943 (cold-load preload-file
))
3945 ;; Prepare for cold load.
3946 (initialize-layouts)
3947 (initialize-packages)
3948 (initialize-static-symbols)
3949 (initialize-static-fns)
3951 ;; Initialize the *COLD-SYMBOLS* system with the information
3952 ;; from common-lisp-exports.lisp-expr.
3953 ;; Packages whose names match SB!THING were set up on the host according
3954 ;; to "package-data-list.lisp-expr" which expresses the desired target
3955 ;; package configuration, so we can just mirror the host into the target.
3956 ;; But by waiting to observe calls to COLD-INTERN that occur during the
3957 ;; loading of the cross-compiler's outputs, it is possible to rid the
3958 ;; target of accidental leftover symbols, not that it wouldn't also be
3959 ;; a good idea to clean up package-data-list once in a while.
3960 (dolist (exported-name
3961 (sb-cold:read-from-file
"common-lisp-exports.lisp-expr"))
3962 (cold-intern (intern exported-name
*cl-package
*) :access
:external
))
3964 ;; Create SB!KERNEL::*TYPE-CLASSES* as an array of NIL
3965 (cold-set (cold-intern 'sb
!kernel
::*type-classes
*)
3966 (vector-in-core (make-list (length sb
!kernel
::*type-classes
*))))
3969 (dolist (file-name object-file-names
)
3970 (cold-load file-name
))
3972 (when *known-structure-classoids
*
3973 (let ((dd-layout (find-layout 'defstruct-description
)))
3974 (dolist (defstruct-args *known-structure-classoids
*)
3975 (let* ((dd (first defstruct-args
))
3976 (name (warm-symbol (read-slot dd dd-layout
:name
)))
3977 (layout (gethash name
*cold-layouts
*)))
3979 (write-slots layout
*host-layout-of-layout
* :info dd
))))
3980 (format t
"~&; SB!Loader: (~D~@{+~D~}) structs/consts/funs/methods/other~%"
3981 (length *known-structure-classoids
*)
3982 (length *!cold-defconstants
*)
3983 (length *!cold-defuns
*)
3984 (reduce #'+ *cold-methods
* :key
(lambda (x) (length (cdr x
))))
3985 (length *!cold-toplevels
*)))
3987 (dolist (symbol '(*!cold-defconstants
* *!cold-defuns
* *!cold-toplevels
*))
3988 (cold-set symbol
(list-to-core (nreverse (symbol-value symbol
))))
3989 (makunbound symbol
)) ; so no further PUSHes can be done
3992 'sb
!pcl
::*!trivial-methods
*
3994 (loop for
(gf-name . methods
) in
*cold-methods
*
3997 (cold-intern gf-name
)
3999 (loop for
(class qual lambda-list fun source-loc
)
4000 ;; Methods must be sorted because we invoke
4001 ;; only the first applicable one.
4002 in
(stable-sort methods
#'> ; highest depthoid first
4003 :key
(lambda (method)
4004 (class-depthoid (car method
))))
4006 (cold-list (cold-intern
4007 (and (null qual
) (predicate-for-specializer class
)))
4011 lambda-list source-loc
)))))))
4013 ;; Tidy up loose ends left by cold loading. ("Postpare from cold load?")
4014 (resolve-deferred-known-funs)
4015 (resolve-assembler-fixups)
4016 #!+x86
(output-load-time-code-fixups)
4017 (foreign-symbols-to-core)
4019 (/show
"back from FINISH-SYMBOLS")
4020 (finalize-load-time-value-noise)
4022 ;; Tell the target Lisp how much stuff we've allocated.
4023 ;; ALLOCATE-COLD-DESCRIPTOR is a weird trick to locate a space's end,
4024 ;; and it doesn't work on immobile space.
4025 (cold-set 'sb
!vm
:*read-only-space-free-pointer
*
4026 (allocate-cold-descriptor *read-only
*
4028 sb
!vm
:even-fixnum-lowtag
))
4029 (cold-set 'sb
!vm
:*static-space-free-pointer
*
4030 (allocate-cold-descriptor *static
*
4032 sb
!vm
:even-fixnum-lowtag
))
4035 (cold-set 'sb
!vm
:*immobile-fixedobj-free-pointer
*
4036 (make-random-descriptor
4037 (ash (+ (gspace-word-address *immobile-fixedobj
*)
4038 (gspace-free-word-index *immobile-fixedobj
*))
4040 ;; The upper bound of the varyobj subspace is delimited by
4041 ;; a structure with no layout and no slots.
4042 ;; This is necessary because 'coreparse' does not have the actual
4043 ;; value of the free pointer, but the space must not contain any
4044 ;; objects that look like conses (due to the tail of 0 words).
4045 (let ((des (allocate-object *immobile-varyobj
* 1 ; 1 word in total
4046 sb
!vm
:instance-pointer-lowtag nil
)))
4047 (write-wordindexed/raw des
0 sb
!vm
:instance-header-widetag
)
4048 (write-wordindexed/raw des sb
!vm
:instance-slots-offset
0))
4049 (cold-set 'sb
!vm
:*immobile-space-free-pointer
*
4050 (make-random-descriptor
4051 (ash (+ (gspace-word-address *immobile-varyobj
*)
4052 (gspace-free-word-index *immobile-varyobj
*))
4053 sb
!vm
:word-shift
))))
4055 (/show
"done setting free pointers")
4057 ;; Write results to files.
4059 (with-open-file (stream map-file-name
:direction
:output
:if-exists
:supersede
)
4060 (write-map stream
)))
4061 (let ((filename (format nil
"~A/Makefile.features" c-header-dir-name
)))
4062 (ensure-directories-exist filename
)
4063 (with-open-file (stream filename
:direction
:output
:if-exists
:supersede
)
4064 (write-makefile-features stream
)))
4065 (macrolet ((out-to (name &body body
) ; write boilerplate and inclusion guard
4066 `(with-open-file (stream (format nil
"~A/~A.h" c-header-dir-name
,name
)
4067 :direction
:output
:if-exists
:supersede
)
4068 (write-boilerplate stream
)
4070 "#ifndef SBCL_GENESIS_~A~%#define SBCL_GENESIS_~:*~A~%"
4071 (c-name (string-upcase ,name
)))
4073 (format stream
"#endif~%"))))
4074 (out-to "config" (write-config-h stream
))
4075 (out-to "constants" (write-constants-h stream
))
4077 (out-to "tagnames" (write-tagnames-h stream
))
4078 (let ((structs (sort (copy-list sb
!vm
:*primitive-objects
*) #'string
<
4079 :key
#'sb
!vm
:primitive-object-name
)))
4080 (dolist (obj structs
)
4081 (out-to (string-downcase (sb!vm
:primitive-object-name obj
))
4082 (write-primitive-object obj stream
)))
4083 (out-to "primitive-objects"
4084 (dolist (obj structs
)
4085 (format stream
"~&#include \"~A.h\"~%"
4086 (string-downcase (sb!vm
:primitive-object-name obj
))))))
4087 (dolist (class '(classoid hash-table layout package
4088 sb
!c
::compiled-debug-info sb
!c
::compiled-debug-fun
))
4089 (out-to (string-downcase class
)
4090 (write-structure-object (layout-info (find-layout class
)) stream
)))
4091 (out-to "static-symbols" (write-static-symbols stream
))
4092 (out-to "sc-offset" (write-sc-offset-coding stream
)))
4094 (when core-file-name
4095 (write-initial-core-file core-file-name
)))))
4097 ;;; Invert the action of HOST-CONSTANT-TO-CORE. If STRICTP is given as NIL,
4098 ;;; then we can produce a host object even if it is not a faithful rendition.
4099 (defun host-object-from-core (descriptor &optional
(strictp t
))
4100 (named-let recurse
((x descriptor
))
4102 (return-from recurse nil
))
4103 (when (eq (descriptor-gspace x
) :load-time-value
)
4104 (error "Can't warm a deferred LTV placeholder"))
4105 (when (is-fixnum-lowtag (descriptor-lowtag x
))
4106 (return-from recurse
(descriptor-fixnum x
)))
4107 (ecase (descriptor-lowtag x
)
4108 (#.sb
!vm
:instance-pointer-lowtag
4109 (if strictp
(error "Can't invert INSTANCE type") "#<instance>"))
4110 (#.sb
!vm
:list-pointer-lowtag
4111 (cons (recurse (cold-car x
)) (recurse (cold-cdr x
))))
4112 (#.sb
!vm
:fun-pointer-lowtag
4114 (error "Can't map cold-fun -> warm-fun")
4115 (let ((name (read-wordindexed x sb
!vm
:simple-fun-name-slot
)))
4116 `(function ,(recurse name
)))))
4117 (#.sb
!vm
:other-pointer-lowtag
4118 (let ((widetag (logand (descriptor-bits (read-memory x
))
4119 sb
!vm
:widetag-mask
)))
4121 (#.sb
!vm
:symbol-header-widetag
4124 (or (gethash (descriptor-bits x
) *cold-symbols
*) ; first try
4126 (recurse (read-wordindexed x sb
!vm
:symbol-name-slot
))))))
4127 (#.sb
!vm
:simple-base-string-widetag
(base-string-from-core x
))
4128 (#.sb
!vm
:simple-vector-widetag
(vector-from-core x
#'recurse
))
4129 (#.sb
!vm
:bignum-widetag
(bignum-from-core x
))))))))