source: branches/generic-class-file/abcl/src/org/armedbear/lisp/jvm.lisp @ 12864

Last change on this file since 12864 was 12864, checked in by ehuelsmann, 13 years ago

Rename opcodes.lisp to jvm-instructions.lisp in order to move our
code-emitters layer and resolvers to it.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 23.6 KB
Line 
1;;; jvm.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves
4;;; $Id: jvm.lisp 12864 2010-08-06 19:51: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., 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-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 "COMPILER-ERROR")
44  (require "KNOWN-FUNCTIONS")
45  (require "DUMP-FORM")
46  (require "JVM-INSTRUCTIONS")
47  (require "JVM-CLASS-FILE")
48  (require "KNOWN-SYMBOLS")
49  (require "JAVA")
50  (require "COMPILER-PASS1")
51  (require "COMPILER-PASS2"))
52
53(defvar *closure-variables* nil)
54
55(defvar *enable-dformat* nil)
56
57#+nil
58(defun dformat (destination control-string &rest args)
59  (when *enable-dformat*
60    (apply #'sys::%format destination control-string args)))
61
62(defmacro dformat (&rest ignored)
63  (declare (ignore ignored)))
64
65
66(defmacro with-saved-compiler-policy (&body body)
67  "Saves compiler policy variables, restoring them after evaluating `body'."
68  `(let ((*speed* *speed*)
69         (*space* *space*)
70         (*safety* *safety*)
71         (*debug* *debug*)
72         (*explain* *explain*)
73         (*inline-declarations* *inline-declarations*))
74     ,@body))
75
76
77
78(defvar *compiler-debug* nil)
79
80(defvar *pool* nil)
81(defvar *pool-count* 1)
82(defvar *pool-entries* nil)
83(defvar *fields* ())
84(defvar *static-code* ())
85
86(defvar *externalized-objects* nil)
87(defvar *declared-functions* nil)
88
89(defstruct (abcl-class-file (:include class-file)
90                            (:constructor %make-abcl-class-file))
91  pathname ; pathname of output file
92  lambda-name
93  lambda-list ; as advertised
94  pool
95  (pool-count 1)
96  (pool-entries (make-hash-table :test #'equal))
97  static-code
98  objects ;; an alist of externalized objects and their field names
99  (functions (make-hash-table :test 'equal)) ;; because of (SETF ...) functions
100  )
101
102(defun class-name-from-filespec (filespec)
103  (let* ((name (pathname-name filespec)))
104    (declare (type string name))
105    (dotimes (i (length name))
106      (declare (type fixnum i))
107      (when (or (char= (char name i) #\-)
108                (char= (char name i) #\Space))
109        (setf (char name i) #\_)))
110    (make-class-name
111     (concatenate 'string "org.armedbear.lisp." name))))
112
113(defun make-unique-class-name ()
114  "Creates a random class name for use with a `class-file' structure's
115`class' slot."
116  (make-class-name
117   (concatenate 'string "abcl_"
118                (substitute #\_ #\-
119                            (java:jcall (java:jmethod "java.util.UUID"
120                                                      "toString")
121                                        (java:jstatic "randomUUID"
122                                                      "java.util.UUID"))))))
123
124(defun make-class-file (&key pathname lambda-name lambda-list)
125  "Creates a `class-file' structure. If `pathname' is non-NIL, it's
126used to derive a class name. If it is NIL, a random one created
127using `make-unique-class-name'."
128  (let* ((class-name (if pathname
129                         (class-name-from-filespec  pathname)
130                         (make-unique-class-name)))
131         (class-file (%make-abcl-class-file :pathname pathname
132                                            :class class-name
133                                            :lambda-name lambda-name
134                                            :lambda-list lambda-list)))
135    class-file))
136
137(defmacro with-class-file (class-file &body body)
138  (let ((var (gensym)))
139    `(let* ((,var ,class-file)
140            (*pool*                 (abcl-class-file-pool ,var))
141            (*pool-count*           (abcl-class-file-pool-count ,var))
142            (*pool-entries*         (abcl-class-file-pool-entries ,var))
143            (*fields*               (abcl-class-file-fields ,var))
144            (*static-code*          (abcl-class-file-static-code ,var))
145            (*externalized-objects* (abcl-class-file-objects ,var))
146            (*declared-functions*   (abcl-class-file-functions ,var)))
147       (progn ,@body)
148       (setf (abcl-class-file-pool ,var)         *pool*
149             (abcl-class-file-pool-count ,var)   *pool-count*
150             (abcl-class-file-pool-entries ,var) *pool-entries*
151             (abcl-class-file-fields ,var)       *fields*
152             (abcl-class-file-static-code ,var)  *static-code*
153             (abcl-class-file-objects ,var)      *externalized-objects*
154             (abcl-class-file-functions ,var)    *declared-functions*))))
155
156(defstruct compiland
157  name
158  lambda-expression
159  arg-vars          ; variables for lambda arguments
160  free-specials     ;
161  arity             ; number of args, or NIL if the number of args can vary.
162  p1-result         ; the parse tree as created in pass 1
163  parent            ; the parent for compilands which defined within another
164  (children 0       ; Number of local functions
165            :type fixnum) ; defined with FLET, LABELS or LAMBDA
166  blocks            ; TAGBODY, PROGV, BLOCK, etc. blocks
167  argument-register
168  closure-register
169  environment-register
170  class-file ; class-file object
171  (%single-valued-p t))
172
173(defknown compiland-single-valued-p (t) t)
174(defun compiland-single-valued-p (compiland)
175  (unless (compiland-parent compiland)
176    (let ((name (compiland-name compiland)))
177      (when name
178        (let ((result-type
179               (or (function-result-type name)
180                   (and (proclaimed-ftype name)
181                        (ftype-result-type (proclaimed-ftype name))))))
182          (when result-type
183            (return-from compiland-single-valued-p
184                         (cond ((eq result-type '*)
185                                nil)
186                               ((atom result-type)
187                                t)
188                               ((eq (%car result-type) 'VALUES)
189                                (= (length result-type) 2))
190                               (t
191                                t))))))))
192  ;; Otherwise...
193  (compiland-%single-valued-p compiland))
194
195(defvar *current-compiland* nil)
196
197(defvar *this-class* nil)
198
199(defvar *code* ())
200
201;; All tags visible at the current point of compilation, some of which may not
202;; be in the current compiland.
203(defvar *visible-tags* ())
204
205;; The next available register.
206(defvar *register* 0)
207
208;; Total number of registers allocated.
209(defvar *registers-allocated* 0)
210
211(defvar *handlers* ())
212
213(defstruct handler
214  from       ;; label indicating the start of the protected block
215  to         ;; label indicating the end of the protected block
216  code       ;; label to jump to if the specified exception occurs
217  catch-type ;; pool index of the class name of the exception, or 0 (zero)
218             ;; for 'all'
219  )
220
221;; Variables visible at the current point of compilation.
222(defvar *visible-variables* nil
223  "All variables visible to the form currently being
224processed, including free specials.")
225
226;; All variables seen so far.
227(defvar *all-variables* nil
228  "All variables in the lexical scope (thus excluding free specials)
229of the compilands being processed (p1: so far; p2: in total).")
230
231;; Undefined variables that we've already warned about.
232(defvar *undefined-variables* nil)
233
234(defvar *dump-variables* nil)
235
236(defun dump-1-variable (variable)
237  (sys::%format t "  ~S special-p = ~S register = ~S binding-reg = ~S index = ~S declared-type = ~S~%"
238           (variable-name variable)
239           (variable-special-p variable)
240           (variable-register variable)
241           (variable-binding-register variable)
242           (variable-index variable)
243           (variable-declared-type variable)))
244
245(defun dump-variables (list caption &optional (force nil))
246  (when (or force *dump-variables*)
247    (write-string caption)
248    (if list
249        (dolist (variable list)
250          (dump-1-variable variable))
251        (sys::%format t "  None.~%"))))
252
253(defstruct (variable-info (:conc-name variable-)
254                          (:constructor make-variable)
255                          (:predicate variable-p))
256  name
257  initform
258  (declared-type :none)
259  (derived-type :none)
260  ignore-p
261  ignorable-p
262  representation
263  special-p     ; indicates whether a variable is special
264  register      ; register number for a local variable
265  binding-register ; register number containing the binding reference
266  index         ; index number for a variable in the argument array
267  closure-index ; index number for a variable in the closure context array
268  environment   ; the environment for the variable, if we're compiling in
269                ; a non-null lexical environment with variables
270    ;; a variable can be either special-p *or* have a register *or*
271    ;; have an index *or* a closure-index *or* an environment
272  (reads 0 :type fixnum)
273  (writes 0 :type fixnum)
274  references
275  (references-allowed-p t) ; NIL if this is a symbol macro in the enclosing
276                           ; lexical environment
277  used-non-locally-p
278  (compiland *current-compiland*)
279  block)
280
281(defstruct (var-ref (:constructor make-var-ref (variable)))
282  ;; The variable this reference refers to. Will be NIL if the VAR-REF has been
283  ;; rewritten to reference a constant value.
284  variable
285  ;; True if the VAR-REF has been rewritten to reference a constant value.
286  constant-p
287  ;; The constant value of this VAR-REF.
288  constant-value)
289
290;; obj can be a symbol or variable
291;; returns variable or nil
292(declaim (ftype (function (t) t) unboxed-fixnum-variable))
293(defun unboxed-fixnum-variable (obj)
294  (cond ((symbolp obj)
295         (let ((variable (find-visible-variable obj)))
296           (if (and variable
297                    (eq (variable-representation variable) :int))
298               variable
299               nil)))
300        ((variable-p obj)
301         (if (eq (variable-representation obj) :int)
302             obj
303             nil))
304        (t
305         nil)))
306
307(defvar *child-p* nil
308  "True for local functions created by FLET, LABELS and (NAMED-)LAMBDA")
309
310(defknown find-variable (symbol list) t)
311(defun find-variable (name variables)
312  (dolist (variable variables)
313    (when (eq name (variable-name variable))
314      (return variable))))
315
316(defknown find-visible-variable (t) t)
317(defun find-visible-variable (name)
318  (dolist (variable *visible-variables*)
319    (when (eq name (variable-name variable))
320      (return variable))))
321
322(defknown allocate-register () (integer 0 65535))
323(defun allocate-register ()
324  (let* ((register *register*)
325         (next-register (1+ register)))
326    (declare (type (unsigned-byte 16) register next-register))
327    (setf *register* next-register)
328    (when (< *registers-allocated* next-register)
329      (setf *registers-allocated* next-register))
330    register))
331
332(defknown allocate-register-pair () (integer 0 65535))
333(defun allocate-register-pair ()
334  (let* ((register *register*)
335         (next-register (+ register 2)))
336    (declare (type (unsigned-byte 16) register next-register))
337    (setf *register* next-register)
338    (when (< *registers-allocated* next-register)
339      (setf *registers-allocated* next-register))
340    register))
341
342(defstruct local-function
343  name
344  definition
345  compiland
346  inline-expansion
347  function    ;; the function loaded through load-compiled-function
348  class-file  ;; the class file structure for this function
349  variable    ;; the variable which contains the loaded compiled function
350              ;; or compiled closure
351  environment ;; the environment in which the function is stored in
352              ;; case of a function from an enclosing lexical environment
353              ;; which itself isn't being compiled
354  (references-allowed-p t) ;;whether a reference to the function CAN be captured
355  (references-needed-p nil) ;;whether a reference to the function NEEDS to be
356          ;;captured, because the function name is used in a
357                            ;;(function ...) form. Obviously implies
358                            ;;references-allowed-p.
359  )
360
361(defvar *local-functions* ())
362
363(defknown find-local-function (t) t)
364(defun find-local-function (name)
365  (dolist (local-function *local-functions* nil)
366    (when (equal name (local-function-name local-function))
367        (return local-function))))
368
369(defvar *using-arg-array* nil)
370(defvar *hairy-arglist-p* nil)
371
372(defstruct node
373  form
374  (compiland *current-compiland*))
375;; No need for a special constructor: nobody instantiates
376;; nodes directly
377
378;; control-transferring blocks: TAGBODY, CATCH, to do: BLOCK
379
380(defstruct (control-transferring-node (:include node))
381  ;; If non-nil, the TAGBODY contains local blocks which "contaminate" the
382  ;; environment, with GO forms in them which target tags in this TAGBODY
383  ;; Non-nil if and only if the block doesn't modify the environment
384  needs-environment-restoration
385  )
386;; No need for a special constructor: nobody instantiates
387;; control-transferring-nodes directly
388
389(defstruct (tagbody-node (:conc-name tagbody-)
390                         (:include control-transferring-node)
391       (:constructor %make-tagbody-node ()))
392  ;; True if a tag in this tagbody is the target of a non-local GO.
393  non-local-go-p
394  ;; Tags in the tagbody form; a list of tag structures
395  tags
396  ;; Contains a variable whose value uniquely identifies the
397  ;; lexical scope from this block, to be used by GO
398  id-variable)
399(defknown make-tagbody-node () t)
400(defun make-tagbody-node ()
401  (let ((block (%make-tagbody-node)))
402    (push block (compiland-blocks *current-compiland*))
403    block))
404
405(defstruct (catch-node (:conc-name catch-)
406                       (:include control-transferring-node)
407           (:constructor %make-catch-node ()))
408  ;; The catch tag-form is evaluated, meaning we
409  ;; have no predefined value to store here
410  )
411(defknown make-catch-node () t)
412(defun make-catch-node ()
413  (let ((block (%make-catch-node)))
414    (push block (compiland-blocks *current-compiland*))
415    block))
416
417(defstruct (block-node (:conc-name block-)
418                       (:include control-transferring-node)
419                       (:constructor %make-block-node (name)))
420  name  ;; Block name
421  (exit (gensym))
422  target
423  ;; True if there is a non-local RETURN from this block.
424  non-local-return-p
425  ;; Contains a variable whose value uniquely identifies the
426  ;; lexical scope from this block, to be used by RETURN-FROM
427  id-variable)
428(defknown make-block-node (t) t)
429(defun make-block-node (name)
430  (let ((block (%make-block-node name)))
431    (push block (compiland-blocks *current-compiland*))
432    block))
433
434;; binding blocks: LET, LET*, FLET, LABELS, M-V-B, PROGV, LOCALLY
435;;
436;; Binding blocks can carry references to local (optionally special) variable bindings,
437;;  contain free special bindings or both
438
439(defstruct (binding-node (:include node))
440  ;; number of the register of the saved dynamic env, or NIL if none
441  environment-register
442  ;; Not used for LOCALLY and FLET; LABELS uses vars to store its functions
443  vars
444  free-specials)
445;; nobody instantiates any binding nodes directly, so there's no reason
446;; to create a constructor with the approprate administration code
447
448(defstruct (let/let*-node (:conc-name let-)
449                          (:include binding-node)
450        (:constructor %make-let/let*-node ())))
451(defknown make-let/let*-node () t)
452(defun make-let/let*-node ()
453  (let ((block (%make-let/let*-node)))
454    (push block (compiland-blocks *current-compiland*))
455    block))
456
457(defstruct (flet-node (:conc-name flet-)
458                      (:include binding-node)
459          (:constructor %make-flet-node ())))
460(defknown make-flet-node () t)
461(defun make-flet-node ()
462  (let ((block (%make-flet-node)))
463    (push block (compiland-blocks *current-compiland*))
464    block))
465
466(defstruct (labels-node (:conc-name labels-)
467                        (:include binding-node)
468      (:constructor %make-labels-node ())))
469(defknown make-labels-node () t)
470(defun make-labels-node ()
471  (let ((block (%make-labels-node)))
472    (push block (compiland-blocks *current-compiland*))
473    block))
474
475(defstruct (m-v-b-node (:conc-name m-v-b-)
476                       (:include binding-node)
477           (:constructor %make-m-v-b-node ())))
478(defknown make-m-v-b-node () t)
479(defun make-m-v-b-node ()
480  (let ((block (%make-m-v-b-node)))
481    (push block (compiland-blocks *current-compiland*))
482    block))
483
484(defstruct (progv-node (:conc-name progv-)
485                       (:include binding-node)
486           (:constructor %make-progv-node ())))
487(defknown make-progv-node () t)
488(defun make-progv-node ()
489  (let ((block (%make-progv-node)))
490    (push block (compiland-blocks *current-compiland*))
491    block))
492
493(defstruct (locally-node (:conc-name locally-)
494                         (:include binding-node)
495       (:constructor %make-locally-node ())))
496(defknown make-locally-node () t)
497(defun make-locally-node ()
498  (let ((block (%make-locally-node)))
499    (push block (compiland-blocks *current-compiland*))
500    block))
501
502;; blocks requiring non-local exits: UNWIND-PROTECT, SYS:SYNCHRONIZED-ON
503
504(defstruct (protected-node (:include node)
505         (:constructor %make-protected-node ())))
506(defknown make-protected-node () t)
507(defun make-protected-node ()
508  (let ((block (%make-protected-node)))
509    (push block (compiland-blocks *current-compiland*))
510    block))
511
512(defstruct (unwind-protect-node (:conc-name unwind-protect-)
513                                (:include protected-node)
514        (:constructor %make-unwind-protect-node ())))
515(defknown make-unwind-protect-node () t)
516(defun make-unwind-protect-node ()
517  (let ((block (%make-unwind-protect-node)))
518    (push block (compiland-blocks *current-compiland*))
519    block))
520
521(defstruct (synchronized-node (:conc-name synchronized-)
522                              (:include protected-node)
523            (:constructor %make-synchronized-node ())))
524(defknown make-synchronized-node () t)
525(defun make-synchronized-node ()
526  (let ((block (%make-synchronized-node)))
527    (push block (compiland-blocks *current-compiland*))
528    block))
529
530
531(defvar *blocks* ())
532
533(defun find-block (name)
534  (dolist (block *blocks*)
535    (when (and (block-node-p block)
536               (eq name (block-name block)))
537      (return block))))
538
539(defknown node-constant-p (t) boolean)
540(defun node-constant-p (object)
541  (cond ((node-p object)
542         nil)
543        ((var-ref-p object)
544         nil)
545        ((constantp object)
546         t)
547        (t
548         nil)))
549
550(defknown block-requires-non-local-exit-p (t) boolean)
551(defun block-requires-non-local-exit-p (object)
552  "A block which *always* requires a 'non-local-exit' is a block which
553requires a transfer control exception to be thrown: e.g. Go and Return.
554
555Non-local exits are required by blocks which do more in their cleanup
556than just restore the lastSpecialBinding (= dynamic environment).
557"
558  (or (unwind-protect-node-p object)
559      (catch-node-p object)
560      (synchronized-node-p object)))
561
562(defknown block-creates-runtime-bindings-p (t) boolean)
563(defun block-creates-runtime-bindings-p (block)
564  ;; FIXME: This may be false, if the bindings to be
565  ;; created are a quoted list
566  (progv-node-p block))
567
568(defknown enclosed-by-runtime-bindings-creating-block-p (t) boolean)
569(defun enclosed-by-runtime-bindings-creating-block-p (outermost-block)
570  "Indicates whether the code being compiled/analyzed is enclosed in a
571block which creates special bindings at runtime."
572  (dolist (enclosing-block *blocks*)
573    (when (eq enclosing-block outermost-block)
574      (return-from enclosed-by-runtime-bindings-creating-block-p nil))
575    (when (block-creates-runtime-bindings-p enclosing-block)
576      (return-from enclosed-by-runtime-bindings-creating-block-p t))))
577
578(defknown enclosed-by-protected-block-p (&optional t) boolean)
579(defun enclosed-by-protected-block-p (&optional outermost-block)
580  "Indicates whether the code being compiled/analyzed is enclosed in
581a block which requires a non-local transfer of control exception to
582be generated.
583"
584  (dolist (enclosing-block *blocks*)
585    (when (eq enclosing-block outermost-block)
586      (return-from enclosed-by-protected-block-p nil))
587    (when (block-requires-non-local-exit-p enclosing-block)
588      (return-from enclosed-by-protected-block-p t))))
589
590(defknown enclosed-by-environment-setting-block-p (&optional t) boolean)
591(defun enclosed-by-environment-setting-block-p (&optional outermost-block)
592  (dolist (enclosing-block *blocks*)
593    (when (eq enclosing-block outermost-block)
594      (return nil))
595    (when (and (binding-node-p enclosing-block)
596               (binding-node-environment-register enclosing-block))
597      (return t))))
598
599(defknown environment-register-to-restore (&optional t) t)
600(defun environment-register-to-restore (&optional outermost-block)
601  "Returns the environment register which contains the
602saved environment from the outermost enclosing block:
603
604That's the one which contains the environment used in the outermost block."
605  (flet ((outermost-register (last-register block)
606           (when (eq block outermost-block)
607             (return-from environment-register-to-restore last-register))
608           (or (and (binding-node-p block)
609                    (binding-node-environment-register block))
610               last-register)))
611    (reduce #'outermost-register *blocks*
612            :initial-value nil)))
613
614(defstruct tag
615  ;; The symbol (or integer) naming the tag
616  name
617  ;; The symbol which is the jump target in JVM byte code
618  label
619  ;; The associated TAGBODY
620  block
621  (compiland *current-compiland*)
622  used
623  used-non-locally)
624
625(defknown find-tag (t) t)
626(defun find-tag (name)
627  (dolist (tag *visible-tags*)
628    (when (eql name (tag-name tag))
629      (return tag))))
630
631(defun process-ignore/ignorable (declaration names variables)
632  (when (memq declaration '(IGNORE IGNORABLE))
633    (let ((what (if (eq declaration 'IGNORE) "ignored" "ignorable")))
634      (dolist (name names)
635        (unless (and (consp name) (eq (car name) 'FUNCTION))
636          (let ((variable (find-variable name variables)))
637            (cond ((null variable)
638                   (compiler-style-warn "Declaring unknown variable ~S to be ~A."
639                                        name what))
640                  ((variable-special-p variable)
641                   (compiler-style-warn "Declaring special variable ~S to be ~A."
642                                        name what))
643                  ((eq declaration 'IGNORE)
644                   (setf (variable-ignore-p variable) t))
645                  (t
646                   (setf (variable-ignorable-p variable) t)))))))))
647
648(defun finalize-generic-functions ()
649  (dolist (sym '(make-instance
650                 initialize-instance
651                 shared-initialize))
652    (let ((gf (and (fboundp sym) (fdefinition sym))))
653      (when (typep gf 'generic-function)
654        (unless (compiled-function-p gf)
655          (mop::finalize-generic-function gf))))))
656
657(finalize-generic-functions)
658
659(provide 'jvm)
Note: See TracBrowser for help on using the repository browser.