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

Last change on this file was 11919, checked in by ehuelsmann, 16 years ago

Separate the precompiler and the file compiler
by giving each its own 'current environment' variable:
introduce *PRECOMPILE-ENV* in precompiler.lisp.

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