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

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

Move the u2, s1 and s2 helper functions to jvm.lisp.

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