0.8.4.28:
[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 *big-compiler-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   (declare (optimize (speed 0)))
58   (do ((res '(fast-read-byte)
59             `(logior (fast-read-byte)
60                      (ash ,res 8)))
61        (cnt 1 (1+ cnt)))
62       ((>= cnt n) res)))
63
64 ;;; like FAST-READ-U-INTEGER, but the size may be determined at run time
65 (defmacro fast-read-var-u-integer (n)
66   (let ((n-pos (gensym))
67         (n-res (gensym))
68         (n-cnt (gensym)))
69     `(do ((,n-pos 8 (+ ,n-pos 8))
70           (,n-cnt (1- ,n) (1- ,n-cnt))
71           (,n-res
72            (fast-read-byte)
73            (dpb (fast-read-byte) (byte 8 ,n-pos) ,n-res)))
74          ((zerop ,n-cnt) ,n-res)
75        (declare (type index ,n-pos ,n-cnt)))))
76
77 ;;; Read a signed integer.
78 (defmacro fast-read-s-integer (n)
79   (declare (optimize (speed 0)))
80   (let ((n-last (gensym)))
81     (do ((res `(let ((,n-last (fast-read-byte)))
82                  (if (zerop (logand ,n-last #x80))
83                      ,n-last
84                      (logior ,n-last #x-100)))
85               `(logior (fast-read-byte)
86                        (ash (the (signed-byte ,(* cnt 8)) ,res) 8)))
87          (cnt 1 (1+ cnt)))
88         ((>= cnt n) res))))
89
90 ;;; Read an N-byte unsigned integer from the *FASL-INPUT-STREAM*
91 (defmacro read-arg (n)
92   (declare (optimize (speed 0)))
93   (if (= n 1)
94       `(the (unsigned-byte 8) (read-byte *fasl-input-stream*))
95       `(prepare-for-fast-read-byte *fasl-input-stream*
96          (prog1
97           (fast-read-u-integer ,n)
98           (done-with-fast-read-byte)))))
99
100 ;;; FIXME: This deserves a more descriptive name, and should probably
101 ;;; be implemented as an ordinary function, not a macro.
102 ;;;
103 ;;; (for the names: There seem to be only two cases, so it could be
104 ;;; named READ-U-INTEGER-8 and READ-U-INTEGER-32 or something.)
105 \f
106 ;;;; the fop table
107
108 ;;; The table is implemented as a simple-vector indexed by the table
109 ;;; offset. We may need to have several, since LOAD can be called
110 ;;; recursively.
111
112 ;;; a list of free fop tables for the fasloader
113 ;;;
114 ;;; FIXME: Is it really a win to have this permanently bound?
115 ;;; Couldn't we just bind it on entry to LOAD-AS-FASL?
116 (defvar *free-fop-tables* (list (make-array 1000)))
117
118 ;;; the current fop table
119 (defvar *current-fop-table*)
120 (declaim (simple-vector *current-fop-table*))
121
122 ;;; the length of the current fop table
123 (defvar *current-fop-table-size*)
124 (declaim (type index *current-fop-table-size*))
125
126 ;;; the index in the fop-table of the next entry to be used
127 (defvar *current-fop-table-index*)
128 (declaim (type index *current-fop-table-index*))
129
130 (defun grow-fop-table ()
131   (let* ((new-size (* *current-fop-table-size* 2))
132          (new-table (make-array new-size)))
133     (declare (fixnum new-size) (simple-vector new-table))
134     (replace new-table (the simple-vector *current-fop-table*))
135     (setq *current-fop-table* new-table)
136     (setq *current-fop-table-size* new-size)))
137
138 (defmacro push-fop-table (thing)
139   (let ((n-index (gensym)))
140     `(let ((,n-index *current-fop-table-index*))
141        (declare (fixnum ,n-index))
142        (when (= ,n-index (the fixnum *current-fop-table-size*))
143          (grow-fop-table))
144        (setq *current-fop-table-index* (1+ ,n-index))
145        (setf (svref *current-fop-table* ,n-index) ,thing))))
146 \f
147 ;;;; the fop stack
148
149 ;;; (This is in a SIMPLE-VECTOR, but it grows down, since it is
150 ;;; somewhat cheaper to test for overflow that way.)
151 (defvar *fop-stack* (make-array 100))
152 (declaim (simple-vector *fop-stack*))
153
154 ;;; the index of the most recently pushed item on the fop stack
155 (defvar *fop-stack-pointer* 100)
156
157 ;;; the current index into the fop stack when we last recursively
158 ;;; entered LOAD
159 (defvar *fop-stack-pointer-on-entry*)
160 (declaim (type index *fop-stack-pointer* *fop-stack-pointer-on-entry*))
161
162 (defun grow-fop-stack ()
163   (let* ((size (length (the simple-vector *fop-stack*)))
164          (new-size (* size 2))
165          (new-stack (make-array new-size)))
166     (declare (fixnum size new-size) (simple-vector new-stack))
167     (replace new-stack (the simple-vector *fop-stack*) :start1 size)
168     (incf *fop-stack-pointer-on-entry* size)
169     (setq *fop-stack-pointer* size)
170     (setq *fop-stack* new-stack)))
171
172 ;;; Cache information about the fop stack in local variables. Define a
173 ;;; local macro to pop from the stack. Push the result of evaluation
174 ;;; if specified.
175 (defmacro with-fop-stack (pushp &body forms)
176   (aver (member pushp '(nil t :nope)))
177   (let ((n-stack (gensym))
178         (n-index (gensym))
179         (n-res (gensym)))
180     `(let ((,n-stack *fop-stack*)
181            (,n-index *fop-stack-pointer*))
182        (declare (simple-vector ,n-stack) (type index ,n-index))
183        (macrolet ((pop-stack ()
184                     `(prog1
185                       (svref ,',n-stack ,',n-index)
186                       (incf ,',n-index)))
187                   (call-with-popped-things (fun n)
188                     (let ((n-start (gensym)))
189                       `(let ((,n-start (+ ,',n-index ,n)))
190                          (declare (type index ,n-start))
191                          (setq ,',n-index ,n-start)
192                          (,fun ,@(make-list n :initial-element
193                                             `(svref ,',n-stack
194                                                     (decf ,n-start))))))))
195          ,(if pushp
196               `(let ((,n-res (progn ,@forms)))
197                  (when (zerop ,n-index)
198                    (grow-fop-stack)
199                    (setq ,n-index *fop-stack-pointer*
200                          ,n-stack *fop-stack*))
201                  (decf ,n-index)
202                  (setq *fop-stack-pointer* ,n-index)
203                  (setf (svref ,n-stack ,n-index) ,n-res))
204               `(prog1
205                 (progn ,@forms)
206                 (setq *fop-stack-pointer* ,n-index)))))))
207 \f
208 ;;;; Conditions signalled on invalid fasls (wrong fasl version, etc),
209 ;;;; so that user code (esp. ASDF) can reasonably handle attempts to
210 ;;;; load such fasls by recompiling them, etc. For simplicity's sake
211 ;;;; make only condition INVALID-FASL part of the public interface,
212 ;;;; and keep the guts internal.
213
214 (define-condition sb!ext::invalid-fasl (error)
215   ((stream :reader invalid-fasl-stream :initarg :stream)
216    (expected :reader invalid-fasl-expected :initarg :expected))
217   (:report
218    (lambda (condition stream)
219      (format stream "~S is an invalid fasl file."
220              (invalid-fasl-stream condition)))))
221
222 (define-condition invalid-fasl-header (sb!ext::invalid-fasl)
223   ((byte :reader invalid-fasl-byte :initarg :byte)
224    (byte-nr :reader invalid-fasl-byte-nr :initarg :byte-nr))
225   (:report
226    (lambda (condition stream)
227      (format stream "~@<~S contains an illegal byte in the FASL header at ~
228                      position ~A: Expected ~A, got ~A.~:@>"
229              (invalid-fasl-stream condition)
230              (invalid-fasl-byte-nr condition)
231              (invalid-fasl-byte condition)
232              (invalid-fasl-expected condition)))))
233
234 (define-condition invalid-fasl-version (sb!ext::invalid-fasl)
235   ((variant :reader invalid-fasl-variant :initarg :variant)
236    (version :reader invalid-fasl-version :initarg :version))
237   (:report
238    (lambda (condition stream)
239      (format stream "~@<~S is in ~A fasl file format version ~W, ~
240                     but this version of SBCL uses format version ~W.~:@>"
241              (invalid-fasl-stream condition)
242              (invalid-fasl-variant condition)
243              (invalid-fasl-version condition)
244              (invalid-fasl-expected condition)))))
245
246 (define-condition invalid-fasl-implementation (sb!ext::invalid-fasl)
247   ((implementation :reader invalid-fasl-implementation
248                    :initarg :implementation))
249   (:report 
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)))))
255
256 (define-condition invalid-fasl-features (sb!ext::invalid-fasl)
257   ((potential-features :reader invalid-fasl-potential-features
258                        :initarg :potential-features)
259    (features :reader invalid-fasl-features :initarg :features))
260   (:report
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.~:>"
266              '*features* 
267              (invalid-fasl-stream condition)
268              (invalid-fasl-potential-features condition)
269              (invalid-fasl-features condition)
270              (invalid-fasl-expected condition)))))
271
272 ;;;; LOAD-AS-FASL
273 ;;;;
274 ;;;; Note: LOAD-AS-FASL is used not only by LOAD, but also (with
275 ;;;; suitable modification of the fop table) in GENESIS. Therefore,
276 ;;;; it's needed not only in the target Lisp, but also in the
277 ;;;; cross-compilation host.
278
279 ;;; a helper function for LOAD-FASL-GROUP
280 ;;;
281 ;;; Return true if we successfully read a FASL header from the stream,
282 ;;; or NIL if EOF was hit before anything was read. Signal an error if
283 ;;; we encounter garbage.
284 (defun check-fasl-header (stream)
285
286   (let ((byte (read-byte stream nil)))
287     (when byte
288
289       ;; Read and validate constant string prefix in fasl header.
290       (let* ((fhsss *fasl-header-string-start-string*)
291              (fhsss-length (length fhsss)))
292         (unless (= byte (char-code (schar fhsss 0)))
293           (error 'invalid-fasl-header
294                  :stream stream
295                  :first-byte-p t
296                  :byte byte
297                  :expected (char-code (schar fhsss 0))))
298         (do ((byte (read-byte stream) (read-byte stream))
299              (count 1 (1+ count)))
300             ((= byte +fasl-header-string-stop-char-code+)
301              t)
302           (declare (fixnum byte count))
303           (when (and (< count fhsss-length)
304                      (not (eql byte (char-code (schar fhsss count)))))
305             (error 'invalid-fasl-header
306                    :stream stream
307                    :byte-nr count
308                    :byte byte
309                    :expected (char-code (schar fhsss count))))))
310
311       ;; Read and validate version-specific compatibility stuff.
312       (flet ((string-from-stream ()
313                (let* ((length (read-arg 4))
314                       (result (make-string length)))
315                  (read-string-as-bytes stream result)
316                  result)))
317         ;; Read and validate implementation and version.
318         (let* ((implementation (keywordicate (string-from-stream)))
319                ;; FIXME: The logic above to read a keyword from the fasl file
320                ;; could probably be shared with the read-a-keyword fop.
321                (version (read-arg 4)))
322           (flet ((check-version (variant
323                                  possible-implementation
324                                  needed-version)
325                    (when (string= possible-implementation implementation)
326                      (or (= version needed-version)
327                          (error 'invalid-fasl-version
328                                 ;; :error :wrong-version
329                                 :stream stream
330                                 :variant variant
331                                 :version version
332                                 :expected needed-version)))))
333             (or (check-version "native code"
334                                +backend-fasl-file-implementation+
335                                +fasl-file-version+)
336                 (error 'invalid-fasl-implementation
337                        :stream stream
338                        :implementation implementation
339                        :expected +backend-fasl-file-implementation+))))
340         ;; Read and validate *FEATURES* which affect binary compatibility.
341         (let ((faff-in-this-file (string-from-stream)))
342           (unless (string= faff-in-this-file *features-affecting-fasl-format*)
343             (error 'invalid-fasl-features
344                    :stream stream
345                    :potential-features *features-potentially-affecting-fasl-format*
346                    :expected *features-affecting-fasl-format*
347                    :features faff-in-this-file)))
348         ;; success
349         t))))
350
351 ;; Setting this variable gives you a trace of fops as they are loaded and
352 ;; executed.
353 #!+sb-show
354 (defvar *show-fops-p* nil)
355
356 ;;; a helper function for LOAD-AS-FASL
357 ;;;
358 ;;; Return true if we successfully load a group from the stream, or
359 ;;; NIL if EOF was encountered while trying to read from the stream.
360 ;;; Dispatch to the right function for each fop. Special-case
361 ;;; FOP-BYTE-PUSH since it is real common.
362 (defun load-fasl-group (stream)
363   (when (check-fasl-header stream)
364     (catch 'fasl-group-end
365       (let ((*current-fop-table-index* 0))
366         (loop
367           (let ((byte (read-byte stream)))
368
369             ;; Do some debugging output.
370             #!+sb-show
371             (when *show-fops-p*
372               (let ((ptr *fop-stack-pointer*)
373                     (stack *fop-stack*))
374                 (fresh-line *trace-output*)
375                 ;; The FOP operations are stack based, so it's sorta
376                 ;; logical to display the operand before the operator.
377                 ;; ("reverse Polish notation")
378                 (unless (= ptr (length stack))
379                   (write-char #\space *trace-output*)
380                   (prin1 (svref stack ptr) *trace-output*)
381                   (terpri *trace-output*))
382                 ;; Display the operator.
383                 (format *trace-output*
384                         "~&~S (#X~X at ~D) (~S)~%"
385                         (svref *fop-names* byte)
386                         byte
387                         (1- (file-position stream))
388                         (svref *fop-funs* byte))))
389
390             ;; Actually execute the fop.
391             (if (eql byte 3)
392               ;; FIXME: This is the special case for FOP-BYTE-PUSH.
393               ;; Benchmark to see whether it's really worth special
394               ;; casing it. If it is, at least express the test in
395               ;; terms of a symbolic name for the FOP-BYTE-PUSH code,
396               ;; not a bare '3' (!). Failing that, remove the special
397               ;; case (and the comment at the head of this function
398               ;; which mentions it).
399               (let ((index *fop-stack-pointer*))
400                 (declare (type index index))
401                 (when (zerop index)
402                   (grow-fop-stack)
403                   (setq index *fop-stack-pointer*))
404                 (decf index)
405                 (setq *fop-stack-pointer* index)
406                 (setf (svref *fop-stack* index)
407                       (svref *current-fop-table* (read-byte stream))))
408               (funcall (the function (svref *fop-funs* byte))))))))))
409
410 (defun load-as-fasl (stream verbose print)
411   ;; KLUDGE: ANSI says it's good to do something with the :PRINT
412   ;; argument to LOAD when we're fasloading a file, but currently we
413   ;; don't. (CMU CL did, but implemented it in a non-ANSI way, and I
414   ;; just disabled that instead of rewriting it.) -- WHN 20000131
415   (declare (ignore print))
416   (when (zerop (file-length stream))
417     (error "attempt to load an empty FASL file:~%  ~S" (namestring stream)))
418   (maybe-announce-load stream verbose)
419   (sb!thread:with-recursive-lock (sb!c::*big-compiler-lock*)
420     (let* ((*fasl-input-stream* stream)
421            (*current-fop-table* (or (pop *free-fop-tables*) (make-array 1000)))
422            (*current-fop-table-size* (length *current-fop-table*))
423            (*fop-stack-pointer-on-entry* *fop-stack-pointer*))
424       (unwind-protect
425            (loop while (load-fasl-group stream))
426         (setq *fop-stack-pointer* *fop-stack-pointer-on-entry*)
427         (push *current-fop-table* *free-fop-tables*)
428         ;; NIL out the stack and table, so that we don't hold onto garbage.
429         ;;
430         ;; FIXME: Couldn't we just get rid of the free fop table pool so
431         ;; that some of this NILing out would go away?
432         (fill *fop-stack* nil :end *fop-stack-pointer-on-entry*)
433         (fill *current-fop-table* nil))))
434   t)
435
436 ;;; This is used in in target-load and also genesis, using
437 ;;; *COLD-FOREIGN-SYMBOL-TABLE*. All the speculative prefix-adding
438 ;;; code for foreign symbol lookup should be here.
439 (defun find-foreign-symbol-in-table (name table)
440   (let ((prefixes
441          #!+(or osf1 sunos linux freebsd darwin) #("" "ldso_stub__")
442          #!+openbsd #("")))
443     (declare (notinline some)) ; to suppress bug 117 bogowarning
444     (some (lambda (prefix)
445             (gethash (concatenate 'string prefix name)
446                      table
447                      nil))
448           prefixes)))
449 \f
450 ;;;; stuff for debugging/tuning by collecting statistics on FOPs (?)
451
452 #|
453 (defvar *fop-counts* (make-array 256 :initial-element 0))
454 (defvar *fop-times* (make-array 256 :initial-element 0))
455 (defvar *print-fops* nil)
456
457 (defun clear-counts ()
458   (fill (the simple-vector *fop-counts*) 0)
459   (fill (the simple-vector *fop-times*) 0)
460   t)
461
462 (defun analyze-counts ()
463   (let ((counts ())
464         (total-count 0)
465         (times ())
466         (total-time 0))
467     (macrolet ((breakdown (lvar tvar vec)
468                  `(progn
469                    (dotimes (i 255)
470                      (declare (fixnum i))
471                      (let ((n (svref ,vec i)))
472                        (push (cons (svref *fop-names* i) n) ,lvar)
473                        (incf ,tvar n)))
474                    (setq ,lvar (subseq (sort ,lvar (lambda (x y)
475                                                      (> (cdr x) (cdr y))))
476                                        0 10)))))
477
478       (breakdown counts total-count *fop-counts*)
479       (breakdown times total-time *fop-times*)
480       (format t "Total fop count is ~D~%" total-count)
481       (dolist (c counts)
482         (format t "~30S: ~4D~%" (car c) (cdr c)))
483       (format t "~%Total fop time is ~D~%" (/ (float total-time) 60.0))
484       (dolist (m times)
485         (format t "~30S: ~6,2F~%" (car m) (/ (float (cdr m)) 60.0))))))
486 |#
487