source: branches/0.19.x/abcl/src/org/armedbear/lisp/compile-file.lisp

Last change on this file was 12484, checked in by Mark Evenson, 15 years ago

Fix bug in loading fasls with "." in NAME of pathname.

Perform the same transformation in the load portion init FASL as
COMPUTE-CLASSFILE-NAME did in creating the files..

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