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 ;;;; There looks to be an exciting amount of state being modified
20 ;;;; here: certainly enough that I (dan, 2003.1.22) don't want to mess
21 ;;;; around deciding how to thread-safetify it. So we use a Big Lock.
22 ;;;; Because this code is mutually recursive with the compiler, we use
23 ;;;; the **WORLD-LOCK**.
25 ;;;; miscellaneous load utilities
27 ;;; Output the current number of semicolons after a fresh-line.
28 ;;; FIXME: non-mnemonic name
29 (defun load-fresh-line ()
31 (let ((semicolons ";;;;;;;;;;;;;;;;"))
32 (do ((count *load-depth
* (- count
(length semicolons
))))
33 ((< count
(length semicolons
))
34 (write-string semicolons
*standard-output
* :end count
))
35 (declare (fixnum count
))
36 (write-string semicolons
))
37 (write-char #\space
)))
39 ;;; If VERBOSE, output (to *STANDARD-OUTPUT*) a message about how
40 ;;; we're loading from STREAM-WE-ARE-LOADING-FROM.
41 (defun maybe-announce-load (stream-we-are-loading-from verbose
)
44 (let ((name #-sb-xc-host
(file-name stream-we-are-loading-from
)
47 (format t
"loading ~S~%" name
)
48 (format t
"loading stuff from ~S~%" stream-we-are-loading-from
)))))
50 ;;;; utilities for reading from fasl files
52 #!-sb-fluid
(declaim (inline read-byte
))
54 ;;; FIXME: why do all of these reading functions and macros declare
55 ;;; (SPEED 0)? was there some bug in the compiler which has since
56 ;;; been fixed? --njf, 2004-09-08
58 ;;; This expands into code to read an N-byte unsigned integer using
60 (defmacro fast-read-u-integer
(n)
61 (declare (optimize (speed 0)))
62 (do ((res '(fast-read-byte)
63 `(logior (fast-read-byte)
68 ;;; like FAST-READ-U-INTEGER, but the size may be determined at run time
69 (defmacro fast-read-var-u-integer
(n)
70 (let ((n-pos (gensym))
73 `(do ((,n-pos
8 (+ ,n-pos
8))
74 (,n-cnt
(1- ,n
) (1- ,n-cnt
))
77 (dpb (fast-read-byte) (byte 8 ,n-pos
) ,n-res
)))
78 ((zerop ,n-cnt
) ,n-res
)
79 (declare (type index
,n-pos
,n-cnt
)))))
81 ;;; Read a signed integer.
82 (defmacro fast-read-s-integer
(n)
83 (declare (optimize (speed 0)))
84 (let ((n-last (gensym)))
85 (do ((res `(let ((,n-last
(fast-read-byte)))
86 (if (zerop (logand ,n-last
#x80
))
88 (logior ,n-last
#x-100
)))
89 `(logior (fast-read-byte)
90 (ash (the (signed-byte ,(* cnt
8)) ,res
) 8)))
94 ;;; Read an N-byte unsigned integer from the *FASL-INPUT-STREAM*.
95 (defmacro read-arg
(n)
96 (declare (optimize (speed 0)))
98 `(the (unsigned-byte 8) (read-byte *fasl-input-stream
*))
99 `(prepare-for-fast-read-byte *fasl-input-stream
*
101 (fast-read-u-integer ,n
)
102 (done-with-fast-read-byte)))))
104 (declaim (inline read-byte-arg read-halfword-arg read-word-arg
))
105 (defun read-byte-arg ()
106 (declare (optimize (speed 0)))
109 (defun read-halfword-arg ()
110 (declare (optimize (speed 0)))
111 (read-arg #.
(/ sb
!vm
:n-word-bytes
2)))
113 (defun read-word-arg ()
114 (declare (optimize (speed 0)))
115 (read-arg #.sb
!vm
:n-word-bytes
))
117 (defun read-unsigned-byte-32-arg ()
118 (declare (optimize (speed 0)))
124 ;;; The table is implemented as a simple-vector indexed by the table
125 ;;; offset. We may need to have several, since LOAD can be called
128 ;;; a list of free fop tables for the fasloader
130 ;;; FIXME: Is it really a win to have this permanently bound?
131 ;;; Couldn't we just bind it on entry to LOAD-AS-FASL?
132 (defvar *free-fop-tables
* (list (make-array 1000)))
134 ;;; the current fop table
135 (defvar *current-fop-table
*)
136 (declaim (simple-vector *current-fop-table
*))
138 ;;; the length of the current fop table
139 (defvar *current-fop-table-size
*)
140 (declaim (type index
*current-fop-table-size
*))
142 ;;; the index in the fop-table of the next entry to be used
143 (defvar *current-fop-table-index
*)
144 (declaim (type index
*current-fop-table-index
*))
146 (defun grow-fop-table ()
147 (let* ((new-size (* *current-fop-table-size
* 2))
148 (new-table (make-array new-size
)))
149 (declare (fixnum new-size
) (simple-vector new-table
))
150 (replace new-table
(the simple-vector
*current-fop-table
*))
151 (setq *current-fop-table
* new-table
)
152 (setq *current-fop-table-size
* new-size
)))
154 (defmacro push-fop-table
(thing)
155 (let ((n-index (gensym)))
156 `(let ((,n-index
*current-fop-table-index
*))
157 (declare (fixnum ,n-index
))
158 (when (= ,n-index
(the fixnum
*current-fop-table-size
*))
160 (setq *current-fop-table-index
* (1+ ,n-index
))
161 (setf (svref *current-fop-table
* ,n-index
) ,thing
))))
165 ;;; (This is to be bound by LOAD to an adjustable (VECTOR T) with
166 ;;; FILL-POINTER, for use as a stack with VECTOR-PUSH-EXTEND.)
168 (declaim (type (vector t
) *fop-stack
*))
170 ;;; Cache information about the fop stack in local variables. Define a
171 ;;; local macro to pop from the stack. Push the result of evaluation
173 (defmacro with-fop-stack
(pushp &body forms
)
174 (aver (member pushp
'(nil t
:nope
)))
175 (with-unique-names (fop-stack)
176 `(let ((,fop-stack
*fop-stack
*))
177 (declare (type (vector t
) ,fop-stack
)
178 (ignorable ,fop-stack
))
179 (macrolet ((pop-stack ()
180 `(vector-pop ,',fop-stack
))
182 `(vector-push-extend ,value
,',fop-stack
))
183 (call-with-popped-args (fun n
)
184 `(%call-with-popped-args
,fun
,n
,',fop-stack
)))
186 `(vector-push-extend (progn ,@forms
) ,fop-stack
)
187 `(progn ,@forms
))))))
189 ;;; Call FUN with N arguments popped from STACK.
190 (defmacro %call-with-popped-args
(fun n stack
)
191 ;; N's integer value must be known at macroexpansion time.
192 (declare (type index n
))
193 (with-unique-names (n-stack old-length new-length
)
194 (let ((argtmps (make-gensym-list n
)))
195 `(let* ((,n-stack
,stack
)
196 (,old-length
(fill-pointer ,n-stack
))
197 (,new-length
(- ,old-length
,n
))
198 ,@(loop for i from
0 below n collecting
200 (aref ,n-stack
(+ ,new-length
,i
)))))
201 (declare (type (vector t
) ,n-stack
))
202 (setf (fill-pointer ,n-stack
) ,new-length
)
203 ;; (For some applications it might be appropriate to FILL the
204 ;; popped area with NIL here, to avoid holding onto garbage. For
205 ;; sbcl-0.8.7.something, though, it shouldn't matter, because
206 ;; we're using this only to pop stuff off *FOP-STACK*, and the
207 ;; entire *FOP-STACK* can be GCed as soon as LOAD returns.)
210 ;;;; Conditions signalled on invalid fasls (wrong fasl version, etc),
211 ;;;; so that user code (esp. ASDF) can reasonably handle attempts to
212 ;;;; load such fasls by recompiling them, etc. For simplicity's sake
213 ;;;; make only condition INVALID-FASL part of the public interface,
214 ;;;; and keep the guts internal.
216 (define-condition invalid-fasl
(error)
217 ((stream :reader invalid-fasl-stream
:initarg
:stream
)
218 (expected :reader invalid-fasl-expected
:initarg
:expected
))
220 (lambda (condition stream
)
221 (format stream
"~S is an invalid fasl file."
222 (invalid-fasl-stream condition
)))))
224 (define-condition invalid-fasl-header
(invalid-fasl)
225 ((byte :reader invalid-fasl-byte
:initarg
:byte
)
226 (byte-nr :reader invalid-fasl-byte-nr
:initarg
:byte-nr
))
228 (lambda (condition stream
)
229 (format stream
"~@<~S contains an illegal byte in the FASL header at ~
230 position ~A: Expected ~A, got ~A.~:@>"
231 (invalid-fasl-stream condition
)
232 (invalid-fasl-byte-nr condition
)
233 (invalid-fasl-expected condition
)
234 (invalid-fasl-byte condition
)))))
236 (define-condition invalid-fasl-version
(invalid-fasl)
237 ((version :reader invalid-fasl-version
:initarg
:version
))
239 (lambda (condition stream
)
240 (format stream
"~@<~S is a fasl file compiled with SBCL ~W, and ~
241 can't be loaded into SBCL ~W.~:@>"
242 (invalid-fasl-stream condition
)
243 (invalid-fasl-version condition
)
244 (invalid-fasl-expected condition
)))))
246 (define-condition invalid-fasl-implementation
(invalid-fasl)
247 ((implementation :reader invalid-fasl-implementation
248 :initarg
:implementation
))
250 (lambda (condition stream
)
251 (format stream
"~S was compiled for implementation ~A, but this is a ~A."
252 (invalid-fasl-stream condition
)
253 (invalid-fasl-implementation condition
)
254 (invalid-fasl-expected condition
)))))
256 (define-condition invalid-fasl-features
(invalid-fasl)
257 ((potential-features :reader invalid-fasl-potential-features
258 :initarg
:potential-features
)
259 (features :reader invalid-fasl-features
:initarg
:features
))
261 (lambda (condition stream
)
262 (format stream
"~@<incompatible ~S in fasl file ~S: ~2I~_~
263 Of features affecting binary compatibility, ~4I~_~S~2I~_~
264 the fasl has ~4I~_~A,~2I~_~
265 while the runtime expects ~4I~_~A.~:>"
267 (invalid-fasl-stream condition
)
268 (invalid-fasl-potential-features condition
)
269 (invalid-fasl-features condition
)
270 (invalid-fasl-expected condition
)))))
272 ;;; Skips past the shebang line on stream, if any.
273 (defun maybe-skip-shebang-line (stream)
274 (let ((p (file-position stream
)))
275 (flet ((next () (read-byte stream nil
)))
277 (when (and (eq (next) (char-code #\
#))
278 (eq (next) (char-code #\
!)))
281 until
(or (not x
) (eq x
(char-code #\newline
)))))
283 (file-position stream p
))))
286 ;;; Returns T if the stream is a binary input stream with a FASL header.
287 (defun fasl-header-p (stream &key errorp
)
288 (let ((p (file-position stream
)))
290 (let* ((header *fasl-header-string-start-string
*)
291 (buffer (make-array (length header
) :element-type
'(unsigned-byte 8)))
294 (maybe-skip-shebang-line stream
)
295 (setf n
(read-sequence buffer stream
))))
298 (or (ignore-errors (scan))
299 ;; no a binary input stream
300 (return-from fasl-header-p nil
))))
301 (if (mismatch buffer header
302 :test
#'(lambda (code char
) (= code
(char-code char
))))
303 ;; Immediate EOF is valid -- we want to match what
304 ;; CHECK-FASL-HEADER does...
307 (error 'fasl-header-missing
312 (file-position stream p
))))
316 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
317 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
318 ;;;; it's needed not only in the target Lisp, but also in the
319 ;;;; cross-compilation host.
321 ;;; a helper function for LOAD-FASL-GROUP
323 ;;; Return true if we successfully read a FASL header from the stream, or NIL
324 ;;; if EOF was hit before anything except the optional shebang line was read.
325 ;;; Signal an error if we encounter garbage.
326 (defun check-fasl-header (stream)
327 (maybe-skip-shebang-line stream
)
328 (let ((byte (read-byte stream nil
)))
330 ;; Read and validate constant string prefix in fasl header.
331 (let* ((fhsss *fasl-header-string-start-string
*)
332 (fhsss-length (length fhsss
)))
333 (unless (= byte
(char-code (schar fhsss
0)))
334 (error 'invalid-fasl-header
338 :expected
(char-code (schar fhsss
0))))
339 (do ((byte (read-byte stream
) (read-byte stream
))
340 (count 1 (1+ count
)))
341 ((= byte
+fasl-header-string-stop-char-code
+)
343 (declare (fixnum byte count
))
344 (when (and (< count fhsss-length
)
345 (not (eql byte
(char-code (schar fhsss count
)))))
346 (error 'invalid-fasl-header
350 :expected
(char-code (schar fhsss count
))))))
351 ;; Read and validate version-specific compatibility stuff.
352 (flet ((string-from-stream ()
353 (let* ((length (read-unsigned-byte-32-arg))
354 (result (make-string length
)))
355 (read-string-as-bytes stream result
)
357 ;; Read and validate implementation and version.
358 (let ((implementation (keywordicate (string-from-stream)))
359 (expected-implementation +backend-fasl-file-implementation
+))
360 (unless (string= expected-implementation implementation
)
361 (error 'invalid-fasl-implementation
363 :implementation implementation
364 :expected expected-implementation
)))
365 (let* ((fasl-version (read-word-arg))
366 (sbcl-version (if (<= fasl-version
76)
368 (string-from-stream)))
369 (expected-version (sb!xc
:lisp-implementation-version
)))
370 (unless (string= expected-version sbcl-version
)
372 (error 'invalid-fasl-version
374 :version sbcl-version
375 :expected expected-version
)
376 (continue () :report
"Load the fasl file anyway"))))
377 ;; Read and validate *FEATURES* which affect binary compatibility.
378 (let ((faff-in-this-file (string-from-stream)))
379 (unless (string= faff-in-this-file
*features-affecting-fasl-format
*)
380 (error 'invalid-fasl-features
382 :potential-features
*features-potentially-affecting-fasl-format
*
383 :expected
*features-affecting-fasl-format
*
384 :features faff-in-this-file
)))
388 ;; Setting this variable gives you a trace of fops as they are loaded and
391 (defvar *show-fops-p
* nil
)
393 ;; buffer for loading symbols
394 (defvar *fasl-symbol-buffer
*)
395 (declaim (simple-string *fasl-symbol-buffer
*))
398 ;;; a helper function for LOAD-AS-FASL
400 ;;; Return true if we successfully load a group from the stream, or
401 ;;; NIL if EOF was encountered while trying to read from the stream.
402 ;;; Dispatch to the right function for each fop.
403 (defun load-fasl-group (stream)
404 (when (check-fasl-header stream
)
405 (catch 'fasl-group-end
406 (let ((*current-fop-table-index
* 0)
408 (declare (special *skip-until
*))
410 (let ((byte (read-byte stream
)))
411 ;; Do some debugging output.
414 (let* ((stack *fop-stack
*)
415 (ptr (1- (fill-pointer *fop-stack
*))))
416 (fresh-line *trace-output
*)
417 ;; The FOP operations are stack based, so it's sorta
418 ;; logical to display the operand before the operator.
419 ;; ("reverse Polish notation")
421 (write-char #\space
*trace-output
*)
422 (prin1 (aref stack ptr
) *trace-output
*)
423 (terpri *trace-output
*))
424 ;; Display the operator.
425 (format *trace-output
*
426 "~&~S (#X~X at ~D) (~S)~%"
427 (aref *fop-names
* byte
)
429 (1- (file-position stream
))
430 (svref *fop-funs
* byte
))))
432 ;; Actually execute the fop.
433 (funcall (the function
(svref *fop-funs
* byte
)))))))))
435 (defun load-as-fasl (stream verbose print
)
436 ;; KLUDGE: ANSI says it's good to do something with the :PRINT
437 ;; argument to LOAD when we're fasloading a file, but currently we
438 ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
439 ;; just disabled that instead of rewriting it.) -- WHN 20000131
440 (declare (ignore print
))
441 (when (zerop (file-length stream
))
442 (error "attempt to load an empty FASL file:~% ~S" (namestring stream
)))
443 (maybe-announce-load stream verbose
)
445 (let* ((*fasl-input-stream
* stream
)
446 (*fasl-symbol-buffer
* (make-string 100))
447 (*current-fop-table
* (or (pop *free-fop-tables
*) (make-array 1000)))
448 (*current-fop-table-size
* (length *current-fop-table
*))
449 (*fop-stack
* (make-array 100 :fill-pointer
0 :adjustable t
)))
451 (loop while
(load-fasl-group stream
))
452 (push *current-fop-table
* *free-fop-tables
*)
453 ;; NIL out the table, so that we don't hold onto garbage.
455 ;; FIXME: Could we just get rid of the free fop table pool so
456 ;; that this would go away?
457 (fill *current-fop-table
* nil
))))
460 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
463 (defvar *fop-counts
* (make-array 256 :initial-element
0))
464 (defvar *fop-times
* (make-array 256 :initial-element
0))
465 (defvar *print-fops
* nil
)
467 (defun clear-counts ()
468 (fill (the simple-vector
*fop-counts
*) 0)
469 (fill (the simple-vector
*fop-times
*) 0)
472 (defun analyze-counts ()
477 (macrolet ((breakdown (lvar tvar vec
)
481 (let ((n (svref ,vec i
)))
482 (push (cons (svref *fop-names
* i
) n
) ,lvar
)
484 (setq ,lvar
(subseq (sort ,lvar
(lambda (x y
)
485 (> (cdr x
) (cdr y
))))
488 (breakdown counts total-count
*fop-counts
*)
489 (breakdown times total-time
*fop-times
*)
490 (format t
"Total fop count is ~D~%" total-count
)
492 (format t
"~30S: ~4D~%" (car c
) (cdr c
)))
493 (format t
"~%Total fop time is ~D~%" (/ (float total-time
) 60.0))
495 (format t
"~30S: ~6,2F~%" (car m
) (/ (float (cdr m
)) 60.0))))))