1 ;;;; parts of the loader which make sense in the cross-compilation
2 ;;;; host (and which are useful in the host, because they're used by
5 ;;;; based on the CMU CL load.lisp code, written by Skef Wholey and
8 ;;;; This software is part of the SBCL system. See the README file for
11 ;;;; This software is derived from the CMU CL system, which was
12 ;;;; written at Carnegie Mellon University and released into the
13 ;;;; public domain. The software is in the public domain and is
14 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
15 ;;;; files for more information.
17 (in-package "SB!FASL")
19 ;;;; miscellaneous load utilities
21 ;;; Output the current number of semicolons after a fresh-line.
22 ;;; FIXME: non-mnemonic name
23 (defun load-fresh-line ()
25 (let ((semicolons ";;;;;;;;;;;;;;;;"))
26 (do ((count *load-depth
* (- count
(length semicolons
))))
27 ((< count
(length semicolons
))
28 (write-string semicolons
*standard-output
* :end count
))
29 (declare (fixnum count
))
30 (write-string semicolons
))
31 (write-char #\space
)))
33 ;;; If VERBOSE, output (to *STANDARD-OUTPUT*) a message about how
34 ;;; we're loading from STREAM-WE-ARE-LOADING-FROM.
35 (defun maybe-announce-load (stream-we-are-loading-from verbose
)
38 (let ((name #-sb-xc-host
(file-name stream-we-are-loading-from
)
41 (format t
"loading ~S~%" name
)
42 (format t
"loading stuff from ~S~%" stream-we-are-loading-from
)))))
44 ;;;; utilities for reading from fasl files
46 #!-sb-fluid
(declaim (inline read-byte
))
48 ;;; This expands into code to read an N-byte unsigned integer using
50 (defmacro fast-read-u-integer
(n)
52 `(let ,(loop for i from
0 below n
53 collect
(let ((name (gensym "B")))
55 `(,name
,(if (zerop i
)
57 `(ash (fast-read-byte) ,(* i
8))))))
60 ;;; like FAST-READ-U-INTEGER, but the size may be determined at run time
61 (defmacro fast-read-var-u-integer
(n)
62 (let ((n-pos (gensym))
65 `(do ((,n-pos
8 (+ ,n-pos
8))
66 (,n-cnt
(1- ,n
) (1- ,n-cnt
))
69 (dpb (fast-read-byte) (byte 8 ,n-pos
) ,n-res
)))
70 ((zerop ,n-cnt
) ,n-res
)
71 (declare (type index
,n-pos
,n-cnt
)))))
73 ;;; FIXME: why do all of these reading functions and macros declare
74 ;;; (SPEED 0)? was there some bug in the compiler which has since
75 ;;; been fixed? --njf, 2004-09-08
76 ;;; Afaict, the (SPEED 0) declarations in here avoid code bloat,
77 ;;; by counteracting the INLINE declaration on the local definition
78 ;;; of FAST-READ-BYTE. At least, that is the effect, and it seems
79 ;;; reasonable. Pretty much the INLINE declaration is probably
80 ;;; the thing that deserves to go away.
82 ;;; Read a signed integer.
83 (defmacro fast-read-s-integer
(n)
84 (declare (optimize (speed 0)))
85 (let ((n-last (gensym)))
86 (do ((res `(let ((,n-last
(fast-read-byte)))
87 (if (zerop (logand ,n-last
#x80
))
89 (logior ,n-last
#x-100
)))
90 `(logior (fast-read-byte)
91 (ash (the (signed-byte ,(* cnt
8)) ,res
) 8)))
95 ;;; Read an N-byte unsigned integer from FASL-INPUT-STREAM.
96 (defmacro read-arg
(n fasl-input-stream
)
98 `(the (unsigned-byte 8) (read-byte ,fasl-input-stream
))
99 `(with-fast-read-byte ((unsigned-byte 8) ,fasl-input-stream
)
100 (fast-read-u-integer ,n
))))
102 (defun read-varint-arg (fasl-input)
103 (let ((accumulator 0)
105 (declare (fixnum shift
) (type word accumulator
))
106 (with-fast-read-byte ((unsigned-byte 8) (%fasl-input-stream fasl-input
))
108 (let ((octet (fast-read-byte)))
109 (setq accumulator
(logior accumulator
(ash (logand octet
#x7F
) shift
)))
111 (unless (logbitp 7 octet
) (return accumulator
)))))))
113 ;; FIXME: on x86-64, these functions exceed 600, 900, and 1200 bytes of code
114 ;; respectively. Either don't inline them, or make a "really" fast inline case
115 ;; that punts if inapplicable. e.g. if the fast-read-byte buffer will not be
116 ;; refilled, then SAP-REF-WORD could work to read 8 bytes.
117 ;; But this would only be feasible on machines that are little-endian
118 ;; and that allow unaligned reads. (like x86)
119 (declaim (inline read-byte-arg read-word-arg
))
120 (defun read-byte-arg (stream)
121 (declare (optimize (speed 0)))
124 (defun read-word-arg (stream)
125 (declare (optimize (speed 0)))
126 (read-arg #.sb
!vm
:n-word-bytes stream
))
128 (defun read-unsigned-byte-32-arg (stream)
129 (declare (optimize (speed 0)))
135 ;;; The table is implemented as a simple-vector indexed by the table
136 ;;; offset. The offset is kept in at index 0 of the vector.
138 ;;; FOPs use the table to save stuff, other FOPs refer to the table by
139 ;;; direct indexes via REF-FOP-TABLE.
141 (declaim (inline ref-fop-table
))
142 (defun ref-fop-table (fasl-input index
)
143 (svref (%fasl-input-table fasl-input
) (1+ (the index index
))))
145 (defun push-fop-table (thing fasl-input
) ; and return THING
146 (let* ((table (%fasl-input-table fasl-input
))
147 (index (+ (the index
(aref table
0)) 1)))
148 (declare (fixnum index
)
149 (simple-vector table
))
150 (when (eql index
(length table
))
151 (setf table
(grow-fop-vector table index
)
152 (%fasl-input-table fasl-input
) table
))
153 (setf (aref table
0) index
154 (aref table index
) thing
)))
156 ;;; These two routines are used for both the stack and the table.
157 (defun grow-fop-vector (old-vector old-size
)
158 (declare (simple-vector old-vector
)
159 (type index old-size
))
160 (let* ((new-size (* old-size
2))
161 (new-vector (make-array new-size
)))
162 (declare (fixnum new-size
)
163 (simple-vector new-vector old-vector
))
164 (replace new-vector old-vector
)
165 (nuke-fop-vector old-vector
)
168 (defun nuke-fop-vector (vector)
169 (declare (simple-vector vector
)
170 #!-gencgc
(ignore vector
)
172 ;; Make sure we don't keep any garbage.
179 (declaim (inline fop-stack-empty-p
))
180 (defun fop-stack-empty-p (stack)
181 (eql 0 (svref stack
0)))
183 ;; Ensure that N arguments can be popped from the FOP stack.
184 ;; Return the stack and the pointer to the first argument.
185 ;; Update the new top-of-stack to reflect that all N have been popped.
186 (defun fop-stack-pop-n (stack n
)
187 (declare (type index n
))
188 (let* ((top (the index
(svref stack
0)))
190 (if (minusp new-top
) ; 0 is ok at this point
191 (error "FOP stack underflow")
192 (progn (setf (svref stack
0) new-top
)
195 (defun push-fop-stack (value fasl-input
)
196 (let* ((stack (%fasl-input-stack fasl-input
))
197 (next (1+ (the index
(svref stack
0)))))
198 (declare (type index next
))
199 (when (eql (length stack
) next
)
200 (setf stack
(grow-fop-vector stack next
)
201 (%fasl-input-stack fasl-input
) stack
))
202 (setf (svref stack
0) next
203 (svref stack next
) value
)))
206 ;;;; Conditions signalled on invalid fasls (wrong fasl version, etc),
207 ;;;; so that user code (esp. ASDF) can reasonably handle attempts to
208 ;;;; load such fasls by recompiling them, etc. For simplicity's sake
209 ;;;; make only condition INVALID-FASL part of the public interface,
210 ;;;; and keep the guts internal.
212 (define-condition invalid-fasl
(error)
213 ((stream :reader invalid-fasl-stream
:initarg
:stream
)
214 (expected :reader invalid-fasl-expected
:initarg
:expected
))
216 (lambda (condition stream
)
217 (format stream
"~S is an invalid fasl file."
218 (invalid-fasl-stream condition
)))))
220 (define-condition invalid-fasl-header
(invalid-fasl)
221 ((byte :reader invalid-fasl-byte
:initarg
:byte
)
222 (byte-nr :reader invalid-fasl-byte-nr
:initarg
:byte-nr
))
224 (lambda (condition stream
)
225 (format stream
"~@<~S contains an illegal byte in the FASL header at ~
226 position ~A: Expected ~A, got ~A.~:@>"
227 (invalid-fasl-stream condition
)
228 (invalid-fasl-byte-nr condition
)
229 (invalid-fasl-expected condition
)
230 (invalid-fasl-byte condition
)))))
232 (define-condition invalid-fasl-version
(invalid-fasl)
233 ((version :reader invalid-fasl-version
:initarg
:version
))
235 (lambda (condition stream
)
236 (format stream
"~@<~S is a fasl file compiled with SBCL ~W, and ~
237 can't be loaded into SBCL ~W.~:@>"
238 (invalid-fasl-stream condition
)
239 (invalid-fasl-version condition
)
240 (invalid-fasl-expected condition
)))))
242 (define-condition invalid-fasl-implementation
(invalid-fasl)
243 ((implementation :reader invalid-fasl-implementation
244 :initarg
:implementation
))
246 (lambda (condition stream
)
247 (format stream
"~S was compiled for implementation ~A, but this is a ~A."
248 (invalid-fasl-stream condition
)
249 (invalid-fasl-implementation condition
)
250 (invalid-fasl-expected condition
)))))
252 (define-condition invalid-fasl-features
(invalid-fasl)
253 ((potential-features :reader invalid-fasl-potential-features
254 :initarg
:potential-features
)
255 (features :reader invalid-fasl-features
:initarg
:features
))
257 (lambda (condition stream
)
258 (format stream
"~@<incompatible ~S in fasl file ~S: ~2I~_~
259 Of features affecting binary compatibility, ~4I~_~S~2I~_~
260 the fasl has ~4I~_~A,~2I~_~
261 while the runtime expects ~4I~_~A.~:>"
263 (invalid-fasl-stream condition
)
264 (invalid-fasl-potential-features condition
)
265 (invalid-fasl-features condition
)
266 (invalid-fasl-expected condition
)))))
268 ;;; Skips past the shebang line on stream, if any.
269 (defun maybe-skip-shebang-line (stream)
270 (let ((p (file-position stream
)))
271 (flet ((next () (read-byte stream nil
)))
273 (when (and (eq (next) (char-code #\
#))
274 (eq (next) (char-code #\
!)))
277 until
(or (not x
) (eq x
(char-code #\newline
)))))
279 (file-position stream p
))))
282 ;;; Returns T if the stream is a binary input stream with a FASL header.
283 #-sb-xc-host
;; FIXME: function belongs in 'target-load'
284 (defun fasl-header-p (stream &key errorp
)
285 (unless (and (member (stream-element-type stream
) '(character base-char
))
286 ;; give up if it's not a file stream, or it's an
287 ;; fd-stream but it's either not bivalent or not
288 ;; seekable (doesn't really have a file)
289 (or (not (typep stream
'file-stream
))
290 (and (typep stream
'fd-stream
)
291 (or (not (sb!impl
::fd-stream-bivalent-p stream
))
292 (not (sb!impl
::fd-stream-file stream
))))))
293 (let ((p (file-position stream
)))
295 (let* ((header *fasl-header-string-start-string
*)
296 (buffer (make-array (length header
) :element-type
'(unsigned-byte 8)))
299 (maybe-skip-shebang-line stream
)
300 (setf n
(read-sequence buffer stream
))))
303 (or (ignore-errors (scan))
304 ;; no a binary input stream
305 (return-from fasl-header-p nil
))))
306 (if (mismatch buffer header
307 :test
#'(lambda (code char
) (= code
(char-code char
))))
308 ;; Immediate EOF is valid -- we want to match what
309 ;; CHECK-FASL-HEADER does...
312 (error 'fasl-header-missing
317 (file-position stream p
)))))
322 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
323 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
324 ;;;; it's needed not only in the target Lisp, but also in the
325 ;;;; cross-compilation host.
327 ;;; a helper function for LOAD-FASL-GROUP
329 ;;; Return true if we successfully read a FASL header from the stream, or NIL
330 ;;; if EOF was hit before anything except the optional shebang line was read.
331 ;;; Signal an error if we encounter garbage.
332 (defun check-fasl-header (stream)
333 (maybe-skip-shebang-line stream
)
334 (let ((byte (read-byte stream nil
)))
336 ;; Read and validate constant string prefix in fasl header.
337 (let* ((fhsss *fasl-header-string-start-string
*)
338 (fhsss-length (length fhsss
)))
339 (unless (= byte
(char-code (schar fhsss
0)))
340 (error 'invalid-fasl-header
344 :expected
(char-code (schar fhsss
0))))
345 (do ((byte (read-byte stream
) (read-byte stream
))
346 (count 1 (1+ count
)))
347 ((= byte
+fasl-header-string-stop-char-code
+)
349 (declare (fixnum byte count
))
350 (when (and (< count fhsss-length
)
351 (not (eql byte
(char-code (schar fhsss count
)))))
352 (error 'invalid-fasl-header
356 :expected
(char-code (schar fhsss count
))))))
357 ;; Read and validate version-specific compatibility stuff.
358 (flet ((string-from-stream ()
359 (let* ((length (read-unsigned-byte-32-arg stream
))
360 (result (make-string length
)))
361 (read-string-as-bytes stream result
)
363 ;; Read and validate implementation and version.
364 (let ((implementation (keywordicate (string-from-stream)))
365 (expected-implementation +backend-fasl-file-implementation
+))
366 (unless (string= expected-implementation implementation
)
367 (error 'invalid-fasl-implementation
369 :implementation implementation
370 :expected expected-implementation
)))
371 (let* ((fasl-version (read-word-arg stream
))
372 (sbcl-version (if (<= fasl-version
76)
374 (string-from-stream)))
375 (expected-version (sb!xc
:lisp-implementation-version
)))
376 (unless (string= expected-version sbcl-version
)
378 (error 'invalid-fasl-version
380 :version sbcl-version
381 :expected expected-version
)
382 (continue () :report
"Load the fasl file anyway"))))
383 ;; Read and validate *FEATURES* which affect binary compatibility.
384 (let ((faff-in-this-file (string-from-stream)))
385 (unless (string= faff-in-this-file
*features-affecting-fasl-format
*)
386 (error 'invalid-fasl-features
388 :potential-features
*features-potentially-affecting-fasl-format
*
389 :expected
*features-affecting-fasl-format
*
390 :features faff-in-this-file
)))
394 ;; Setting this variable gives you a trace of fops as they are loaded and
397 (defvar *show-fops-p
* nil
)
398 (defvar *fasl-source-info
*)
400 ;;; a helper function for LOAD-AS-FASL
402 ;;; Return true if we successfully load a group from the stream, or
403 ;;; NIL if EOF was encountered while trying to read from the stream.
404 ;;; Dispatch to the right function for each fop.
405 (defun load-fasl-group (fasl-input print
)
407 ;; PRINT causes most tlf-equivalent forms to print their primary value.
408 ;; This differs from loading of Lisp source, which prints all values of
409 ;; only truly-toplevel forms. This is permissible per CLHS -
410 ;; "If print is true, load incrementally prints information to standard
411 ;; output showing the progress of the loading process. [...]
412 ;; For a compiled file, what is printed might not reflect precisely the
413 ;; contents of the source file, but some information is generally printed."
415 (declare (ignorable print
))
416 (let ((stream (%fasl-input-stream fasl-input
))
418 #!+sb-show
(trace *show-fops-p
*))
419 (unless (check-fasl-header stream
)
420 (return-from load-fasl-group
))
421 (catch 'fasl-group-end
422 (setf (svref (%fasl-input-table fasl-input
) 0) 0)
423 (macrolet ((tracing (&body forms
)
424 #!+sb-show
`(when trace
,@forms
)
425 #!-sb-show
(progn forms nil
)))
427 (let* ((byte (the (unsigned-byte 8) (read-byte stream
)))
428 (function (svref **fop-funs
** byte
))
429 (n-operands (aref (car **fop-signatures
**) byte
)))
430 ;; Do some debugging output.
432 (format *trace-output
* "~&~6x : [~D,~D] ~2,'0x(~A)"
433 (1- (file-position stream
))
434 (svref (%fasl-input-stack fasl-input
) 0) ; stack pointer
435 (svref (%fasl-input-table fasl-input
) 0) ; table pointer
436 byte
(and (functionp function
)
437 (nth-value 2 (function-lambda-expression function
)))))
438 ;; Actually execute the fop.
440 (cond ((not (functionp function
))
441 (error "corrupt fasl file: FOP code #x~x" byte
))
443 (funcall function fasl-input
))
445 (let (arg1 arg2 arg3
)
446 (with-fast-read-byte ((unsigned-byte 8) stream
)
447 ;; The low 2 bits of the opcode determine the
448 ;; number of octets used for the 1st operand.
449 (setq arg1
(fast-read-var-u-integer (ash 1 (logand byte
3)))))
450 (when (>= n-operands
2)
451 (setq arg2
(read-varint-arg fasl-input
))
452 (when (>= n-operands
3)
453 (setq arg3
(read-varint-arg fasl-input
))))
454 (tracing (format *trace-output
* "{~D~@[,~D~@[,~D~]~]}"
457 (3 (funcall function fasl-input arg1 arg2 arg3
))
458 (2 (funcall function fasl-input arg1 arg2
))
459 (1 (funcall function fasl-input arg1
))))))))
460 (when (plusp (sbit (cdr **fop-signatures
**) byte
))
461 (push-fop-stack result fasl-input
))
462 (let ((stack (%fasl-input-stack fasl-input
)))
463 (declare (ignorable stack
)) ; not used in xc-host
465 (let ((ptr (svref stack
0)))
466 (format *trace-output
* " -- ~[<empty>,~D~:;[~:*~D,~D] ~S~]"
467 ptr
(svref (%fasl-input-table fasl-input
) 0)
468 (unless (eql ptr
0) (aref stack ptr
)))
469 (terpri *trace-output
*)))
471 (macrolet ((terminator-opcode ()
472 (or (get 'fop-funcall-for-effect
'opcode
)
473 (error "Missing FOP definition?"))))
474 (when (and (eq byte
(terminator-opcode))
475 (fop-stack-empty-p stack
)) ; (presumed) end of TLF
476 (awhen (%fasl-input-deprecated-stuff fasl-input
)
477 ;; Delaying this message rather than printing it
478 ;; in fop-fdefn makes it more informative (usually).
479 (setf (%fasl-input-deprecated-stuff fasl-input
) nil
)
480 (loader-deprecation-warn
482 (and (eq (svref stack
1) 'sb
!impl
::%defun
) (svref stack
2))))
485 (prin1 result
))))))))))))
487 (defun load-as-fasl (stream verbose print
)
488 (when (zerop (file-length stream
))
489 (error "attempt to load an empty FASL file:~% ~S" (namestring stream
)))
490 (maybe-announce-load stream verbose
)
491 (let ((fasl-input (make-fasl-input stream
)))
493 (loop while
(load-fasl-group fasl-input print
))
494 ;; Nuke the table and stack to avoid keeping garbage on
495 ;; conservatively collected platforms.
496 (nuke-fop-vector (%fasl-input-table fasl-input
))
497 (nuke-fop-vector (%fasl-input-stack fasl-input
))))
500 (declaim (notinline read-byte
)) ; Why is it even *declaimed* inline above?
502 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
505 (defvar *fop-counts
* (make-array 256 :initial-element
0))
506 (defvar *fop-times
* (make-array 256 :initial-element
0))
507 (defvar *print-fops
* nil
)
509 (defun clear-counts ()
510 (fill (the simple-vector
*fop-counts
*) 0)
511 (fill (the simple-vector
*fop-times
*) 0)
514 (defun analyze-counts ()
519 (macrolet ((breakdown (lvar tvar vec
)
523 (let ((n (svref ,vec i
)))
524 (push (cons (%fun-name
(svref **fop-funs
** i
)) n
) ,lvar
)
526 (setq ,lvar
(subseq (sort ,lvar
(lambda (x y
)
527 (> (cdr x
) (cdr y
))))
530 (breakdown counts total-count
*fop-counts
*)
531 (breakdown times total-time
*fop-times
*)
532 (format t
"Total fop count is ~D~%" total-count
)
534 (format t
"~30S: ~4D~%" (car c
) (cdr c
)))
535 (format t
"~%Total fop time is ~D~%" (/ (float total-time
) 60.0))
537 (format t
"~30S: ~6,2F~%" (car m
) (/ (float (cdr m
)) 60.0))))))