source: trunk/abcl/src/org/armedbear/lisp/compile-file.lisp @ 12742

Last change on this file since 12742 was 12742, checked in by astalla, 13 years ago

less-reflection branch merged with trunk. verify-load temporarily disabled.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 32.2 KB
Line 
1;;; compile-file.lisp
2;;;
3;;; Copyright (C) 2004-2006 Peter Graves
4;;; $Id: compile-file.lisp 12742 2010-06-07 18:30:36Z astalla $
5;;;
6;;; This program is free software; you can redistribute it and/or
7;;; modify it under the terms of the GNU General Public License
8;;; as published by the Free Software Foundation; either version 2
9;;; of the License, or (at your option) any later version.
10;;;
11;;; This program is distributed in the hope that it will be useful,
12;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
13;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14;;; GNU General Public License for more details.
15;;;
16;;; You should have received a copy of the GNU General Public License
17;;; along with this program; if not, write to the Free Software
18;;; Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA  02111-1307, USA.
19;;;
20;;; As a special exception, the copyright holders of this library give you
21;;; permission to link this library with independent modules to produce an
22;;; executable, regardless of the license terms of these independent
23;;; modules, and to copy and distribute the resulting executable under
24;;; terms of your choice, provided that you also meet, for each linked
25;;; independent module, the terms and conditions of the license of that
26;;; module.  An independent module is a module which is not derived from
27;;; or based on this library.  If you modify this library, you may extend
28;;; this exception to your version of the library, but you are not
29;;; obligated to do so.  If you do not wish to do so, delete this
30;;; exception statement from your version.
31
32(in-package #:system)
33
34(require "JVM")
35;; (require "COMPILER-ERROR") already made accessible through JVM
36
37(defvar *fbound-names*)
38
39(defvar *class-number*)
40
41(defvar *output-file-pathname*)
42
43(defun base-classname (&optional (output-file-pathname *output-file-pathname*))
44  (sanitize-class-name (pathname-name output-file-pathname)))
45
46(defun fasl-loader-classname (&optional (output-file-pathname *output-file-pathname*))
47  (%format nil "~A_0" (base-classname output-file-pathname)))
48
49(declaim (ftype (function (t) t) compute-classfile-name))
50(defun compute-classfile-name (n &optional (output-file-pathname
51                                            *output-file-pathname*))
52  "Computes the name of the class file associated with number `n'."
53  (let ((name
54         (sanitize-class-name
55    (%format nil "~A_~D" (pathname-name output-file-pathname) n))))
56    (namestring (merge-pathnames (make-pathname :name name :type "cls")
57                                 output-file-pathname))))
58
59(defun sanitize-class-name (name)
60  (let ((name (copy-seq name)))
61    (dotimes (i (length name))
62      (declare (type fixnum i))
63      (when (or (char= (char name i) #\-)
64    (char= (char name i) #\.)
65    (char= (char name i) #\Space))
66        (setf (char name i) #\_)))
67    name))
68 
69
70(declaim (ftype (function () t) next-classfile-name))
71(defun next-classfile-name ()
72  (compute-classfile-name (incf *class-number*)))
73
74(defmacro report-error (&rest forms)
75  `(handler-case (progn ,@forms)
76     (compiler-unsupported-feature-error (condition)
77       (fresh-line)
78       (%format t "; UNSUPPORTED-FEATURE: ~A~%" condition)
79       (values nil condition))))
80
81;; Dummy function. Should never be called.
82(defun dummy (&rest ignored)
83  (declare (ignore ignored))
84  (assert nil))
85
86(declaim (ftype (function (t) t) verify-load))
87(defun verify-load (classfile)
88  #|(if (> *safety* 0)
89      (and classfile
90         (let ((*load-truename* *output-file-pathname*))
91           (report-error
92            (load-compiled-function classfile))))
93    t)|#
94  (declare (ignore classfile))
95  t)
96
97(declaim (ftype (function (t) t) process-defconstant))
98(defun process-defconstant (form)
99  ;; "If a DEFCONSTANT form appears as a top level form, the compiler
100  ;; must recognize that [the] name names a constant variable. An
101  ;; implementation may choose to evaluate the value-form at compile
102  ;; time, load time, or both. Therefore, users must ensure that the
103  ;; initial-value can be evaluated at compile time (regardless of
104  ;; whether or not references to name appear in the file) and that
105  ;; it always evaluates to the same value."
106  (eval form)
107  (output-form form))
108
109(declaim (ftype (function (t) t) note-toplevel-form))
110(defun note-toplevel-form (form)
111  (when *compile-print*
112    (fresh-line)
113    (princ "; ")
114    (let ((*print-length* 2)
115          (*print-level* 2)
116          (*print-pretty* nil))
117      (prin1 form))
118    (terpri)))
119
120(declaim (ftype (function (t stream t) t) process-toplevel-form))
121(defun process-toplevel-form (form stream compile-time-too)
122  (if (atom form)
123      (when compile-time-too
124        (eval form))
125    (progn
126      (let ((operator (%car form)))
127        (case operator
128          (MACROLET
129           (process-toplevel-macrolet form stream compile-time-too)
130           (return-from process-toplevel-form))
131          ((IN-PACKAGE DEFPACKAGE)
132           (note-toplevel-form form)
133           (setf form (precompiler:precompile-form form nil *compile-file-environment*))
134           (eval form)
135           ;; Force package prefix to be used when dumping form.
136           (let ((*package* +keyword-package+))
137             (output-form form))
138           (return-from process-toplevel-form))
139          ((DEFVAR DEFPARAMETER)
140           (note-toplevel-form form)
141           (if compile-time-too
142               (eval form)
143               ;; "If a DEFVAR or DEFPARAMETER form appears as a top level form,
144               ;; the compiler must recognize that the name has been proclaimed
145               ;; special. However, it must neither evaluate the initial-value
146               ;; form nor assign the dynamic variable named NAME at compile
147               ;; time."
148               (let ((name (second form)))
149                 (%defvar name))))
150          (DEFCONSTANT
151           (note-toplevel-form form)
152           (process-defconstant form)
153           (return-from process-toplevel-form))
154          (DEFUN
155           (note-toplevel-form form)
156           (let* ((name (second form))
157                  (block-name (fdefinition-block-name name))
158                  (lambda-list (third form))
159                  (body (nthcdr 3 form)))
160             (jvm::with-saved-compiler-policy
161               (multiple-value-bind (body decls doc)
162                   (parse-body body)
163                 (let* ((expr `(lambda ,lambda-list
164                                 ,@decls (block ,block-name ,@body)))
165      (saved-class-number *class-number*)
166                        (classfile (next-classfile-name))
167                        (internal-compiler-errors nil)
168                        (result (with-open-file
169            (f classfile
170               :direction :output
171               :element-type '(unsigned-byte 8)
172               :if-exists :supersede)
173                                  (handler-bind 
174                                      ((internal-compiler-error
175                                        #'(lambda (e)
176                                            (push e internal-compiler-errors)
177                                            (continue))))
178                                    (report-error
179                                     (jvm:compile-defun name expr nil
180                                                        classfile f nil)))))
181                        (compiled-function (if (not internal-compiler-errors)
182                                               (verify-load classfile)
183                                               nil)))
184       (declare (ignore result))
185                   (cond
186                     ((and (not internal-compiler-errors)
187                           compiled-function)
188                      (setf form
189                            `(fset ',name
190           (sys::get-fasl-function *fasl-loader*
191                 ,saved-class-number)
192                                   ,*source-position*
193                                   ',lambda-list
194                                   ,doc))
195                      (when compile-time-too
196                        (fset name compiled-function)))
197                     (t
198                      ;; Add this warning when the stock ABCL compiles
199                      ;; again, as all warnings in COMPILE-SYSTEM
200                      ;; produce a non-zero exit status that stops
201                      ;; build.xml in its tracks.
202                      #+nil
203                      (compiler-warn "Unable to compile function ~A.  Using interpreted form instead.~%" name)
204                      (format *error-output*
205                              "; Unable to compile function ~A.  Using interpreted form instead.~%" name)
206                      (when internal-compiler-errors
207                        (dolist (e internal-compiler-errors)
208                          (format *error-output*
209                                  "; ~A~%" e)))
210                      (let ((precompiled-function
211                             (precompiler:precompile-form expr nil
212                                              *compile-file-environment*)))
213                        (setf form
214                              `(fset ',name
215                                     ,precompiled-function
216                                     ,*source-position*
217                                     ',lambda-list
218                                     ,doc)))
219                      (when compile-time-too
220                        (eval form)))))
221                 (when (and (symbolp name) (eq (get name '%inline) 'INLINE))
222                 ;; FIXME Need to support SETF functions too!
223                   (setf (inline-expansion name)
224                         (jvm::generate-inline-expansion block-name
225                                                         lambda-list body))
226                   (output-form `(setf (inline-expansion ',name)
227                                       ',(inline-expansion name))))))
228             (push name jvm::*functions-defined-in-current-file*)
229             (note-name-defined name)
230             ;; If NAME is not fbound, provide a dummy definition so that
231             ;; getSymbolFunctionOrDie() will succeed when we try to verify that
232             ;; functions defined later in the same file can be loaded correctly.
233             (unless (fboundp name)
234               (setf (fdefinition name) #'dummy)
235               (push name *fbound-names*))))
236          ((DEFGENERIC DEFMETHOD)
237           (note-toplevel-form form)
238           (note-name-defined (second form))
239           (let ((*compile-print* nil))
240             (process-toplevel-form (macroexpand-1 form *compile-file-environment*)
241                                    stream compile-time-too))
242             (return-from process-toplevel-form))
243          (DEFMACRO
244           (note-toplevel-form form)
245           (let ((name (second form)))
246             (eval form)
247             (let* ((expr (function-lambda-expression (macro-function name)))
248        (saved-class-number *class-number*)
249                    (classfile (next-classfile-name)))
250         (with-open-file
251       (f classfile
252          :direction :output
253          :element-type '(unsigned-byte 8)
254          :if-exists :supersede)
255     (ignore-errors
256       (jvm:compile-defun nil expr nil classfile f nil)))
257               (if (null (verify-load classfile))
258                   ;; FIXME error or warning
259                   (format *error-output* "; Unable to compile macro ~A~%" name)
260                 (progn
261                   (setf form
262                         (if (special-operator-p name)
263                             `(put ',name 'macroexpand-macro
264                                   (make-macro ',name
265                 (sys::get-fasl-function *fasl-loader* ,saved-class-number)))
266                             `(fset ',name
267                                    (make-macro ',name
268            (sys::get-fasl-function *fasl-loader* ,saved-class-number))
269                                    ,*source-position*
270                                    ',(third form)))))))))
271          (DEFTYPE
272           (note-toplevel-form form)
273           (eval form))
274          (EVAL-WHEN
275           (multiple-value-bind (ct lt e)
276               (parse-eval-when-situations (cadr form))
277             (let ((new-compile-time-too (or ct (and compile-time-too e)))
278                   (body (cddr form)))
279               (if lt
280                   (process-toplevel-progn body stream new-compile-time-too)
281                 (when new-compile-time-too
282                   (eval `(progn ,@body)))))
283           (return-from process-toplevel-form)))
284          (LOCALLY
285           ;; FIXME Need to handle special declarations too!
286           (jvm::with-saved-compiler-policy
287             (multiple-value-bind (forms decls)
288                 (parse-body (cdr form) nil)
289               (process-optimization-declarations decls)
290               (let* ((jvm::*visible-variables* jvm::*visible-variables*)
291                      (specials (jvm::process-declarations-for-vars (cdr form)
292                                                                    nil nil)))
293                 (dolist (special specials)
294                   (push special jvm::*visible-variables*))
295                 (process-toplevel-progn forms stream compile-time-too))
296               (return-from process-toplevel-form))))
297          (PROGN
298           (process-toplevel-progn (cdr form) stream compile-time-too)
299           (return-from process-toplevel-form))
300          (DECLARE
301           (compiler-style-warn "Misplaced declaration: ~S" form))
302          (t
303           (when (and (symbolp operator)
304                      (macro-function operator *compile-file-environment*))
305             (note-toplevel-form form)
306             ;; Note that we want MACROEXPAND-1 and not MACROEXPAND here, in
307             ;; case the form being expanded expands into something that needs
308             ;; special handling by PROCESS-TOPLEVEL-FORM (e.g. DEFMACRO).
309             (let ((*compile-print* nil))
310               (process-toplevel-form (macroexpand-1 form *compile-file-environment*)
311                                      stream compile-time-too))
312             (return-from process-toplevel-form))
313
314           (cond ((eq operator 'QUOTE)
315;;;                      (setf form (precompiler:precompile-form form nil
316;;;                                                  *compile-file-environment*))
317                  (when compile-time-too
318                    (eval form))
319                  (return-from process-toplevel-form))
320                 ((eq operator 'PUT)
321                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
322                 ((eq operator 'COMPILER-DEFSTRUCT)
323                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
324                 ((eq operator 'PROCLAIM)
325                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
326                 ((and (memq operator '(EXPORT REQUIRE PROVIDE SHADOW))
327                       (or (keywordp (second form))
328                           (and (listp (second form))
329                                (eq (first (second form)) 'QUOTE))))
330                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
331                 ((eq operator 'IMPORT)
332                  (setf form (precompiler:precompile-form form nil *compile-file-environment*))
333                  ;; Make sure package prefix is printed when symbols are imported.
334                  (let ((*package* +keyword-package+))
335                    (output-form form))
336                  (when compile-time-too
337                    (eval form))
338                  (return-from process-toplevel-form))
339                 ((and (eq operator '%SET-FDEFINITION)
340                       (eq (car (second form)) 'QUOTE)
341                       (consp (third form))
342                       (eq (%car (third form)) 'FUNCTION)
343                       (symbolp (cadr (third form))))
344                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
345;;;                     ((memq operator '(LET LET*))
346;;;                      (let ((body (cddr form)))
347;;;                        (if (dolist (subform body nil)
348;;;                              (when (and (consp subform) (eq (%car subform) 'DEFUN))
349;;;                                (return t)))
350;;;                            (setf form (convert-toplevel-form form))
351;;;                            (setf form (precompiler:precompile-form form nil)))))
352                 ((eq operator 'mop::ensure-method)
353                  (setf form (convert-ensure-method form)))
354                 ((and (symbolp operator)
355                       (not (special-operator-p operator))
356                       (null (cdr form)))
357                  (setf form (precompiler:precompile-form form nil *compile-file-environment*)))
358                 (t
359;;;                      (setf form (precompiler:precompile-form form nil))
360                  (note-toplevel-form form)
361                  (setf form (convert-toplevel-form form nil)))))))))
362  (when (consp form)
363    (output-form form))
364  ;; Make sure the compiled-function loader knows where
365  ;; to load the compiled functions. Note that this trickery
366  ;; was already used in verify-load before I used it,
367  ;; however, binding *load-truename* isn't fully compliant, I think.
368  (when compile-time-too
369    (let ((*load-truename* *output-file-pathname*)
370    (*fasl-loader* (make-fasl-class-loader
371        *class-number*
372        (concatenate 'string "org.armedbear.lisp." (base-classname))
373        nil)))
374      (eval form))))
375
376(declaim (ftype (function (t) t) convert-ensure-method))
377(defun convert-ensure-method (form)
378  (c-e-m-1 form :function)
379  (c-e-m-1 form :fast-function)
380  (precompiler:precompile-form form nil *compile-file-environment*))
381
382(declaim (ftype (function (t t) t) c-e-m-1))
383(defun c-e-m-1 (form key)
384  (let* ((tail (cddr form))
385         (function-form (getf tail key)))
386    (when (and function-form (consp function-form)
387               (eq (%car function-form) 'FUNCTION))
388      (let ((lambda-expression (cadr function-form)))
389        (jvm::with-saved-compiler-policy
390          (let* ((saved-class-number *class-number*)
391     (classfile (next-classfile-name))
392                 (result
393      (with-open-file
394          (f classfile
395       :direction :output
396       :element-type '(unsigned-byte 8)
397       :if-exists :supersede)
398        (report-error
399         (jvm:compile-defun nil lambda-expression nil classfile f nil))))
400                 (compiled-function (verify-load classfile)))
401      (declare (ignore result))
402            (cond (compiled-function
403                   (setf (getf tail key)
404       `(sys::get-fasl-function *fasl-loader* ,saved-class-number)))
405;;                         `(load-compiled-function ,(file-namestring classfile))))
406                  (t
407                   ;; FIXME This should be a warning or error of some sort...
408                   (format *error-output* "; Unable to compile method~%")))))))))
409
410(declaim (ftype (function (t) t) simple-toplevel-form-p))
411(defun simple-toplevel-form-p (form)
412  "Returns NIL if the form is too complex to become an
413interpreted toplevel form, non-NIL if it is 'simple enough'."
414  (and (consp form)
415             (every #'(lambda (arg)
416                        (or (and (atom arg)
417                                 (not (and (symbolp arg)
418                                           (symbol-macro-p arg))))
419                            (and (consp arg)
420                                 (eq 'QUOTE (car arg)))))
421              (cdr form))))
422
423(declaim (ftype (function (t t) t) convert-toplevel-form))
424(defun convert-toplevel-form (form declare-inline)
425  (when (or (simple-toplevel-form-p form)
426            (and (eq (car form) 'SETQ)
427                 ;; for SETQ, look at the evaluated part
428                 (simple-toplevel-form-p (third form))))
429    ;; single form with simple or constant arguments
430    ;; Without this exception, toplevel function calls
431    ;; will be compiled into lambdas which get compiled to
432    ;; compiled-functions. Those need to be loaded.
433    ;; Conclusion: Top level interpreting the function call
434    ;;  and its arguments may be (and should be) more efficient.
435    (return-from convert-toplevel-form
436      (precompiler:precompile-form form nil *compile-file-environment*)))
437  (let* ((expr `(lambda () ,form))
438   (saved-class-number *class-number*)
439         (classfile (next-classfile-name))
440         (result
441    (with-open-file
442        (f classfile
443     :direction :output
444     :element-type '(unsigned-byte 8)
445     :if-exists :supersede)
446      (report-error (jvm:compile-defun nil expr nil classfile
447                                             f declare-inline))))
448         (compiled-function (verify-load classfile)))
449    (declare (ignore result))
450    (setf form
451          (if compiled-function
452              `(funcall (sys::get-fasl-function *fasl-loader* ,saved-class-number))
453              (precompiler:precompile-form form nil *compile-file-environment*)))))
454
455
456(defun process-toplevel-macrolet (form stream compile-time-too)
457  (let ((*compile-file-environment* (make-environment *compile-file-environment*)))
458    (dolist (definition (cadr form))
459      (environment-add-macro-definition *compile-file-environment*
460                                        (car definition)
461                                        (make-macro (car definition)
462                                                    (make-expander-for-macrolet definition))))
463    (dolist (body-form (cddr form))
464      (process-toplevel-form body-form stream compile-time-too))))
465
466(declaim (ftype (function (t stream t) t) process-toplevel-progn))
467(defun process-toplevel-progn (forms stream compile-time-too)
468  (dolist (form forms)
469    (process-toplevel-form form stream compile-time-too)))
470
471;;; Adapted from SBCL.
472;;; Parse an EVAL-WHEN situations list, returning three flags,
473;;; (VALUES COMPILE-TOPLEVEL LOAD-TOPLEVEL EXECUTE), indicating
474;;; the types of situations present in the list.
475(defun parse-eval-when-situations (situations)
476  (when (or (not (listp situations))
477      (set-difference situations
478          '(:compile-toplevel
479            compile
480            :load-toplevel
481            load
482            :execute
483            eval)))
484    (error "Bad EVAL-WHEN situation list: ~S." situations))
485  (values (intersection '(:compile-toplevel compile) situations)
486    (intersection '(:load-toplevel load) situations)
487    (intersection '(:execute eval) situations)))
488
489
490(defvar *binary-fasls* nil)
491(defvar *forms-for-output* nil)
492(defvar *fasl-stream* nil)
493
494(defun output-form (form)
495  (if *binary-fasls*
496      (push form *forms-for-output*)
497      (progn
498        (dump-form form *fasl-stream*)
499        (%stream-terpri *fasl-stream*))))
500
501(defun finalize-fasl-output ()
502  (when *binary-fasls*
503    (let ((*package* (find-package :keyword))
504          (*double-colon-package-separators* T))
505      (dump-form (convert-toplevel-form (list* 'PROGN
506                                               (nreverse *forms-for-output*))
507                                        t)
508                 *fasl-stream*))
509    (%stream-terpri *fasl-stream*)))
510
511(defun compile-file (input-file
512                     &key
513                     output-file
514                     ((:verbose *compile-verbose*) *compile-verbose*)
515                     ((:print *compile-print*) *compile-print*)
516                     external-format)
517  (declare (ignore external-format))    ; FIXME
518  (unless (or (and (probe-file input-file) (not (file-directory-p input-file)))
519              (pathname-type input-file))
520    (let ((pathname (merge-pathnames (make-pathname :type "lisp") input-file)))
521      (when (probe-file pathname)
522        (setf input-file pathname))))
523  (setf output-file (if output-file
524                        (merge-pathnames output-file *default-pathname-defaults*)
525                        (compile-file-pathname input-file)))
526  (let* ((*output-file-pathname* output-file)
527         (type (pathname-type output-file))
528         (temp-file (merge-pathnames (make-pathname :type (concatenate 'string type "-tmp"))
529                                     output-file))
530         (temp-file2 (merge-pathnames (make-pathname :type (concatenate 'string type "-tmp2"))
531                                     output-file))
532         (warnings-p nil)
533         (failure-p nil))
534    (with-open-file (in input-file :direction :input)
535      (let* ((*compile-file-pathname* (pathname in))
536             (*compile-file-truename* (truename in))
537             (*source* *compile-file-truename*)
538             (*class-number* 0)
539             (namestring (namestring *compile-file-truename*))
540             (start (get-internal-real-time))
541             elapsed
542             *fasl-uninterned-symbols*)
543        (when *compile-verbose*
544          (format t "; Compiling ~A ...~%" namestring))
545        (with-compilation-unit ()
546          (with-open-file (out temp-file
547                               :direction :output :if-exists :supersede
548                               :external-format *fasl-external-format*)
549            (let ((*readtable* *readtable*)
550                  (*read-default-float-format* *read-default-float-format*)
551                  (*read-base* *read-base*)
552                  (*package* *package*)
553                  (jvm::*functions-defined-in-current-file* '())
554                  (*fbound-names* '())
555                  (*fasl-stream* out)
556                  *forms-for-output*)
557              (jvm::with-saved-compiler-policy
558                (jvm::with-file-compilation
559                    (handler-bind ((style-warning 
560                                    #'(lambda (c)
561                                        (setf warnings-p t)
562                                        ;; let outer handlers do their thing
563                                        (signal c)
564                                        ;; prevent the next handler
565                                        ;; from running: we're a
566                                        ;; WARNING subclass
567                                        (continue)))
568                                   ((or warning 
569                                        compiler-error)
570                                    #'(lambda (c)
571                                        (declare (ignore c))
572                                        (setf warnings-p t
573                                              failure-p t))))
574                      (loop
575                         (let* ((*source-position* (file-position in))
576                                (jvm::*source-line-number* (stream-line-number in))
577                                (form (read in nil in))
578                                (*compiler-error-context* form))
579                           (when (eq form in)
580                             (return))
581                           (process-toplevel-form form out nil))))
582                    (finalize-fasl-output)
583                    (dolist (name *fbound-names*)
584                      (fmakunbound name)))))))
585        (with-open-file (in temp-file :direction :input)
586          (with-open-file (out temp-file2 :direction :output
587                               :if-does-not-exist :create
588                               :if-exists :supersede)
589            ;; write header
590            (write "; -*- Mode: Lisp -*-" :escape nil :stream out)
591            (%stream-terpri out)
592            (let ((*package* (find-package '#:cl)))
593              (write (list 'init-fasl :version *fasl-version*)
594                     :stream out)
595              (%stream-terpri out)
596              (write (list 'setq '*source* *compile-file-truename*)
597                     :stream out)
598              (%stream-terpri out)
599        ;; Note: Beyond this point, you can't use DUMP-FORM,
600        ;; because the list of uninterned symbols has been fixed now.
601        (when *fasl-uninterned-symbols*
602    (write (list 'setq '*fasl-uninterned-symbols*
603           (coerce (mapcar #'car
604               (nreverse *fasl-uninterned-symbols*))
605             'vector))
606           :stream out))
607        (%stream-terpri out)
608
609        (when (> *class-number* 0)
610    (generate-loader-function)
611    (write (list 'setq '*fasl-loader*
612           `(sys::make-fasl-class-loader
613             ,*class-number*
614             ,(concatenate 'string "org.armedbear.lisp." (base-classname)))) :stream out))
615              (%stream-terpri out))
616
617
618            ;; copy remaining content
619            (loop for line = (read-line in nil :eof)
620               while (not (eq line :eof))
621               do (write-line line out))))
622        (delete-file temp-file)
623  (remove-zip-cache-entry output-file) ;; Necessary under windows
624        (rename-file temp-file2 output-file)
625
626        (when *compile-file-zip*
627          (let* ((type ;; Don't use ".zip", it'll result in an extension
628                  ;;  with a dot, which is rejected by NAMESTRING
629                  (%format nil "~A~A" (pathname-type output-file) "-zip"))
630                 (zipfile (namestring
631                           (merge-pathnames (make-pathname :type type)
632                                            output-file)))
633                 (pathnames nil)
634     (fasl-loader (namestring (merge-pathnames (make-pathname :name (fasl-loader-classname) :type "cls")
635                 output-file))))
636      (when (probe-file fasl-loader)
637        (push fasl-loader pathnames))
638            (dotimes (i *class-number*)
639              (let* ((pathname (compute-classfile-name (1+ i))))
640                (when (probe-file pathname)
641                  (push pathname pathnames))))
642            (setf pathnames (nreverse pathnames))
643            (let ((load-file (merge-pathnames (make-pathname :type "_")
644                                              output-file)))
645              (rename-file output-file load-file)
646              (push load-file pathnames))
647            (zip zipfile pathnames)
648            (dolist (pathname pathnames)
649              (let ((truename (probe-file pathname)))
650                (when truename
651                  (delete-file truename))))
652            (rename-file zipfile output-file)))
653
654        (setf elapsed (/ (- (get-internal-real-time) start) 1000.0))
655        (when *compile-verbose*
656          (format t "~&; Wrote ~A (~A seconds)~%"
657                  (namestring output-file) elapsed))))
658    (values (truename output-file) warnings-p failure-p)))
659
660(defmacro ncase (expr min max &rest clauses)
661  "A CASE where all test clauses are numbers ranging from a minimum to a maximum."
662  ;;Expr is subject to multiple evaluation, but since we only use ncase for
663  ;;fn-index below, let's ignore it.
664  (let* ((half (floor (/ (- max min) 2)))
665   (middle (+ min half)))
666    (if (> (- max min) 10)
667  `(if (< ,expr ,middle)
668       (ncase ,expr ,min ,middle ,@(subseq clauses 0 half))
669       (ncase ,expr ,middle ,max ,@(subseq clauses half)))
670  `(case ,expr ,@clauses))))
671
672(defun generate-loader-function ()
673  (let* ((basename (base-classname))
674   (expr `(lambda (fasl-loader fn-index)
675      (identity fasl-loader) ;;to avoid unused arg
676      (ncase fn-index 0 ,(1- *class-number*)
677        ,@(loop
678       :for i :from 1 :to *class-number*
679       :collect
680       (let ((class (%format nil "org/armedbear/lisp/~A_~A" basename i)))
681         `(,(1- i)
682            (jvm::with-inline-code ()
683        (jvm::emit 'jvm::aload 1)
684        (jvm::emit-invokevirtual jvm::+lisp-object-class+ "javaInstance"
685               nil jvm::+java-object+)
686        (jvm::emit 'jvm::checkcast "org/armedbear/lisp/FaslClassLoader")
687        (jvm::emit 'jvm::dup)
688        (jvm::emit-push-constant-int ,(1- i))
689        (jvm::emit 'jvm::new ,class)
690        (jvm::emit 'jvm::dup)
691        (jvm::emit-invokespecial-init ,class '())
692        (jvm::emit-invokevirtual "org/armedbear/lisp/FaslClassLoader" "putFunction"
693               (list "I" jvm::+lisp-object+) jvm::+lisp-object+)
694        (jvm::emit 'jvm::pop))
695            t))))))
696   (classname (fasl-loader-classname))
697   (classfile (namestring (merge-pathnames (make-pathname :name classname :type "cls")
698             *output-file-pathname*))))
699    (jvm::with-saved-compiler-policy
700  (jvm::with-file-compilation
701      (with-open-file
702    (f classfile
703       :direction :output
704       :element-type '(unsigned-byte 8)
705       :if-exists :supersede)
706        (jvm:compile-defun nil expr nil
707         classfile f nil))))))
708
709(defun compile-file-if-needed (input-file &rest allargs &key force-compile
710                               &allow-other-keys)
711  (setf input-file (truename input-file))
712  (cond (force-compile
713         (remf allargs :force-compile)
714         (apply 'compile-file input-file allargs))
715        (t
716         (let* ((source-write-time (file-write-date input-file))
717                (output-file       (or (getf allargs :output-file)
718                                       (compile-file-pathname input-file)))
719                (target-write-time (and (probe-file output-file)
720                                        (file-write-date output-file))))
721           (if (or (null target-write-time)
722                   (<= target-write-time source-write-time))
723               (apply 'compile-file input-file allargs)
724               output-file)))))
725
726(provide 'compile-file)
Note: See TracBrowser for help on using the repository browser.