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

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

Switch pass2 to the pool routines from jvm-class-file.lisp.

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