source: branches/less-reflection/abcl/src/org/armedbear/lisp/compile-file.lisp @ 12630

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

First rough attempt at a fasl classloader to load local functions using new.
Top-level functions are loaded through the same classloader but still using
reflection.

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