1.0.9.48: texi2pdf rework (Aymeric Vincent sbcl-devel 2007-09-05)
[sbcl/lichteblau.git] / src / code / load.lisp
blob8b3067df27ca8639abed6154e0fd6fb4ab4a3e90
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 ;;;; 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 *big-compiler-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 ()
30 (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)
42 (when verbose
43 (load-fresh-line)
44 (let ((name #-sb-xc-host (file-name stream-we-are-loading-from)
45 #+sb-xc-host nil))
46 (if name
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
59 ;;; FAST-READ-BYTE.
60 (defmacro fast-read-u-integer (n)
61 (declare (optimize (speed 0)))
62 (do ((res '(fast-read-byte)
63 `(logior (fast-read-byte)
64 (ash ,res 8)))
65 (cnt 1 (1+ cnt)))
66 ((>= cnt n) res)))
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))
71 (n-res (gensym))
72 (n-cnt (gensym)))
73 `(do ((,n-pos 8 (+ ,n-pos 8))
74 (,n-cnt (1- ,n) (1- ,n-cnt))
75 (,n-res
76 (fast-read-byte)
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))
87 ,n-last
88 (logior ,n-last #x-100)))
89 `(logior (fast-read-byte)
90 (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
91 (cnt 1 (1+ cnt)))
92 ((>= cnt n) res))))
94 ;;; Read an N-byte unsigned integer from the *FASL-INPUT-STREAM*.
95 (defmacro read-arg (n)
96 (declare (optimize (speed 0)))
97 (if (= n 1)
98 `(the (unsigned-byte 8) (read-byte *fasl-input-stream*))
99 `(prepare-for-fast-read-byte *fasl-input-stream*
100 (prog1
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)))
107 (read-arg 1))
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)))
119 (read-arg 4))
122 ;;;; the fop table
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
126 ;;; recursively.
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*))
159 (grow-fop-table))
160 (setq *current-fop-table-index* (1+ ,n-index))
161 (setf (svref *current-fop-table* ,n-index) ,thing))))
163 ;;;; the fop stack
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.)
167 (defvar *fop-stack*)
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
172 ;;; if PUSHP.
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))
181 (push-stack (value)
182 `(vector-push-extend ,value ,',fop-stack))
183 (call-with-popped-args (fun n)
184 `(%call-with-popped-args ,fun ,n ,',fop-stack)))
185 ,(if pushp
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
199 `(,(nth i argtmps)
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.)
208 (,fun ,@argtmps)))))
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))
219 (:report
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))
227 (:report
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-byte condition)
234 (invalid-fasl-expected condition)))))
236 (define-condition invalid-fasl-version (invalid-fasl)
237 ((variant :reader invalid-fasl-variant :initarg :variant)
238 (version :reader invalid-fasl-version :initarg :version))
239 (:report
240 (lambda (condition stream)
241 (format stream "~@<~S is in ~A fasl file format version ~W, ~
242 but this version of SBCL uses format version ~W.~:@>"
243 (invalid-fasl-stream condition)
244 (invalid-fasl-variant condition)
245 (invalid-fasl-version condition)
246 (invalid-fasl-expected condition)))))
248 (define-condition invalid-fasl-implementation (invalid-fasl)
249 ((implementation :reader invalid-fasl-implementation
250 :initarg :implementation))
251 (:report
252 (lambda (condition stream)
253 (format stream "~S was compiled for implementation ~A, but this is a ~A."
254 (invalid-fasl-stream condition)
255 (invalid-fasl-implementation condition)
256 (invalid-fasl-expected condition)))))
258 (define-condition invalid-fasl-features (invalid-fasl)
259 ((potential-features :reader invalid-fasl-potential-features
260 :initarg :potential-features)
261 (features :reader invalid-fasl-features :initarg :features))
262 (:report
263 (lambda (condition stream)
264 (format stream "~@<incompatible ~S in fasl file ~S: ~2I~_~
265 Of features affecting binary compatibility, ~4I~_~S~2I~_~
266 the fasl has ~4I~_~A,~2I~_~
267 while the runtime expects ~4I~_~A.~:>"
268 '*features*
269 (invalid-fasl-stream condition)
270 (invalid-fasl-potential-features condition)
271 (invalid-fasl-features condition)
272 (invalid-fasl-expected condition)))))
274 ;;;; LOAD-AS-FASL
275 ;;;;
276 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
277 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
278 ;;;; it's needed not only in the target Lisp, but also in the
279 ;;;; cross-compilation host.
281 ;;; a helper function for LOAD-FASL-GROUP
283 ;;; Return true if we successfully read a FASL header from the stream,
284 ;;; or NIL if EOF was hit before anything was read. Signal an error if
285 ;;; we encounter garbage.
286 (defun check-fasl-header (stream)
288 (let ((byte (read-byte stream nil)))
289 (when byte
291 ;; Read and validate constant string prefix in fasl header.
292 (let* ((fhsss *fasl-header-string-start-string*)
293 (fhsss-length (length fhsss)))
294 (unless (= byte (char-code (schar fhsss 0)))
295 (error 'invalid-fasl-header
296 :stream stream
297 :first-byte-p t
298 :byte byte
299 :expected (char-code (schar fhsss 0))))
300 (do ((byte (read-byte stream) (read-byte stream))
301 (count 1 (1+ count)))
302 ((= byte +fasl-header-string-stop-char-code+)
304 (declare (fixnum byte count))
305 (when (and (< count fhsss-length)
306 (not (eql byte (char-code (schar fhsss count)))))
307 (error 'invalid-fasl-header
308 :stream stream
309 :byte-nr count
310 :byte byte
311 :expected (char-code (schar fhsss count))))))
313 ;; Read and validate version-specific compatibility stuff.
314 (flet ((string-from-stream ()
315 (let* ((length (read-unsigned-byte-32-arg))
316 (result (make-string length)))
317 (read-string-as-bytes stream result)
318 result)))
319 ;; Read and validate implementation and version.
320 (let* ((implementation (keywordicate (string-from-stream)))
321 ;; FIXME: The logic above to read a keyword from the fasl file
322 ;; could probably be shared with the read-a-keyword fop.
323 (version (read-word-arg)))
324 (flet ((check-version (variant
325 possible-implementation
326 needed-version)
327 (when (string= possible-implementation implementation)
328 (or (= version needed-version)
329 (error 'invalid-fasl-version
330 ;; :error :wrong-version
331 :stream stream
332 :variant variant
333 :version version
334 :expected needed-version)))))
335 (or (check-version "native code"
336 +backend-fasl-file-implementation+
337 +fasl-file-version+)
338 (error 'invalid-fasl-implementation
339 :stream stream
340 :implementation implementation
341 :expected +backend-fasl-file-implementation+))))
342 ;; Read and validate *FEATURES* which affect binary compatibility.
343 (let ((faff-in-this-file (string-from-stream)))
344 (unless (string= faff-in-this-file *features-affecting-fasl-format*)
345 (error 'invalid-fasl-features
346 :stream stream
347 :potential-features *features-potentially-affecting-fasl-format*
348 :expected *features-affecting-fasl-format*
349 :features faff-in-this-file)))
350 ;; success
351 t))))
353 ;; Setting this variable gives you a trace of fops as they are loaded and
354 ;; executed.
355 #!+sb-show
356 (defvar *show-fops-p* nil)
358 ;; buffer for loading symbols
359 (defvar *fasl-symbol-buffer*)
360 (declaim (simple-string *fasl-symbol-buffer*))
363 ;;; a helper function for LOAD-AS-FASL
365 ;;; Return true if we successfully load a group from the stream, or
366 ;;; NIL if EOF was encountered while trying to read from the stream.
367 ;;; Dispatch to the right function for each fop.
368 (defun load-fasl-group (stream)
369 (when (check-fasl-header stream)
370 (catch 'fasl-group-end
371 (let ((*current-fop-table-index* 0)
372 (*skip-until* nil))
373 (declare (special *skip-until*))
374 (loop
375 (let ((byte (read-byte stream)))
376 ;; Do some debugging output.
377 #!+sb-show
378 (when *show-fops-p*
379 (let* ((stack *fop-stack*)
380 (ptr (1- (fill-pointer *fop-stack*))))
381 (fresh-line *trace-output*)
382 ;; The FOP operations are stack based, so it's sorta
383 ;; logical to display the operand before the operator.
384 ;; ("reverse Polish notation")
385 (unless (= ptr -1)
386 (write-char #\space *trace-output*)
387 (prin1 (aref stack ptr) *trace-output*)
388 (terpri *trace-output*))
389 ;; Display the operator.
390 (format *trace-output*
391 "~&~S (#X~X at ~D) (~S)~%"
392 (aref *fop-names* byte)
393 byte
394 (1- (file-position stream))
395 (svref *fop-funs* byte))))
397 ;; Actually execute the fop.
398 (funcall (the function (svref *fop-funs* byte)))))))))
400 (defun load-as-fasl (stream verbose print)
401 ;; KLUDGE: ANSI says it's good to do something with the :PRINT
402 ;; argument to LOAD when we're fasloading a file, but currently we
403 ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
404 ;; just disabled that instead of rewriting it.) -- WHN 20000131
405 (declare (ignore print))
406 (when (zerop (file-length stream))
407 (error "attempt to load an empty FASL file:~% ~S" (namestring stream)))
408 (maybe-announce-load stream verbose)
409 (sb!thread:with-recursive-lock (sb!c::*big-compiler-lock*)
410 (let* ((*fasl-input-stream* stream)
411 (*fasl-symbol-buffer* (make-string 100))
412 (*current-fop-table* (or (pop *free-fop-tables*) (make-array 1000)))
413 (*current-fop-table-size* (length *current-fop-table*))
414 (*fop-stack* (make-array 100 :fill-pointer 0 :adjustable t)))
415 (unwind-protect
416 (loop while (load-fasl-group stream))
417 (push *current-fop-table* *free-fop-tables*)
418 ;; NIL out the table, so that we don't hold onto garbage.
420 ;; FIXME: Could we just get rid of the free fop table pool so
421 ;; that this would go away?
422 (fill *current-fop-table* nil))))
425 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
428 (defvar *fop-counts* (make-array 256 :initial-element 0))
429 (defvar *fop-times* (make-array 256 :initial-element 0))
430 (defvar *print-fops* nil)
432 (defun clear-counts ()
433 (fill (the simple-vector *fop-counts*) 0)
434 (fill (the simple-vector *fop-times*) 0)
437 (defun analyze-counts ()
438 (let ((counts ())
439 (total-count 0)
440 (times ())
441 (total-time 0))
442 (macrolet ((breakdown (lvar tvar vec)
443 `(progn
444 (dotimes (i 255)
445 (declare (fixnum i))
446 (let ((n (svref ,vec i)))
447 (push (cons (svref *fop-names* i) n) ,lvar)
448 (incf ,tvar n)))
449 (setq ,lvar (subseq (sort ,lvar (lambda (x y)
450 (> (cdr x) (cdr y))))
451 0 10)))))
453 (breakdown counts total-count *fop-counts*)
454 (breakdown times total-time *fop-times*)
455 (format t "Total fop count is ~D~%" total-count)
456 (dolist (c counts)
457 (format t "~30S: ~4D~%" (car c) (cdr c)))
458 (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
459 (dolist (m times)
460 (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))