source: branches/0.22.x/abcl/src/org/armedbear/lisp/jvm.lisp

Last change on this file was 12690, checked in by ehuelsmann, 15 years ago

Replace serialization related DECLARE-* functions with
a single API: EXTERNALIZE-OBJECT, which builds upon a
set of SERIALIZE-* functions. The intent is to make
building blocks which allow - at a later stage -
serialization without utilizing the reader for restoring.

With this commit, the compiler stops generating meaningful
field names; instead it just uses a type ("STR") and a
sequence number.

Note: A number of DECLARE-* functions remain in place,
these don't have to do with serialization, though; most
have caching characteristics.

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