easier to read FAST-READ-U-INTEGER expansion
[sbcl.git] / src / code / load.lisp
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
7
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.
16
17 (in-package "SB!FASL")
18 \f
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**.
24
25 ;;;; miscellaneous load utilities
26
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)))
38
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)))))
49 \f
50 ;;;; utilities for reading from fasl files
51
52 #!-sb-fluid (declaim (inline read-byte))
53
54 ;;; This expands into code to read an N-byte unsigned integer using
55 ;;; FAST-READ-BYTE.
56 (defmacro fast-read-u-integer (n)
57   (let (bytes)
58     `(let ,(loop for i from 0 below n
59                  collect (let ((name (gensym "B")))
60                            (push name bytes)
61                            `(,name ,(if (zerop i)
62                                         `(fast-read-byte)
63                                         `(ash (fast-read-byte) ,(* i 8))))))
64        (logior ,@bytes))))
65
66 ;;; like FAST-READ-U-INTEGER, but the size may be determined at run time
67 (defmacro fast-read-var-u-integer (n)
68   (let ((n-pos (gensym))
69         (n-res (gensym))
70         (n-cnt (gensym)))
71     `(do ((,n-pos 8 (+ ,n-pos 8))
72           (,n-cnt (1- ,n) (1- ,n-cnt))
73           (,n-res
74            (fast-read-byte)
75            (dpb (fast-read-byte) (byte 8 ,n-pos) ,n-res)))
76          ((zerop ,n-cnt) ,n-res)
77        (declare (type index ,n-pos ,n-cnt)))))
78
79 ;;; Read a signed integer.
80 (defmacro fast-read-s-integer (n)
81   (declare (optimize (speed 0)))
82   (let ((n-last (gensym)))
83     (do ((res `(let ((,n-last (fast-read-byte)))
84                  (if (zerop (logand ,n-last #x80))
85                      ,n-last
86                      (logior ,n-last #x-100)))
87               `(logior (fast-read-byte)
88                        (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
89          (cnt 1 (1+ cnt)))
90         ((>= cnt n) res))))
91
92 ;;; Read an N-byte unsigned integer from the *FASL-INPUT-STREAM*.
93 (defmacro read-arg (n)
94   (declare (optimize (speed 0)))
95   (if (= n 1)
96       `(the (unsigned-byte 8) (read-byte *fasl-input-stream*))
97       `(with-fast-read-byte ((unsigned-byte 8) *fasl-input-stream*)
98          (fast-read-u-integer ,n))))
99
100 (declaim (inline read-byte-arg read-halfword-arg read-word-arg))
101 (defun read-byte-arg ()
102   (declare (optimize (speed 0)))
103   (read-arg 1))
104
105 (defun read-halfword-arg ()
106   (declare (optimize (speed 0)))
107   (read-arg #.(/ sb!vm:n-word-bytes 2)))
108
109 (defun read-word-arg ()
110   (declare (optimize (speed 0)))
111   (read-arg #.sb!vm:n-word-bytes))
112
113 (defun read-unsigned-byte-32-arg ()
114   (declare (optimize (speed 0)))
115   (read-arg 4))
116
117 \f
118 ;;;; the fop table
119
120 ;;; The table is implemented as a simple-vector indexed by the table
121 ;;; offset. We may need to have several, since LOAD can be called
122 ;;; recursively.
123
124 ;;; a list of free fop tables for the fasloader
125 ;;;
126 ;;; FIXME: Is it really a win to have this permanently bound?
127 ;;; Couldn't we just bind it on entry to LOAD-AS-FASL?
128 (defvar *free-fop-tables* (list (make-array 1000)))
129
130 ;;; the current fop table
131 (defvar *current-fop-table*)
132 (declaim (simple-vector *current-fop-table*))
133
134 ;;; the length of the current fop table
135 (defvar *current-fop-table-size*)
136 (declaim (type index *current-fop-table-size*))
137
138 ;;; the index in the fop-table of the next entry to be used
139 (defvar *current-fop-table-index*)
140 (declaim (type index *current-fop-table-index*))
141
142 (defun grow-fop-table ()
143   (let* ((new-size (* *current-fop-table-size* 2))
144          (new-table (make-array new-size)))
145     (declare (fixnum new-size) (simple-vector new-table))
146     (replace new-table (the simple-vector *current-fop-table*))
147     (setq *current-fop-table* new-table)
148     (setq *current-fop-table-size* new-size)))
149
150 (defmacro push-fop-table (thing)
151   (let ((n-index (gensym)))
152     `(let ((,n-index *current-fop-table-index*))
153        (declare (fixnum ,n-index))
154        (when (= ,n-index (the fixnum *current-fop-table-size*))
155          (grow-fop-table))
156        (setq *current-fop-table-index* (1+ ,n-index))
157        (setf (svref *current-fop-table* ,n-index) ,thing))))
158 \f
159 ;;;; the fop stack
160
161 ;;; (This is to be bound by LOAD to an adjustable (VECTOR T) with
162 ;;; FILL-POINTER, for use as a stack with VECTOR-PUSH-EXTEND.)
163 (defvar *fop-stack*)
164 (declaim (type (vector t) *fop-stack*))
165
166 ;;; Cache information about the fop stack in local variables. Define a
167 ;;; local macro to pop from the stack. Push the result of evaluation
168 ;;; if PUSHP.
169 (defmacro with-fop-stack (pushp &body forms)
170   (aver (member pushp '(nil t :nope)))
171   (with-unique-names (fop-stack)
172     `(let ((,fop-stack *fop-stack*))
173        (declare (type (vector t) ,fop-stack)
174                 (ignorable ,fop-stack))
175        (macrolet ((pop-stack ()
176                     `(vector-pop ,',fop-stack))
177                   (push-stack (value)
178                     `(vector-push-extend ,value ,',fop-stack))
179                   (call-with-popped-args (fun n)
180                     `(%call-with-popped-args ,fun ,n ,',fop-stack)))
181          ,(if pushp
182               `(vector-push-extend (progn ,@forms) ,fop-stack)
183               `(progn ,@forms))))))
184
185 ;;; Call FUN with N arguments popped from STACK.
186 (defmacro %call-with-popped-args (fun n stack)
187   ;; N's integer value must be known at macroexpansion time.
188   (declare (type index n))
189   (with-unique-names (n-stack old-length new-length)
190     (let ((argtmps (make-gensym-list n)))
191       `(let* ((,n-stack ,stack)
192               (,old-length (fill-pointer ,n-stack))
193               (,new-length (- ,old-length ,n))
194               ,@(loop for i from 0 below n collecting
195                       `(,(nth i argtmps)
196                         (aref ,n-stack (+ ,new-length ,i)))))
197         (declare (type (vector t) ,n-stack))
198         (setf (fill-pointer ,n-stack) ,new-length)
199         ;; (For some applications it might be appropriate to FILL the
200         ;; popped area with NIL here, to avoid holding onto garbage. For
201         ;; sbcl-0.8.7.something, though, it shouldn't matter, because
202         ;; we're using this only to pop stuff off *FOP-STACK*, and the
203         ;; entire *FOP-STACK* can be GCed as soon as LOAD returns.)
204         (,fun ,@argtmps)))))
205 \f
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.
211
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)))))
219
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)))))
231
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)))))
241
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)))))
251
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))
256   (:report
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.~:>"
262              '*features*
263              (invalid-fasl-stream condition)
264              (invalid-fasl-potential-features condition)
265              (invalid-fasl-features condition)
266              (invalid-fasl-expected condition)))))
267
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)))
272       (unwind-protect
273            (when (and (eq (next) (char-code #\#))
274                       (eq (next) (char-code #\!)))
275              (setf p nil)
276              (loop for x = (next)
277                    until (or (not x) (eq x (char-code #\newline)))))
278         (when p
279           (file-position stream p))))
280     t))
281
282 ;;; Returns T if the stream is a binary input stream with a FASL header.
283 (defun fasl-header-p (stream &key errorp)
284   (unless (member (stream-element-type stream) '(character base-char))
285     (let ((p (file-position stream)))
286       (unwind-protect
287            (let* ((header *fasl-header-string-start-string*)
288                   (buffer (make-array (length header) :element-type '(unsigned-byte 8)))
289                   (n 0))
290              (flet ((scan ()
291                       (maybe-skip-shebang-line stream)
292                       (setf n (read-sequence buffer stream))))
293                (if errorp
294                    (scan)
295                    (or (ignore-errors (scan))
296                        ;; no a binary input stream
297                        (return-from fasl-header-p nil))))
298              (if (mismatch buffer header
299                            :test #'(lambda (code char) (= code (char-code char))))
300                  ;; Immediate EOF is valid -- we want to match what
301                  ;; CHECK-FASL-HEADER does...
302                  (or (zerop n)
303                      (when errorp
304                        (error 'fasl-header-missing
305                               :stream stream
306                               :fhsss buffer
307                               :expected header)))
308                  t))
309         (file-position stream p)))))
310
311
312 ;;;; LOAD-AS-FASL
313 ;;;;
314 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
315 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
316 ;;;; it's needed not only in the target Lisp, but also in the
317 ;;;; cross-compilation host.
318
319 ;;; a helper function for LOAD-FASL-GROUP
320 ;;;
321 ;;; Return true if we successfully read a FASL header from the stream, or NIL
322 ;;; if EOF was hit before anything except the optional shebang line was read.
323 ;;; Signal an error if we encounter garbage.
324 (defun check-fasl-header (stream)
325   (maybe-skip-shebang-line stream)
326   (let ((byte (read-byte stream nil)))
327     (when byte
328       ;; Read and validate constant string prefix in fasl header.
329       (let* ((fhsss *fasl-header-string-start-string*)
330              (fhsss-length (length fhsss)))
331         (unless (= byte (char-code (schar fhsss 0)))
332           (error 'invalid-fasl-header
333                  :stream stream
334                  :byte-nr 0
335                  :byte byte
336                  :expected (char-code (schar fhsss 0))))
337         (do ((byte (read-byte stream) (read-byte stream))
338              (count 1 (1+ count)))
339             ((= byte +fasl-header-string-stop-char-code+)
340              t)
341           (declare (fixnum byte count))
342           (when (and (< count fhsss-length)
343                      (not (eql byte (char-code (schar fhsss count)))))
344             (error 'invalid-fasl-header
345                    :stream stream
346                    :byte-nr count
347                    :byte byte
348                    :expected (char-code (schar fhsss count))))))
349       ;; Read and validate version-specific compatibility stuff.
350       (flet ((string-from-stream ()
351                (let* ((length (read-unsigned-byte-32-arg))
352                       (result (make-string length)))
353                  (read-string-as-bytes stream result)
354                  result)))
355         ;; Read and validate implementation and version.
356         (let ((implementation (keywordicate (string-from-stream)))
357               (expected-implementation +backend-fasl-file-implementation+))
358           (unless (string= expected-implementation implementation)
359             (error 'invalid-fasl-implementation
360                    :stream stream
361                    :implementation implementation
362                    :expected expected-implementation)))
363         (let* ((fasl-version (read-word-arg))
364                (sbcl-version (if (<= fasl-version 76)
365                                  "1.0.11.18"
366                                  (string-from-stream)))
367                (expected-version (sb!xc:lisp-implementation-version)))
368           (unless (string= expected-version sbcl-version)
369             (restart-case
370                 (error 'invalid-fasl-version
371                        :stream stream
372                        :version sbcl-version
373                        :expected expected-version)
374               (continue () :report "Load the fasl file anyway"))))
375         ;; Read and validate *FEATURES* which affect binary compatibility.
376         (let ((faff-in-this-file (string-from-stream)))
377           (unless (string= faff-in-this-file *features-affecting-fasl-format*)
378             (error 'invalid-fasl-features
379                    :stream stream
380                    :potential-features *features-potentially-affecting-fasl-format*
381                    :expected *features-affecting-fasl-format*
382                    :features faff-in-this-file)))
383         ;; success
384         t))))
385
386 ;; Setting this variable gives you a trace of fops as they are loaded and
387 ;; executed.
388 #!+sb-show
389 (defvar *show-fops-p* nil)
390
391 ;; buffer for loading symbols
392 (defvar *fasl-symbol-buffer*)
393 (declaim (simple-string *fasl-symbol-buffer*))
394
395 ;;;
396 ;;; a helper function for LOAD-AS-FASL
397 ;;;
398 ;;; Return true if we successfully load a group from the stream, or
399 ;;; NIL if EOF was encountered while trying to read from the stream.
400 ;;; Dispatch to the right function for each fop.
401 (defun load-fasl-group (stream)
402   (when (check-fasl-header stream)
403     (catch 'fasl-group-end
404       (let ((*current-fop-table-index* 0)
405             (*skip-until* nil))
406         (declare (special *skip-until*))
407         (loop
408           (let ((byte (read-byte stream)))
409             ;; Do some debugging output.
410             #!+sb-show
411             (when *show-fops-p*
412               (let* ((stack *fop-stack*)
413                      (ptr (1- (fill-pointer *fop-stack*))))
414                 (fresh-line *trace-output*)
415                 ;; The FOP operations are stack based, so it's sorta
416                 ;; logical to display the operand before the operator.
417                 ;; ("reverse Polish notation")
418                 (unless (= ptr -1)
419                   (write-char #\space *trace-output*)
420                   (prin1 (aref stack ptr) *trace-output*)
421                   (terpri *trace-output*))
422                 ;; Display the operator.
423                 (format *trace-output*
424                         "~&~S (#X~X at ~D) (~S)~%"
425                         (aref *fop-names* byte)
426                         byte
427                         (1- (file-position stream))
428                         (svref *fop-funs* byte))))
429
430             ;; Actually execute the fop.
431             (funcall (the function (svref *fop-funs* byte)))))))))
432
433 (defun load-as-fasl (stream verbose print)
434   ;; KLUDGE: ANSI says it's good to do something with the :PRINT
435   ;; argument to LOAD when we're fasloading a file, but currently we
436   ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
437   ;; just disabled that instead of rewriting it.) -- WHN 20000131
438   (declare (ignore print))
439   (when (zerop (file-length stream))
440     (error "attempt to load an empty FASL file:~%  ~S" (namestring stream)))
441   (maybe-announce-load stream verbose)
442   (with-world-lock ()
443     (let* ((*fasl-input-stream* stream)
444            (*fasl-symbol-buffer* (make-string 100))
445            (*current-fop-table* (or (pop *free-fop-tables*) (make-array 1000)))
446            (*current-fop-table-size* (length *current-fop-table*))
447            (*fop-stack* (make-array 100 :fill-pointer 0 :adjustable t)))
448       (unwind-protect
449            (loop while (load-fasl-group stream))
450         (push *current-fop-table* *free-fop-tables*)
451         ;; NIL out the table, so that we don't hold onto garbage.
452         ;;
453         ;; FIXME: Could we just get rid of the free fop table pool so
454         ;; that this would go away?
455         (fill *current-fop-table* nil))))
456   t)
457
458 (declaim (notinline read-byte)) ; Why is it even *declaimed* inline above?
459 \f
460 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
461
462 #|
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)
466
467 (defun clear-counts ()
468   (fill (the simple-vector *fop-counts*) 0)
469   (fill (the simple-vector *fop-times*) 0)
470   t)
471
472 (defun analyze-counts ()
473   (let ((counts ())
474         (total-count 0)
475         (times ())
476         (total-time 0))
477     (macrolet ((breakdown (lvar tvar vec)
478                  `(progn
479                    (dotimes (i 255)
480                      (declare (fixnum i))
481                      (let ((n (svref ,vec i)))
482                        (push (cons (svref *fop-names* i) n) ,lvar)
483                        (incf ,tvar n)))
484                    (setq ,lvar (subseq (sort ,lvar (lambda (x y)
485                                                      (> (cdr x) (cdr y))))
486                                        0 10)))))
487
488       (breakdown counts total-count *fop-counts*)
489       (breakdown times total-time *fop-times*)
490       (format t "Total fop count is ~D~%" total-count)
491       (dolist (c counts)
492         (format t "~30S: ~4D~%" (car c) (cdr c)))
493       (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
494       (dolist (m times)
495         (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))
496 |#
497