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

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

Use PROCESS-DECLARATIONS-FOR-VARS in compile-file.lisp.

Rationale: Use package internals which return the required information,
so that we don't need to create it ourselves.

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