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

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

Clean up after old pool concept removal.

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