Fix FORMAT compilation on non-simple strings.
[sbcl.git] / src / code / load.lisp
blob2b08c79f62b2bc0ca6a22b97f28e76338d3f35ab
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
3 ;;;; GENESIS)
4 ;;;;
5 ;;;; based on the CMU CL load.lisp code, written by Skef Wholey and
6 ;;;; Rob Maclachlan
8 ;;;; This software is part of the SBCL system. See the README file for
9 ;;;; more information.
10 ;;;;
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 ()
24 (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)
36 (when verbose
37 (load-fresh-line)
38 (let ((name #-sb-xc-host (file-name stream-we-are-loading-from)
39 #+sb-xc-host nil))
40 (if name
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
49 ;;; FAST-READ-BYTE.
50 (defmacro fast-read-u-integer (n)
51 (let (bytes)
52 `(let ,(loop for i from 0 below n
53 collect (let ((name (gensym "B")))
54 (push name bytes)
55 `(,name ,(if (zerop i)
56 `(fast-read-byte)
57 `(ash (fast-read-byte) ,(* i 8))))))
58 (logior ,@bytes))))
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))
63 (n-res (gensym))
64 (n-cnt (gensym)))
65 `(do ((,n-pos 8 (+ ,n-pos 8))
66 (,n-cnt (1- ,n) (1- ,n-cnt))
67 (,n-res
68 (fast-read-byte)
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))
88 ,n-last
89 (logior ,n-last #x-100)))
90 `(logior (fast-read-byte)
91 (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
92 (cnt 1 (1+ cnt)))
93 ((>= cnt n) res))))
95 ;;; Read an N-byte unsigned integer from FASL-INPUT-STREAM.
96 (defmacro read-arg (n fasl-input-stream)
97 (if (= n 1)
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)
104 (shift 0))
105 (declare (fixnum shift) (type word accumulator))
106 (with-fast-read-byte ((unsigned-byte 8) (%fasl-input-stream fasl-input))
107 (loop
108 (let ((octet (fast-read-byte)))
109 (setq accumulator (logior accumulator (ash (logand octet #x7F) shift)))
110 (incf shift 7)
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)))
122 (read-arg 1 stream))
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)))
130 (read-arg 4 stream))
133 ;;;; the fop table
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)
166 new-vector))
168 (defun nuke-fop-vector (vector)
169 (declare (simple-vector vector)
170 #!-gencgc (ignore vector)
171 (optimize speed))
172 ;; Make sure we don't keep any garbage.
173 #!+gencgc
174 (fill vector 0))
177 ;;;; the fop stack
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)))
189 (new-top (- top n)))
190 (if (minusp new-top) ; 0 is ok at this point
191 (error "FOP stack underflow")
192 (progn (setf (svref stack 0) new-top)
193 (1+ 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))
215 (:report
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))
223 (:report
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))
234 (:report
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))
245 (:report
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 ((features :reader invalid-fasl-features :initarg :features))
254 (:report
255 (lambda (condition stream)
256 (format stream "~@<incompatible features ~A ~_in fasl file ~S: ~2I~_~
257 Runtime expects ~A~:>"
258 (invalid-fasl-features condition)
259 (invalid-fasl-stream condition)
260 (invalid-fasl-expected condition)))))
262 ;;; Skips past the shebang line on stream, if any.
263 (defun maybe-skip-shebang-line (stream)
264 (let ((p (file-position stream)))
265 (flet ((next () (read-byte stream nil)))
266 (unwind-protect
267 (when (and (eq (next) (char-code #\#))
268 (eq (next) (char-code #\!)))
269 (setf p nil)
270 (loop for x = (next)
271 until (or (not x) (eq x (char-code #\newline)))))
272 (when p
273 (file-position stream p))))
276 ;;; Returns T if the stream is a binary input stream with a FASL header.
277 #-sb-xc-host ;; FIXME: function belongs in 'target-load'
278 (defun fasl-header-p (stream &key errorp)
279 (unless (and (member (stream-element-type stream) '(character base-char))
280 ;; give up if it's not a file stream, or it's an
281 ;; fd-stream but it's either not bivalent or not
282 ;; seekable (doesn't really have a file)
283 (or (not (typep stream 'file-stream))
284 (and (typep stream 'fd-stream)
285 (or (not (sb!impl::fd-stream-bivalent-p stream))
286 (not (sb!impl::fd-stream-file stream))))))
287 (let ((p (file-position stream)))
288 (unwind-protect
289 (let* ((header *fasl-header-string-start-string*)
290 (buffer (make-array (length header) :element-type '(unsigned-byte 8)))
291 (n 0))
292 (flet ((scan ()
293 (maybe-skip-shebang-line stream)
294 (setf n (read-sequence buffer stream))))
295 (if errorp
296 (scan)
297 (or (ignore-errors (scan))
298 ;; no a binary input stream
299 (return-from fasl-header-p nil))))
300 (if (mismatch buffer header
301 :test #'(lambda (code char) (= code (char-code char))))
302 ;; Immediate EOF is valid -- we want to match what
303 ;; CHECK-FASL-HEADER does...
304 (or (zerop n)
305 (when errorp
306 (error 'fasl-header-missing
307 :stream stream
308 :fhsss buffer
309 :expected header)))
311 (file-position stream p)))))
314 ;;;; LOAD-AS-FASL
315 ;;;;
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)))
329 (when byte
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
335 :stream stream
336 :byte-nr 0
337 :byte byte
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
347 :stream stream
348 :byte-nr count
349 :byte byte
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 stream))
354 (result (make-string length)))
355 (read-string-as-bytes stream result)
356 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
362 :stream stream
363 :implementation implementation
364 :expected expected-implementation)))
365 (let* ((fasl-version (read-word-arg stream))
366 (sbcl-version (if (<= fasl-version 76)
367 "1.0.11.18"
368 (string-from-stream)))
369 (expected-version (sb!xc:lisp-implementation-version)))
370 (unless (string= expected-version sbcl-version)
371 (restart-case
372 (error 'invalid-fasl-version
373 :stream stream
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 (expected (compute-features-affecting-fasl-format)))
380 (unless (string= faff-in-this-file expected)
381 (error 'invalid-fasl-features
382 :stream stream
383 :expected expected
384 :features faff-in-this-file)))
385 ;; success
386 t))))
388 ;; Setting this variable gives you a trace of fops as they are loaded and
389 ;; executed.
390 #!+sb-show
391 (defvar *show-fops-p* nil)
392 (defvar *fasl-source-info*)
394 ;;; a helper function for LOAD-AS-FASL
396 ;;; Return true if we successfully load a group from the stream, or
397 ;;; NIL if EOF was encountered while trying to read from the stream.
398 ;;; Dispatch to the right function for each fop.
399 (defun load-fasl-group (fasl-input print)
401 ;; PRINT causes most tlf-equivalent forms to print their primary value.
402 ;; This differs from loading of Lisp source, which prints all values of
403 ;; only truly-toplevel forms. This is permissible per CLHS -
404 ;; "If print is true, load incrementally prints information to standard
405 ;; output showing the progress of the loading process. [...]
406 ;; For a compiled file, what is printed might not reflect precisely the
407 ;; contents of the source file, but some information is generally printed."
409 (declare (ignorable print))
410 (let ((stream (%fasl-input-stream fasl-input))
411 *fasl-source-info*
412 (trace #!+sb-show *show-fops-p*))
413 (unless (check-fasl-header stream)
414 (return-from load-fasl-group))
415 (catch 'fasl-group-end
416 (setf (svref (%fasl-input-table fasl-input) 0) 0)
417 (macrolet ((tracing (&body forms) `(when trace ,@forms)))
418 (loop
419 (let* ((byte (the (unsigned-byte 8) (read-byte stream)))
420 (function (svref **fop-funs** byte))
421 (n-operands (aref (car **fop-signatures**) byte)))
422 ;; Do some debugging output.
423 (tracing
424 (format *trace-output* "~&~6x : [~D,~D] ~2,'0x(~A)"
425 (1- (file-position stream))
426 (svref (%fasl-input-stack fasl-input) 0) ; stack pointer
427 (svref (%fasl-input-table fasl-input) 0) ; table pointer
428 byte (and (functionp function) (%fun-name function))))
429 ;; Actually execute the fop.
430 (let ((result
431 (cond ((not (functionp function))
432 (error "corrupt fasl file: FOP code #x~x" byte))
433 ((zerop n-operands)
434 (funcall function fasl-input))
436 (let (arg1 arg2 arg3)
437 (with-fast-read-byte ((unsigned-byte 8) stream)
438 ;; The low 2 bits of the opcode determine the
439 ;; number of octets used for the 1st operand.
440 (setq arg1 (fast-read-var-u-integer (ash 1 (logand byte 3)))))
441 (when (>= n-operands 2)
442 (setq arg2 (read-varint-arg fasl-input))
443 (when (>= n-operands 3)
444 (setq arg3 (read-varint-arg fasl-input))))
445 (tracing (format *trace-output* "{~D~@[,~D~@[,~D~]~]}"
446 arg1 arg2 arg3))
447 (case n-operands
448 (3 (funcall function fasl-input arg1 arg2 arg3))
449 (2 (funcall function fasl-input arg1 arg2))
450 (1 (funcall function fasl-input arg1))))))))
451 (when (plusp (sbit (cdr **fop-signatures**) byte))
452 (push-fop-stack result fasl-input))
453 (let ((stack (%fasl-input-stack fasl-input)))
454 (declare (ignorable stack)) ; not used in xc-host
455 (tracing
456 (let ((ptr (svref stack 0)))
457 (format *trace-output* " -- ~[<empty>,~D~:;[~:*~D,~D] ~S~]"
458 ptr (svref (%fasl-input-table fasl-input) 0)
459 (unless (eql ptr 0) (aref stack ptr)))
460 (terpri *trace-output*)))
461 #-sb-xc-host
462 (macrolet ((terminator-opcode ()
463 (or (get 'fop-funcall-for-effect 'opcode)
464 (error "Missing FOP definition?"))))
465 (when (and (eq byte (terminator-opcode))
466 (fop-stack-empty-p stack)) ; (presumed) end of TLF
467 (awhen (%fasl-input-deprecated-stuff fasl-input)
468 ;; Delaying this message rather than printing it
469 ;; in fop-fdefn makes it more informative (usually).
470 (setf (%fasl-input-deprecated-stuff fasl-input) nil)
471 (loader-deprecation-warn
473 (and (eq (svref stack 1) 'sb!impl::%defun) (svref stack 2))))
474 (when print
475 (load-fresh-line)
476 (prin1 result))))))))))))
478 (defun load-as-fasl (stream verbose print)
479 (when (zerop (file-length stream))
480 (error "attempt to load an empty FASL file:~% ~S" (namestring stream)))
481 (maybe-announce-load stream verbose)
482 (let ((fasl-input (make-fasl-input stream)))
483 (unwind-protect
484 (loop while (load-fasl-group fasl-input print))
485 ;; Nuke the table and stack to avoid keeping garbage on
486 ;; conservatively collected platforms.
487 (nuke-fop-vector (%fasl-input-table fasl-input))
488 (nuke-fop-vector (%fasl-input-stack fasl-input))))
491 (declaim (notinline read-byte)) ; Why is it even *declaimed* inline above?
493 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
496 (defvar *fop-counts* (make-array 256 :initial-element 0))
497 (defvar *fop-times* (make-array 256 :initial-element 0))
498 (defvar *print-fops* nil)
500 (defun clear-counts ()
501 (fill (the simple-vector *fop-counts*) 0)
502 (fill (the simple-vector *fop-times*) 0)
505 (defun analyze-counts ()
506 (let ((counts ())
507 (total-count 0)
508 (times ())
509 (total-time 0))
510 (macrolet ((breakdown (lvar tvar vec)
511 `(progn
512 (dotimes (i 255)
513 (declare (fixnum i))
514 (let ((n (svref ,vec i)))
515 (push (cons (%fun-name (svref **fop-funs** i)) n) ,lvar)
516 (incf ,tvar n)))
517 (setq ,lvar (subseq (sort ,lvar (lambda (x y)
518 (> (cdr x) (cdr y))))
519 0 10)))))
521 (breakdown counts total-count *fop-counts*)
522 (breakdown times total-time *fop-times*)
523 (format t "Total fop count is ~D~%" total-count)
524 (dolist (c counts)
525 (format t "~30S: ~4D~%" (car c) (cdr c)))
526 (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
527 (dolist (m times)
528 (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))