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

Last change on this file since 13448 was 13448, checked in by ehuelsmann, 12 years ago

Add more documentation.

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