source: trunk/abcl/src/org/armedbear/lisp/jvm.lisp @ 11898

Last change on this file since 11898 was 11898, checked in by ehuelsmann, 14 years ago

Revert r11892 and r11896 because they keep causing breakage
in different places.

We need general infrastructure for this problem. To come.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 16.9 KB
Line 
1;;; jvm.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves
4;;; $Id: jvm.lisp 11898 2009-05-18 21:21:02Z 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., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, 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 "JVM")
33
34(export '(compile-defun *catch-errors* jvm-compile jvm-compile-package
35          derive-compiler-type))
36
37(eval-when (:compile-toplevel :load-toplevel :execute)
38  (require "LOOP")
39  (require "FORMAT")
40  (require "CLOS")
41  (require "PRINT-OBJECT")
42  (require "COMPILER-TYPES")
43  (require "KNOWN-FUNCTIONS")
44  (require "KNOWN-SYMBOLS")
45  (require "DUMP-FORM")
46  (require "OPCODES")
47  (require "JAVA")
48  (require "COMPILER-PASS1")
49  (require "COMPILER-PASS2"))
50
51(defvar *closure-variables* nil)
52
53(defvar *enable-dformat* nil)
54
55#+nil
56(defun dformat (destination control-string &rest args)
57  (when *enable-dformat*
58    (apply #'sys::%format destination control-string args)))
59
60(defmacro dformat (&rest ignored)
61  (declare (ignore ignored)))
62
63
64(defmacro with-saved-compiler-policy (&body body)
65  "Saves compiler policy variables, restoring them after evaluating `body'."
66  `(let ((*speed* *speed*)
67         (*space* *space*)
68         (*safety* *safety*)
69         (*debug* *debug*)
70         (*explain* *explain*)
71         (*inline-declarations* *inline-declarations*))
72     ,@body))
73
74
75
76(defvar *compiler-debug* nil)
77
78(defvar *pool* nil)
79(defvar *pool-count* 1)
80(defvar *pool-entries* nil)
81(defvar *fields* ())
82(defvar *static-code* ())
83
84(defvar *declared-symbols* nil)
85(defvar *declared-functions* nil)
86(defvar *declared-strings* nil)
87(defvar *declared-integers* nil)
88(defvar *declared-floats* nil)
89(defvar *declared-doubles* nil)
90
91(defstruct (class-file (:constructor %make-class-file))
92  pathname ; pathname of output file
93  lambda-name
94  class
95  superclass
96  lambda-list ; as advertised
97  pool
98  (pool-count 1)
99  (pool-entries (make-hash-table :test #'equal))
100  fields
101  methods
102  static-code
103  (symbols (make-hash-table :test 'eq))
104  (functions (make-hash-table :test 'equal))
105  (strings (make-hash-table :test 'eq))
106  (integers (make-hash-table :test 'eql))
107  (floats (make-hash-table :test 'eql))
108  (doubles (make-hash-table :test 'eql)))
109
110(defun class-name-from-filespec (filespec)
111  (let* ((name (pathname-name filespec)))
112    (declare (type string name))
113    (dotimes (i (length name))
114      (declare (type fixnum i))
115      (when (char= (char name i) #\-)
116        (setf (char name i) #\_)))
117    (concatenate 'string "org/armedbear/lisp/" name)))
118
119(defun make-class-file (&key pathname lambda-name lambda-list)
120  (aver (not (null pathname)))
121  (let ((class-file (%make-class-file :pathname pathname
122                                      :lambda-name lambda-name
123                                      :lambda-list lambda-list)))
124    (setf (class-file-class class-file) (class-name-from-filespec pathname))
125    class-file))
126
127(defmacro with-class-file (class-file &body body)
128  (let ((var (gensym)))
129    `(let* ((,var ,class-file)
130            (*pool*               (class-file-pool ,var))
131            (*pool-count*         (class-file-pool-count ,var))
132            (*pool-entries*       (class-file-pool-entries ,var))
133            (*fields*             (class-file-fields ,var))
134            (*static-code*        (class-file-static-code ,var))
135            (*declared-symbols*   (class-file-symbols ,var))
136            (*declared-functions* (class-file-functions ,var))
137            (*declared-strings*   (class-file-strings ,var))
138            (*declared-integers*  (class-file-integers ,var))
139            (*declared-floats*    (class-file-floats ,var))
140            (*declared-doubles*   (class-file-doubles ,var)))
141       (progn ,@body)
142       (setf (class-file-pool ,var)         *pool*
143             (class-file-pool-count ,var)   *pool-count*
144             (class-file-pool-entries ,var) *pool-entries*
145             (class-file-fields ,var)       *fields*
146             (class-file-static-code ,var)  *static-code*
147             (class-file-symbols ,var)      *declared-symbols*
148             (class-file-functions ,var)    *declared-functions*
149             (class-file-strings ,var)      *declared-strings*
150             (class-file-integers ,var)     *declared-integers*
151             (class-file-floats ,var)       *declared-floats*
152             (class-file-doubles ,var)      *declared-doubles*))))
153
154(defstruct compiland
155  name
156  lambda-expression
157  arg-vars          ; variables for lambda arguments
158  free-specials     ;
159  arity             ; number of args, or NIL if the number of args can vary.
160  p1-result         ; the parse tree as created in pass 1
161  parent            ; the parent for compilands which defined within another
162  (children 0       ; Number of local functions
163            :type fixnum) ; defined with with FLET, LABELS or LAMBDA
164  argument-register
165  closure-register
166  environment-register
167  class-file ; class-file object
168  (%single-valued-p t))
169
170(defknown compiland-single-valued-p (t) t)
171(defun compiland-single-valued-p (compiland)
172  (unless (compiland-parent compiland)
173    (let ((name (compiland-name compiland)))
174      (when name
175        (let ((result-type
176               (or (function-result-type name)
177                   (and (proclaimed-ftype name)
178                        (ftype-result-type (proclaimed-ftype name))))))
179          (when result-type
180            (return-from compiland-single-valued-p
181                         (cond ((eq result-type '*)
182                                nil)
183                               ((atom result-type)
184                                t)
185                               ((eq (%car result-type) 'VALUES)
186                                (= (length result-type) 2))
187                               (t
188                                t))))))))
189  ;; Otherwise...
190  (compiland-%single-valued-p compiland))
191
192(defvar *current-compiland* nil)
193
194(defvar *this-class* nil)
195
196(defvar *code* ())
197
198;; All tags visible at the current point of compilation, some of which may not
199;; be in the current compiland.
200(defvar *visible-tags* ())
201
202;; The next available register.
203(defvar *register* 0)
204
205;; Total number of registers allocated.
206(defvar *registers-allocated* 0)
207
208(defvar *handlers* ())
209
210(defstruct handler
211  from
212  to
213  code
214  catch-type)
215
216;; Variables visible at the current point of compilation.
217(defvar *visible-variables* nil)
218
219;; All variables seen so far.
220(defvar *all-variables* nil)
221
222;; Undefined variables that we've already warned about.
223(defvar *undefined-variables* nil)
224
225(defvar *dump-variables* nil)
226
227(defun dump-1-variable (variable)
228  (sys::%format t "  ~S special-p = ~S register = ~S index = ~S declared-type = ~S~%"
229           (variable-name variable)
230           (variable-special-p variable)
231           (variable-register variable)
232           (variable-index variable)
233           (variable-declared-type variable)))
234
235(defun dump-variables (list caption &optional (force nil))
236  (when (or force *dump-variables*)
237    (write-string caption)
238    (if list
239        (dolist (variable list)
240          (dump-1-variable variable))
241        (sys::%format t "  None.~%"))))
242
243(defstruct (variable-info (:conc-name variable-)
244                          (:constructor make-variable)
245                          (:predicate variable-p))
246  name
247  initform
248  (declared-type :none)
249  (derived-type :none)
250  ignore-p
251  ignorable-p
252  representation
253  special-p     ; indicates whether a variable is special
254  register      ; register number for a local variable
255  index         ; index number for a variable in the argument array
256  closure-index ; index number for a variable in the closure context array
257    ;; a variable can be either special-p *or* have a register *or*
258    ;; have an index *or a closure-index
259  (reads 0 :type fixnum)
260  (writes 0 :type fixnum)
261  references
262  used-non-locally-p
263  (compiland *current-compiland*))
264
265(defstruct (var-ref (:constructor make-var-ref (variable)))
266  ;; The variable this reference refers to. Will be NIL if the VAR-REF has been
267  ;; rewritten to reference a constant value.
268  variable
269  ;; True if the VAR-REF has been rewritten to reference a constant value.
270  constant-p
271  ;; The constant value of this VAR-REF.
272  constant-value)
273
274;; obj can be a symbol or variable
275;; returns variable or nil
276(declaim (ftype (function (t) t) unboxed-fixnum-variable))
277(defun unboxed-fixnum-variable (obj)
278  (cond ((symbolp obj)
279         (let ((variable (find-visible-variable obj)))
280           (if (and variable
281                    (eq (variable-representation variable) :int))
282               variable
283               nil)))
284        ((variable-p obj)
285         (if (eq (variable-representation obj) :int)
286             obj
287             nil))
288        (t
289         nil)))
290
291(defvar *child-p* nil
292  "True for local functions created by FLET, LABELS and (NAMED-)LAMBDA")
293
294(defknown find-variable (symbol list) t)
295(defun find-variable (name variables)
296  (dolist (variable variables)
297    (when (eq name (variable-name variable))
298      (return variable))))
299
300(defknown find-visible-variable (t) t)
301(defun find-visible-variable (name)
302  (dolist (variable *visible-variables*)
303    (when (eq name (variable-name variable))
304      (return variable))))
305
306(defknown allocate-register () (integer 0 65535))
307(defun allocate-register ()
308  (let* ((register *register*)
309         (next-register (1+ register)))
310    (declare (type (unsigned-byte 16) register next-register))
311    (setf *register* next-register)
312    (when (< *registers-allocated* next-register)
313      (setf *registers-allocated* next-register))
314    register))
315
316(defknown allocate-register-pair () (integer 0 65535))
317(defun allocate-register-pair ()
318  (let* ((register *register*)
319         (next-register (+ register 2)))
320    (declare (type (unsigned-byte 16) register next-register))
321    (setf *register* next-register)
322    (when (< *registers-allocated* next-register)
323      (setf *registers-allocated* next-register))
324    register))
325
326(defstruct local-function
327  name
328  compiland
329  inline-expansion
330  function  ;; the function loaded through load-compiled-function
331  class-file
332  variable  ;; the variable which contains the loaded compiled function
333            ;; or compiled closure
334  )
335
336(defvar *local-functions* ())
337
338(defknown find-local-function (t) t)
339(defun find-local-function (name)
340  (dolist (local-function *local-functions* nil)
341    (when (equal name (local-function-name local-function))
342        (return local-function))))
343
344(defvar *using-arg-array* nil)
345(defvar *hairy-arglist-p* nil)
346
347(defstruct node
348  ;; Block name or (TAGBODY) or (LET) or (MULTIPLE-VALUE-BIND).
349  name
350  form
351  (compiland *current-compiland*))
352
353;; Used to wrap TAGBODYs, UNWIND-PROTECTs and LET/LET*/M-V-B forms as well as
354;; BLOCKs per se.
355(defstruct (block-node (:conc-name block-)
356                       (:include node)
357                       (:constructor make-block-node (name)))
358  (exit (gensym))
359  target
360  catch-tag
361  ;; True if there is any RETURN from this block.
362  return-p
363  ;; True if there is a non-local RETURN from this block.
364  non-local-return-p
365  ;; True if a tag in this tagbody is the target of a non-local GO.
366  non-local-go-p
367  ;; If non-nil, the TAGBODY contains local blocks which "contaminate" the
368  ;; environment, with GO forms in them which target tags in this TAGBODY
369  ;; Non-nil if and only if the block doesn't modify the environment
370  needs-environment-restoration
371  ;; If non-nil, register containing saved dynamic environment for this block.
372  environment-register
373  ;; Only used in LET/LET*/M-V-B nodes.
374  vars
375  free-specials
376  ;; Only used in TAGBODY
377  tags
378  )
379
380(defvar *blocks* ())
381
382(defun find-block (name)
383  (dolist (block *blocks*)
384    (when (eq name (block-name block))
385      (return block))))
386
387(defknown node-constant-p (t) boolean)
388(defun node-constant-p (object)
389  (cond ((block-node-p object)
390         nil)
391        ((var-ref-p object)
392         nil)
393        ((constantp object)
394         t)
395        (t
396         nil)))
397
398(defknown block-requires-non-local-exit-p (t) boolean)
399(defun block-requires-non-local-exit-p (object)
400  "A block which *always* requires a 'non-local-exit' is a block which
401requires a transfer control exception to be thrown: e.g. Go and Return.
402
403Non-local exits are required by blocks which do more in their cleanup
404than just restore the lastSpecialBinding (= dynamic environment).
405"
406  (let ((name (block-name object)))
407    (or (equal name '(CATCH))
408        (equal name '(UNWIND-PROTECT)))))
409
410
411(defknown enclosed-by-protected-block-p (&optional t) boolean)
412(defun enclosed-by-protected-block-p (&optional outermost-block)
413  "Indicates whether the code being compiled/analyzed is enclosed in
414a block which requires a non-local transfer of control exception to
415be generated.
416"
417  (dolist (enclosing-block *blocks*)
418    (when (eq enclosing-block outermost-block)
419      (return-from enclosed-by-protected-block-p nil))
420    (when (block-requires-non-local-exit-p enclosing-block)
421      (return-from enclosed-by-protected-block-p t))))
422
423(defknown enclosed-by-environment-setting-block-p (&optional t) boolean)
424(defun enclosed-by-environment-setting-block-p (&optional outermost-block)
425  (dolist (enclosing-block *blocks*)
426    (when (eq enclosing-block outermost-block)
427      (return nil))
428    (when (and (block-environment-register enclosing-block)
429               (not (block-needs-environment-restoration enclosing-block)))
430      (return t))))
431
432(defknown environment-register-to-restore (&optional t) t)
433(defun environment-register-to-restore (&optional outermost-block)
434  "Returns the environment register which contains the
435saved environment from the outermost enclosing block:
436
437That's the one which contains the environment used in the outermost block."
438  (flet ((outermost-register (last-register block)
439           (when (eq block outermost-block)
440             (return-from environment-register-to-restore last-register))
441           (or (block-environment-register block)
442               last-register)))
443    (reduce #'outermost-register *blocks*
444            :initial-value nil)))
445
446(defstruct tag
447  ;; The symbol (or integer) naming the tag
448  name
449  ;; The symbol which is the jump target in JVM byte code
450  label
451  ;; The associated TAGBODY
452  block
453  (compiland *current-compiland*)
454  used)
455
456(defknown find-tag (t) t)
457(defun find-tag (name)
458  (dolist (tag *visible-tags*)
459    (when (eql name (tag-name tag))
460      (return tag))))
461
462(defun process-ignore/ignorable (declaration names variables)
463  (when (memq declaration '(IGNORE IGNORABLE))
464    (let ((what (if (eq declaration 'IGNORE) "ignored" "ignorable")))
465      (dolist (name names)
466        (let ((variable (find-variable name variables)))
467          (cond ((null variable)
468                 (compiler-style-warn "Declaring unknown variable ~S to be ~A."
469                                      name what))
470                ((variable-special-p variable)
471                 (compiler-style-warn "Declaring special variable ~S to be ~A."
472                                      name what))
473                ((eq declaration 'IGNORE)
474                 (setf (variable-ignore-p variable) t))
475                (t
476                 (setf (variable-ignorable-p variable) t))))))))
477
478(defvar *file-compilation* nil)
479(defvar *pathnames-generator* #'make-temp-file)
480
481(defun compile (name &optional definition)
482  (let ((*file-compilation* nil)
483        (*pathnames-generator* #'make-temp-file)
484        (sys::*fasl-anonymous-package* (sys::%make-package)))
485    (jvm-compile name definition)))
486
487(defmacro with-file-compilation (&body body)
488  `(let ((*file-compilation* t)
489         (*pathnames-generator* #'sys::next-classfile-name))
490     ,@body))
491
492(defun finalize-generic-functions ()
493  (dolist (sym '(make-instance
494                 initialize-instance
495                 shared-initialize))
496    (let ((gf (and (fboundp sym) (fdefinition sym))))
497      (when (typep gf 'generic-function)
498        (unless (compiled-function-p gf)
499          (mop::finalize-generic-function gf))))))
500
501(finalize-generic-functions)
502
503(provide 'jvm)
Note: See TracBrowser for help on using the repository browser.