fix direct execution of (shebanged) fasls
[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. The offset is kept in at index 0 of the vector.
122 ;;;
123 ;;; FOPs use the table to save stuff, other FOPs refer to the table by
124 ;;; direct indexes via REF-FOP-TABLE.
125
126 (defvar *fop-table*)
127 (declaim (simple-vector *fop-table*))
128
129 (declaim (inline ref-fop-table))
130 (defun ref-fop-table (index)
131   (declare (type index index))
132   (svref *fop-table* (the index (+ index 1))))
133
134 (defun get-fop-table-index ()
135   (svref *fop-table* 0))
136
137 (defun reset-fop-table ()
138   (setf (svref *fop-table* 0) 0))
139
140 (defun push-fop-table (thing)
141   (let* ((table *fop-table*)
142          (index (+ (the index (aref table 0)) 1)))
143     (declare (fixnum index)
144              (simple-vector table))
145     (when (eql index (length table))
146       (setf table (grow-fop-vector table index)
147             *fop-table* table))
148     (setf (aref table 0) index
149           (aref table index) thing)))
150
151 ;;; These three routines are used for both the stack and the table.
152 (defun make-fop-vector (size)
153   (declare (type index size))
154   (let ((vector (make-array size)))
155     (setf (aref vector 0) 0)
156     vector))
157
158 (defun grow-fop-vector (old-vector old-size)
159   (declare (simple-vector old-vector)
160            (type index old-size))
161   (let* ((new-size (* old-size 2))
162          (new-vector (make-array new-size)))
163     (declare (fixnum new-size)
164              (simple-vector new-vector old-vector))
165     (replace new-vector old-vector)
166     (nuke-fop-vector old-vector)
167     new-vector))
168
169 (defun nuke-fop-vector (vector)
170   (declare (simple-vector vector)
171            #!-gencgc (ignore vector)
172            (optimize speed))
173   ;; Make sure we don't keep any garbage.
174   #!+gencgc
175   (fill vector 0))
176
177 \f
178 ;;;; the fop stack
179
180 ;;; Much like the table, this is bound to a simple vector whose first
181 ;;; element is the current index.
182 (defvar *fop-stack*)
183 (declaim (simple-vector *fop-stack*))
184
185 (defun fop-stack-empty-p ()
186   (eql 0 (svref *fop-stack* 0)))
187
188 (defun pop-fop-stack ()
189   (let* ((stack *fop-stack*)
190          (top (svref stack 0)))
191     (declare (type index top))
192     (when (eql 0 top)
193       (error "FOP stack empty"))
194     (setf (svref stack 0) (1- top))
195     (svref stack top)))
196
197 (defun push-fop-stack (value)
198   (let* ((stack *fop-stack*)
199          (next (1+ (the index (svref stack 0)))))
200     (declare (type index next))
201     (when (eql (length stack) next)
202       (setf stack (grow-fop-vector stack next)
203             *fop-stack* stack))
204     (setf (svref stack 0) next
205           (svref stack next) value)))
206
207 ;;; Define a local macro to pop from the stack. Push the result of evaluation
208 ;;; if PUSHP.
209 (defmacro with-fop-stack (pushp &body forms)
210   (aver (member pushp '(nil t :nope)))
211   `(macrolet ((pop-stack ()
212                 `(pop-fop-stack))
213               (push-stack (value)
214                 `(push-fop-stack ,value)))
215      ,(if pushp
216           `(push-fop-stack (progn ,@forms))
217           `(progn ,@forms))))
218
219 ;;; Call FUN with N arguments popped from STACK.
220 (defmacro call-with-popped-args (fun n)
221   ;; N's integer value must be known at macroexpansion time.
222   (declare (type index n))
223   (with-unique-names (n-stack old-top new-top)
224     (let ((argtmps (make-gensym-list n)))
225       `(let* ((,n-stack *fop-stack*)
226               (,old-top (svref ,n-stack 0))
227               (,new-top (- ,old-top ,n))
228               ,@(loop for i from 1 upto n collecting
229                       `(,(nth (1- i) argtmps)
230                         (aref ,n-stack (+ ,new-top ,i)))))
231          (declare (simple-vector ,n-stack))
232          (setf (svref ,n-stack 0) ,new-top)
233         ;; (For some applications it might be appropriate to FILL the
234         ;; popped area with NIL here, to avoid holding onto garbage. For
235         ;; sbcl-0.8.7.something, though, it shouldn't matter, because
236         ;; we're using this only to pop stuff off *FOP-STACK*, and the
237         ;; entire *FOP-STACK* can be GCed as soon as LOAD returns.)
238         (,fun ,@argtmps)))))
239 \f
240 ;;;; Conditions signalled on invalid fasls (wrong fasl version, etc),
241 ;;;; so that user code (esp. ASDF) can reasonably handle attempts to
242 ;;;; load such fasls by recompiling them, etc. For simplicity's sake
243 ;;;; make only condition INVALID-FASL part of the public interface,
244 ;;;; and keep the guts internal.
245
246 (define-condition invalid-fasl (error)
247   ((stream :reader invalid-fasl-stream :initarg :stream)
248    (expected :reader invalid-fasl-expected :initarg :expected))
249   (:report
250    (lambda (condition stream)
251      (format stream "~S is an invalid fasl file."
252              (invalid-fasl-stream condition)))))
253
254 (define-condition invalid-fasl-header (invalid-fasl)
255   ((byte :reader invalid-fasl-byte :initarg :byte)
256    (byte-nr :reader invalid-fasl-byte-nr :initarg :byte-nr))
257   (:report
258    (lambda (condition stream)
259      (format stream "~@<~S contains an illegal byte in the FASL header at ~
260                      position ~A: Expected ~A, got ~A.~:@>"
261              (invalid-fasl-stream condition)
262              (invalid-fasl-byte-nr condition)
263              (invalid-fasl-expected condition)
264              (invalid-fasl-byte condition)))))
265
266 (define-condition invalid-fasl-version (invalid-fasl)
267   ((version :reader invalid-fasl-version :initarg :version))
268   (:report
269    (lambda (condition stream)
270      (format stream "~@<~S is a fasl file compiled with SBCL ~W, and ~
271                       can't be loaded into SBCL ~W.~:@>"
272              (invalid-fasl-stream condition)
273              (invalid-fasl-version condition)
274              (invalid-fasl-expected condition)))))
275
276 (define-condition invalid-fasl-implementation (invalid-fasl)
277   ((implementation :reader invalid-fasl-implementation
278                    :initarg :implementation))
279   (:report
280    (lambda (condition stream)
281      (format stream "~S was compiled for implementation ~A, but this is a ~A."
282              (invalid-fasl-stream condition)
283              (invalid-fasl-implementation condition)
284              (invalid-fasl-expected condition)))))
285
286 (define-condition invalid-fasl-features (invalid-fasl)
287   ((potential-features :reader invalid-fasl-potential-features
288                        :initarg :potential-features)
289    (features :reader invalid-fasl-features :initarg :features))
290   (:report
291    (lambda (condition stream)
292      (format stream "~@<incompatible ~S in fasl file ~S: ~2I~_~
293                      Of features affecting binary compatibility, ~4I~_~S~2I~_~
294                      the fasl has ~4I~_~A,~2I~_~
295                      while the runtime expects ~4I~_~A.~:>"
296              '*features*
297              (invalid-fasl-stream condition)
298              (invalid-fasl-potential-features condition)
299              (invalid-fasl-features condition)
300              (invalid-fasl-expected condition)))))
301
302 ;;; Skips past the shebang line on stream, if any.
303 (defun maybe-skip-shebang-line (stream)
304   (let ((p (file-position stream)))
305     (flet ((next () (read-byte stream nil)))
306       (unwind-protect
307            (when (and (eq (next) (char-code #\#))
308                       (eq (next) (char-code #\!)))
309              (setf p nil)
310              (loop for x = (next)
311                    until (or (not x) (eq x (char-code #\newline)))))
312         (when p
313           (file-position stream p))))
314     t))
315
316 ;;; Returns T if the stream is a binary input stream with a FASL header.
317 (defun fasl-header-p (stream &key errorp)
318   (unless (and (member (stream-element-type stream) '(character base-char))
319                ;; give up if it's not a file stream, or it's an
320                ;; fd-stream but it's either not bivalent or not
321                ;; seekable (doesn't really have a file)
322                (or (not (typep stream 'file-stream))
323                    (and (typep stream 'fd-stream)
324                         (or (not (sb!impl::fd-stream-bivalent-p stream))
325                             (not (sb!impl::fd-stream-file stream))))))
326     (let ((p (file-position stream)))
327       (unwind-protect
328            (let* ((header *fasl-header-string-start-string*)
329                   (buffer (make-array (length header) :element-type '(unsigned-byte 8)))
330                   (n 0))
331              (flet ((scan ()
332                       (maybe-skip-shebang-line stream)
333                       (setf n (read-sequence buffer stream))))
334                (if errorp
335                    (scan)
336                    (or (ignore-errors (scan))
337                        ;; no a binary input stream
338                        (return-from fasl-header-p nil))))
339              (if (mismatch buffer header
340                            :test #'(lambda (code char) (= code (char-code char))))
341                  ;; Immediate EOF is valid -- we want to match what
342                  ;; CHECK-FASL-HEADER does...
343                  (or (zerop n)
344                      (when errorp
345                        (error 'fasl-header-missing
346                               :stream stream
347                               :fhsss buffer
348                               :expected header)))
349                  t))
350         (file-position stream p)))))
351
352
353 ;;;; LOAD-AS-FASL
354 ;;;;
355 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
356 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
357 ;;;; it's needed not only in the target Lisp, but also in the
358 ;;;; cross-compilation host.
359
360 ;;; a helper function for LOAD-FASL-GROUP
361 ;;;
362 ;;; Return true if we successfully read a FASL header from the stream, or NIL
363 ;;; if EOF was hit before anything except the optional shebang line was read.
364 ;;; Signal an error if we encounter garbage.
365 (defun check-fasl-header (stream)
366   (maybe-skip-shebang-line stream)
367   (let ((byte (read-byte stream nil)))
368     (when byte
369       ;; Read and validate constant string prefix in fasl header.
370       (let* ((fhsss *fasl-header-string-start-string*)
371              (fhsss-length (length fhsss)))
372         (unless (= byte (char-code (schar fhsss 0)))
373           (error 'invalid-fasl-header
374                  :stream stream
375                  :byte-nr 0
376                  :byte byte
377                  :expected (char-code (schar fhsss 0))))
378         (do ((byte (read-byte stream) (read-byte stream))
379              (count 1 (1+ count)))
380             ((= byte +fasl-header-string-stop-char-code+)
381              t)
382           (declare (fixnum byte count))
383           (when (and (< count fhsss-length)
384                      (not (eql byte (char-code (schar fhsss count)))))
385             (error 'invalid-fasl-header
386                    :stream stream
387                    :byte-nr count
388                    :byte byte
389                    :expected (char-code (schar fhsss count))))))
390       ;; Read and validate version-specific compatibility stuff.
391       (flet ((string-from-stream ()
392                (let* ((length (read-unsigned-byte-32-arg))
393                       (result (make-string length)))
394                  (read-string-as-bytes stream result)
395                  result)))
396         ;; Read and validate implementation and version.
397         (let ((implementation (keywordicate (string-from-stream)))
398               (expected-implementation +backend-fasl-file-implementation+))
399           (unless (string= expected-implementation implementation)
400             (error 'invalid-fasl-implementation
401                    :stream stream
402                    :implementation implementation
403                    :expected expected-implementation)))
404         (let* ((fasl-version (read-word-arg))
405                (sbcl-version (if (<= fasl-version 76)
406                                  "1.0.11.18"
407                                  (string-from-stream)))
408                (expected-version (sb!xc:lisp-implementation-version)))
409           (unless (string= expected-version sbcl-version)
410             (restart-case
411                 (error 'invalid-fasl-version
412                        :stream stream
413                        :version sbcl-version
414                        :expected expected-version)
415               (continue () :report "Load the fasl file anyway"))))
416         ;; Read and validate *FEATURES* which affect binary compatibility.
417         (let ((faff-in-this-file (string-from-stream)))
418           (unless (string= faff-in-this-file *features-affecting-fasl-format*)
419             (error 'invalid-fasl-features
420                    :stream stream
421                    :potential-features *features-potentially-affecting-fasl-format*
422                    :expected *features-affecting-fasl-format*
423                    :features faff-in-this-file)))
424         ;; success
425         t))))
426
427 ;; Setting this variable gives you a trace of fops as they are loaded and
428 ;; executed.
429 #!+sb-show
430 (defvar *show-fops-p* nil)
431
432 ;;;
433 ;;; a helper function for LOAD-AS-FASL
434 ;;;
435 ;;; Return true if we successfully load a group from the stream, or
436 ;;; NIL if EOF was encountered while trying to read from the stream.
437 ;;; Dispatch to the right function for each fop.
438 (defun load-fasl-group (stream)
439   (when (check-fasl-header stream)
440     (catch 'fasl-group-end
441       (reset-fop-table)
442       (let ((*skip-until* nil))
443         (declare (special *skip-until*))
444         (loop
445           (let ((byte (read-byte stream)))
446             ;; Do some debugging output.
447             #!+sb-show
448             (when *show-fops-p*
449               (let* ((stack *fop-stack*)
450                      (ptr (svref stack 0)))
451                 (fresh-line *trace-output*)
452                 ;; The FOP operations are stack based, so it's sorta
453                 ;; logical to display the operand before the operator.
454                 ;; ("reverse Polish notation")
455                 (unless (= ptr 0)
456                   (write-char #\space *trace-output*)
457                   (prin1 (aref stack ptr) *trace-output*)
458                   (terpri *trace-output*))
459                 ;; Display the operator.
460                 (format *trace-output*
461                         "~&~S (#X~X at ~D) (~S)~%"
462                         (aref *fop-names* byte)
463                         byte
464                         (1- (file-position stream))
465                         (svref *fop-funs* byte))))
466
467             ;; Actually execute the fop.
468             (funcall (the function (svref *fop-funs* byte)))))))))
469
470 (defun load-as-fasl (stream verbose print)
471   ;; KLUDGE: ANSI says it's good to do something with the :PRINT
472   ;; argument to LOAD when we're fasloading a file, but currently we
473   ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
474   ;; just disabled that instead of rewriting it.) -- WHN 20000131
475   (declare (ignore print))
476   (when (zerop (file-length stream))
477     (error "attempt to load an empty FASL file:~%  ~S" (namestring stream)))
478   (maybe-announce-load stream verbose)
479   (let* ((*fasl-input-stream* stream)
480          (*fop-table* (make-fop-vector 1000))
481          (*fop-stack* (make-fop-vector 100)))
482     (unwind-protect
483          (loop while (load-fasl-group stream))
484       ;; Nuke the table and stack to avoid keeping garbage on
485       ;; conservatively collected platforms.
486       (nuke-fop-vector *fop-table*)
487       (nuke-fop-vector *fop-stack*)))
488   t)
489
490 (declaim (notinline read-byte)) ; Why is it even *declaimed* inline above?
491 \f
492 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
493
494 #|
495 (defvar *fop-counts* (make-array 256 :initial-element 0))
496 (defvar *fop-times* (make-array 256 :initial-element 0))
497 (defvar *print-fops* nil)
498
499 (defun clear-counts ()
500   (fill (the simple-vector *fop-counts*) 0)
501   (fill (the simple-vector *fop-times*) 0)
502   t)
503
504 (defun analyze-counts ()
505   (let ((counts ())
506         (total-count 0)
507         (times ())
508         (total-time 0))
509     (macrolet ((breakdown (lvar tvar vec)
510                  `(progn
511                    (dotimes (i 255)
512                      (declare (fixnum i))
513                      (let ((n (svref ,vec i)))
514                        (push (cons (svref *fop-names* i) n) ,lvar)
515                        (incf ,tvar n)))
516                    (setq ,lvar (subseq (sort ,lvar (lambda (x y)
517                                                      (> (cdr x) (cdr y))))
518                                        0 10)))))
519
520       (breakdown counts total-count *fop-counts*)
521       (breakdown times total-time *fop-times*)
522       (format t "Total fop count is ~D~%" total-count)
523       (dolist (c counts)
524         (format t "~30S: ~4D~%" (car c) (cdr c)))
525       (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
526       (dolist (m times)
527         (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))
528 |#
529