source: trunk/abcl/src/org/armedbear/lisp/java.lisp

Last change on this file was 15763, checked in by Mark Evenson, 4 months ago

JAVA package docstring and export adjustment

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 27.2 KB
Line 
1;;; java.lisp
2;;;
3;;; Copyright (C) 2003-2007 Peter Graves, Andras Simon
4;;; $Id: java.lisp 15763 2023-12-13 08:58:22Z mevenson $
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 "JAVA")
33
34(require "CLOS")
35(require "PRINT-OBJECT")
36
37(defvar *classloader* (get-default-classloader))
38
39(export '(jregister-handler jinterface-implementation jmake-invocation-handler
40          jmake-proxy jproperty-value jobject-class jclass-superclass
41          jclass-interfaces jclass-interface-p jclass-superclass-p
42          jclass-array-p jarray-component-type jarray-length
43          jnew-array-from-array jnew-array-from-list jarray-from-list
44          vector-from-jarray list-from-jarray
45          list-from-jenumeration
46          jclass-constructors jconstructor-params jclass-field jclass-fields
47          jfield-type jfield-name jclass-methods jmethod-params jmethod-name
48          jinstance-of-p jmember-static-p jmember-public-p jmember-protected-p
49          jnew-runtime-class define-java-class ensure-java-class chain
50          jmethod-let jequal))
51
52(defun add-url-to-classpath (url &optional (classloader *classloader*))
53  (jcall "addUrl" classloader url))
54
55(defun add-urls-to-classpath (&rest urls)
56  (dolist (url urls)
57    (add-url-to-classpath url)))
58
59(defgeneric add-to-classpath (jar-or-jars &optional classloader)
60  (:documentation "Add JAR-OR-JARS to the JVM classpath optionally specifying the CLASSLOADER to add.
61
62JAR-OR-JARS is either a pathname designating a jar archive or the root
63directory to search for classes or a list of such values."))
64
65(defmethod add-to-classpath (jar-or-jars &optional (classloader (get-current-classloader)))
66  (%add-to-classpath jar-or-jars classloader))
67
68(defun jregister-handler (object event handler &key data count)
69  (%jregister-handler object event handler data count))
70
71(defun jinterface-implementation (interface &rest method-names-and-defs)
72  "Creates and returns an implementation of a Java interface with
73   methods calling Lisp closures as given in METHOD-NAMES-AND-DEFS.
74
75   INTERFACE is either a Java interface or a string naming one.
76
77   METHOD-NAMES-AND-DEFS is an alternating list of method names
78   (strings) and method definitions (closures).
79
80   For missing methods, a dummy implementation is provided that
81   returns nothing or null depending on whether the return type is
82   void or not. This is for convenience only, and a warning is issued
83   for each undefined method."
84  (let ((interface (jclass interface))
85        (implemented-methods
86         (loop for m in method-names-and-defs
87           for i from 0
88           if (evenp i)
89           do (assert (stringp m) (m) "Method names must be strings: ~s" m) and collect m
90           else
91           do (assert (or (symbolp m) (functionp m)) (m) "Methods must be function designators: ~s" m))))
92    (loop for method across
93      (jclass-methods interface :declared nil :public t)
94      for method-name = (jmethod-name method)
95      when (not (member method-name implemented-methods :test #'string=))
96      do
97      (let* ((void-p (string= (jclass-name (jmethod-return-type method)) "void"))
98             (arglist (when (plusp (length (jmethod-params method))) '(&rest ignore)))
99             (def `(lambda
100                     ,arglist
101                     ,(when arglist '(declare (ignore ignore)))
102                     ,(if void-p '(values) java:+null+))))
103        (warn "Implementing dummy method ~a for interface ~a"
104              method-name (jclass-name interface))
105        (push (coerce def 'function) method-names-and-defs)
106        (push method-name method-names-and-defs)))
107    (apply #'%jnew-proxy interface method-names-and-defs)))
108
109(defun jmake-invocation-handler (function)
110  (%jmake-invocation-handler function))
111
112(when (autoloadp 'jmake-proxy)
113  (fmakunbound 'jmake-proxy))
114
115(defgeneric jmake-proxy (interface implementation &optional lisp-this)
116  (:documentation "Returns a proxy Java object implementing the provided interface(s) using methods implemented in Lisp
117
118Method are typically closures, but implementations are free to provide other mechanisms. You can pass an optional 'lisp-this' object that will be passed to the implementing methods as their first argument. If you don't provide this object, NIL will be used. The second argument of the Lisp methods is the name of the Java method being implemented. This has the implication that overloaded methods are merged, so you have to manually discriminate them if you want to. The remaining arguments are java-objects wrapping the method's parameters."))
119
120(defun canonicalize-jproxy-interfaces (ifaces)
121  (if (listp ifaces)
122      (mapcar #'jclass ifaces)
123      (list (jclass ifaces))))
124
125(defmethod jmake-proxy (interface invocation-handler &optional lisp-this)
126  "Java interface proxy that directly uses an invocation handler"
127  (%jmake-proxy (canonicalize-jproxy-interfaces interface) invocation-handler lisp-this))
128
129(defmethod jmake-proxy (interface (implementation function) &optional lisp-this)
130  "Implements a Java interface forwarding method calls to a Lisp function"
131  (%jmake-proxy
132   (canonicalize-jproxy-interfaces interface)
133   (jmake-invocation-handler implementation) lisp-this))
134
135(defmethod jmake-proxy (interface (implementation package) &optional lisp-this)
136  "Implements a Java interface mapping Java method names to symbols in a given package
137
138The implementing javaMethodName is mapped to a JAVA-METHOD-NAME symbol. An error is signaled if no such symbol exists in the package, or if the symbol exists but does not name a function."
139  (flet ((java->lisp (name)
140           (with-output-to-string (str)
141             (let ((last-lower-p nil))
142               (map nil (lambda (char)
143                          (let ((upper-p (char= (char-upcase char) char)))
144                            (when (and last-lower-p upper-p)
145                              (princ "-" str))
146                            (setf last-lower-p (not upper-p))
147                            (princ (char-upcase char) str)))
148                    name)))))
149    (%jmake-proxy (canonicalize-jproxy-interfaces interface)
150                  (jmake-invocation-handler 
151                   (lambda (obj method &rest args)
152                     (let ((sym (find-symbol
153                                 (java->lisp method)
154                                 implementation)))
155                       (unless sym
156                         (error "Symbol ~A, implementation of method ~A, not found in ~A"
157                                  (java->lisp method)
158                                  method
159                                  implementation))
160                         (if (fboundp sym)
161                             (apply (symbol-function sym) obj method args)
162                             (error "Function ~A, implementation of method ~A, not found in ~A"
163                                    sym method implementation)))))
164                  lisp-this)))
165
166(defmethod jmake-proxy (interface (implementation hash-table) &optional lisp-this)
167  "Implements a Java interface using closures in an hash-table keyed by Java method name"
168  (%jmake-proxy (canonicalize-jproxy-interfaces interface)
169                (jmake-invocation-handler 
170                 (lambda (obj method &rest args)
171                   (let ((fn (gethash method implementation)))
172                     (if fn
173                         (apply fn obj args)
174                         (error "Implementation for method ~A not found in ~A"
175                                method implementation)))))
176                lisp-this))
177
178(defun jequal (obj1 obj2)
179  "Compares obj1 with obj2 using java.lang.Object.equals()"
180  (jcall (jmethod "java.lang.Object" "equals" "java.lang.Object")
181         obj1 obj2))
182
183(defun jobject-class (obj)
184  "Returns the Java class that OBJ belongs to"
185  (jcall (jmethod "java.lang.Object" "getClass") obj))
186
187(defun jclass-superclass (class)
188  "Returns the superclass of CLASS, or NIL if it hasn't got one"
189  (jcall (jmethod "java.lang.Class" "getSuperclass") (jclass class)))
190
191(defun jclass-interfaces (class)
192  "Returns a list of interfaces of CLASS"
193  (jcall (jmethod "java.lang.Class" "getInterfaces") (jclass class)))
194
195(defun jclass-interface-p (class)
196  "Boolean predicate for whether CLASS is an interface"
197  (jcall (jmethod "java.lang.Class" "isInterface") (jclass class)))
198
199(defun jclass-superclass-p (class-1 class-2)
200  "Boolean predicate for whether CLASS-1 is a superclass or interface of CLASS-2"
201  (jcall (jmethod "java.lang.Class" "isAssignableFrom" "java.lang.Class")
202         (jclass class-1)
203         (jclass class-2)))
204
205(defun jclass-array-p (class)
206  "Boolean predicate for whether CLASS is an array class"
207  (jcall (jmethod "java.lang.Class" "isArray") (jclass class)))
208
209(defun jarray-component-type (atype)
210  "Returns the component type of the array type ATYPE"
211  (assert (jclass-array-p atype))
212  (jcall (jmethod "java.lang.Class" "getComponentType") atype))
213
214(defun jarray-length (java-array)
215  "Returns the length of a Java primitive JAVA-ARRAY"
216  (jstatic "getLength" "java.lang.reflect.Array" java-array)  )
217
218(defun (setf jarray-ref) (new-value java-array &rest indices)
219  (apply #'jarray-set java-array new-value indices))
220
221(defun jnew-array-from-array (element-type array)
222  "Returns a new Java array with base type ELEMENT-TYPE initialized from ARRAY
223
224ELEMENT-TYPE is either a string or a class reference."
225  (flet
226    ((row-major-to-index (dimensions n)
227                         (loop for dims on dimensions
228                           with indices
229                           do
230                           (multiple-value-bind (m r) (floor n (apply #'* (cdr dims)))
231                             (push m indices)
232                             (setq n r))
233                           finally (return (nreverse indices)))))
234    (let* ((fill-pointer (when (array-has-fill-pointer-p array) (fill-pointer array)))
235           (dimensions (if fill-pointer (list fill-pointer) (array-dimensions array)))
236           (jarray (apply #'jnew-array element-type dimensions)))
237      (dotimes (i (if fill-pointer fill-pointer (array-total-size array)) jarray)
238        #+maybe_one_day
239        (setf (apply #'jarray-ref jarray (row-major-to-index dimensions i)) (row-major-aref array i))
240        (apply #'(setf jarray-ref) (row-major-aref array i) jarray (row-major-to-index dimensions i))))))
241
242(defun jnew-array-from-list (element-type list)
243  "Returns a new Java array with base type ELEMENT-TYPE initialized from a Lisp list
244
245ELEMENT-TYPE is either a string or a class reference."
246  (let ((jarray (jnew-array element-type (length list)))
247        (i 0))
248    (dolist (x list)
249      (setf (jarray-ref jarray i) x
250            i (1+ i)))
251    jarray))
252
253(defun jarray-from-list (list)
254  "Return a Java array from LIST whose type is inferred from the first element
255
256For more control over the type of the array, use JNEW-ARRAY-FROM-LIST."
257  (jnew-array-from-list
258   (jobject-class (first list))
259   list))
260
261(defun list-from-jarray (jarray)
262  "Returns a list with the elements of JARRAY coerced to corresponding Lisp types"
263  (loop for i from 0 below (jarray-length jarray)
264        collect (jarray-ref jarray i)))
265
266(defun vector-from-jarray (jarray)
267  "Returns a vector with the elements of JARRAY coerced to corresponding Lisp types"
268  (loop with vec = (make-array (jarray-length jarray))
269        for i from 0 below (jarray-length jarray)
270        do (setf (aref vec i) (jarray-ref jarray i))
271        finally (return vec)))
272
273(defun list-from-jenumeration (jenumeration)
274  "Returns a list with the elements returned by successive nextElement() calls on the JENUMERATION
275
276JENUMERATION is a reference to a java.util.Enumeration."
277  (loop while (jcall jenumeration
278                     (jmethod "java.util.Enumeration" "hasMoreElements"))
279        collect (jcall jenumeration
280                       (jmethod "java.util.Enumeration" "nextElement"))))
281
282(defun jclass-constructors (class)
283  "Returns a vector of constructors for CLASS"
284  (jcall (jmethod "java.lang.Class" "getConstructors") (jclass class)))
285
286(defun jconstructor-params (constructor)
287  "Returns a vector of parameter types (Java classes) for CONSTRUCTOR"
288  (jcall (jmethod "java.lang.reflect.Constructor" "getParameterTypes") constructor))
289
290(defun jclass-fields (class &key declared public)
291  "Returns a list of all fields of CLASS
292
293The values of the generalized booleans DECLARED and PUBLIC restrict
294the returned values to fields that were declared or public respectively."
295  (let* ((getter (if declared "getDeclaredFields" "getFields"))
296         (fields (jcall (jmethod "java.lang.Class" getter) (jclass class))))
297    (if public (delete-if-not #'jmember-public-p fields) fields)))
298
299(defun jclass-field (class field-name)
300  "Returns the reflected FIELD-NAME of CLASS"
301  (jcall (jmethod "java.lang.Class" "getField" "java.lang.String")
302         (jclass class) field-name))
303
304(defun jfield-type (field)
305  "Returns the type of a reflected Java FIELD"
306  (jcall (jmethod "java.lang.reflect.Field" "getType") field))
307
308(defun jfield-name (field)
309  "Returns the name of reflected Java FIELD"
310  (jcall (jmethod "java.lang.reflect.Field" "getName") field))
311
312
313(defun (setf jfield) (newvalue class-ref-or-field field-or-instance
314                      &optional (instance nil instance-supplied-p) unused-value)
315  (declare (ignore unused-value))
316  (if instance-supplied-p
317      (jfield class-ref-or-field field-or-instance instance newvalue)
318      (jfield class-ref-or-field field-or-instance nil newvalue)))
319
320(defun jclass-methods (class &key declared public)
321  "Returns list of the methods of CLASS
322
323The values of the generalized booleans DECLARED and PUBLIC restrict
324the returned values to methods that were either declared or public
325respectively."
326  (let* ((getter (if declared "getDeclaredMethods" "getMethods"))
327         (methods (jcall (jmethod "java.lang.Class" getter) (jclass class))))
328    (if public (delete-if-not #'jmember-public-p methods) methods)))
329
330(defun jmethod-params (method)
331  "Returns a list of the Java relected parameter types for METHOD"
332  (jcall (jmethod "java.lang.reflect.Method" "getParameterTypes") method))
333
334(defun jmethod-return-type (method)
335  "Returns the Java reflected result type of the METHOD"
336  (jcall (jmethod "java.lang.reflect.Method" "getReturnType") method))
337
338(defun jmethod-declaring-class (method)
339  "Returns the Java class declaring METHOD"
340  (jcall (jmethod "java.lang.reflect.Method" "getDeclaringClass") method))
341
342(defun jmethod-name (method)
343  "Returns the name of METHOD as a Lisp string"
344  (jcall (jmethod "java.lang.reflect.Method" "getName") method))
345
346(defun jinstance-of-p (obj class)
347  "OBJ is an instance of CLASS (or one of its subclasses)"
348  (and (java-object-p obj)
349       (jcall (jmethod "java.lang.Class" "isInstance" "java.lang.Object") (jclass class) obj)))
350
351(defun jmember-static-p (member)
352  "Predicate for whether MEMBER is a static member of its declaring class"
353  (jstatic (jmethod "java.lang.reflect.Modifier" "isStatic" "int")
354           "java.lang.reflect.Modifier"
355           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
356
357(defun jmember-public-p (member)
358  "Predixate for whether MEMBER is a public member of its declaring class"
359  (jstatic (jmethod "java.lang.reflect.Modifier" "isPublic" "int")
360           "java.lang.reflect.Modifier"
361           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
362
363(defun jmember-protected-p (member)
364  "Prediate for whether MEMBER is a protected member of its declaring class"
365  (jstatic (jmethod "java.lang.reflect.Modifier" "isProtected" "int")
366           "java.lang.reflect.Modifier"
367           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
368
369(defmethod make-load-form ((object java-object) &optional environment)
370  (declare (ignore environment))
371  (let ((class-name (jclass-name (jclass-of object))))
372    (cond
373     ((string= class-name "java.lang.reflect.Constructor")
374      `(java:jconstructor ,(jclass-name
375                            (jcall (jmethod "java.lang.reflect.Constructor"
376                                            "getDeclaringClass") object))
377                          ,@(loop for arg-type across
378                              (jcall
379                               (jmethod "java.lang.reflect.Constructor"
380                                        "getParameterTypes")
381                               object)
382                              collecting
383                              (jclass-name arg-type))))
384     ((string= class-name "java.lang.reflect.Method")
385      `(java:jmethod ,(jclass-name
386                       (jcall (jmethod "java.lang.reflect.Method"
387                                       "getDeclaringClass") object))
388                     ,(jmethod-name object)
389                     ,@(loop for arg-type across
390                         (jcall
391                          (jmethod "java.lang.reflect.Method"
392                                   "getParameterTypes")
393                          object)
394                         collecting
395                         (jclass-name arg-type))))
396     ((string= class-name "java.lang.reflect.Field")
397      `(let ((field 
398               (find ,(jcall "getName" object) 
399                     (jcall "getDeclaredFields"
400                            ,(jcall "getDeclaringClass" object))
401                     :key (lambda(el) (jcall "getName" el))
402                     :test 'equal)))
403         (jcall "setAccessible" field t)
404         field))
405     ((jinstance-of-p object "java.lang.Class")
406      `(java:jclass ,(jcall (jmethod "java.lang.Class" "getName") object)))
407     (t
408      (error "Unknown load-form for ~A" class-name)))))
409
410(defun jproperty-value (object property)
411  "setf-able access on the Java Beans notion of property named PROPETRY on OBJECT."
412  (%jget-property-value object property))
413
414(defun (setf jproperty-value) (value obj prop)
415  (%jset-property-value obj prop value))
416
417;;; higher-level operators
418
419(defmacro chain (target op &rest ops)
420  "Performs chained method invocations
421
422TARGET is either the receiver object when the first call is a virtual method
423call or a list in the form (:static <jclass>) when the first method
424call is a static method call.
425
426OP and each of the OPS are either method designators or lists in the
427form (<method designator> &rest args), where a method designator is
428either a string naming a method, or a jmethod object. CHAIN will
429perform the method call specified by OP on TARGET; then, for each
430of the OPS, CHAIN will perform the specified method call using the
431object returned by the previous method call as the receiver, and will
432ultimately return the result of the last method call.  For example,
433the form:
434
435  (chain (:static \"java.lang.Runtime\") \"getRuntime\" (\"exec\" \"ls\"))
436
437is equivalent to the following Java code:
438
439  java.lang.Runtime.getRuntime().exec(\"ls\");"
440  (labels ((canonicalize-op (op) (if (listp op) op (list op)))
441           (compose-arglist (target op) `(,(car op) ,target ,@(cdr op)))
442           (make-binding-for (form) `(,(gensym) ,form))
443           (make-binding (bindings next-op &aux (target (caar bindings)))
444             (cons (make-binding-for
445                    `(jcall ,@(compose-arglist target
446                                               (canonicalize-op next-op))))
447                   bindings)))
448    (let* ((first (if (and (consp target) (eq (first target) :static))
449                      `(jstatic ,@(compose-arglist (cadr target) (canonicalize-op op)))
450                      `(jcall ,@(compose-arglist target (canonicalize-op op)))))
451           (bindings (nreverse
452                      (reduce #'make-binding ops
453                              :initial-value (list (make-binding-for first))))))
454      `(let* ,bindings
455         (declare (ignore ,@(butlast (mapcar #'car bindings))))
456         ,(caar (last bindings))))))
457
458(defmacro jmethod-let (bindings &body body)
459  (let ((args (gensym)))
460    `(let ,(mapcar (lambda (binding)
461                     `(,(car binding) (jmethod ,@(cdr binding))))
462                   bindings)
463       (macrolet ,(mapcar (lambda (binding)
464                            `(,(car binding) (&rest ,args)
465                               `(jcall ,,(car binding) ,@,args)))
466                          bindings)
467         ,@body))))
468
469;;; print-object
470
471(defmethod print-object ((obj java:java-object) stream)
472  (if (jnull-ref-p obj)
473      (write-string "#<null>" stream)
474      (print-java-object-by-class (jobject-class obj) obj stream)))
475
476;;define extensions by eql methods on class name interned in keyword package
477;;e.g. (defmethod java::print-java-object-by-class ((class (eql ':|uk.ac.manchester.cs.owl.owlapi.concurrent.ConcurrentOWLOntologyImpl|)) obj stream)
478;;         (print 'hi)
479;;         (call-next-method))
480(defmethod print-java-object-by-class :around (class obj stream)
481  (handler-bind ((java-exception #'(lambda(c)
482                                     (format stream "#<~a, while printing a ~a>"
483                                             (jcall "toString" (java-exception-cause  c))
484                                             (jcall "getName" (jcall "getClass" obj)))
485                                     (return-from print-java-object-by-class))))
486    (call-next-method)))
487
488;; we have to do our own inheritence for the java class
489(defmethod print-java-object-by-class (class obj stream)
490  (loop for super = class then (jclass-superclass super)
491        for keyword = (intern (jcall "getName" super) 'keyword)
492        for method = (find-method #'print-java-object-by-class nil (list `(eql ,keyword) t t) nil)
493        while (jclass-superclass super)
494        when method do (return-from print-java-object-by-class
495                         (print-java-object-by-class keyword obj stream)))
496  (write-string (sys::%write-to-string obj) stream))
497
498(defmethod print-object ((e java:java-exception) stream)
499  (handler-bind ((java-exception #'(lambda(c)
500                                     (format stream "#<~a,while printing a ~a>"
501                                             (jcall "toString" (java-exception-cause  c))
502                                             (jcall "getName" (jcall "getClass" e)))
503                                     (return-from print-object))))
504    (if *print-escape*
505        (print-unreadable-object (e stream :type t :identity t)
506          (format stream "~A"
507                  (java:jcall (java:jmethod "java.lang.Object" "toString")
508                              (java:java-exception-cause e))))
509        (format stream "Java exception '~A'."
510                (java:jcall (java:jmethod "java.lang.Object" "toString")
511                            (java:java-exception-cause e))))))
512
513;;; JAVA-CLASS support
514(defconstant +java-lang-object+ (jclass "java.lang.Object"))
515
516(defclass java-class (standard-class)
517  ((jclass :initarg :java-class
518           :initform (error "class is required")
519           :reader java-class-jclass)))
520
521;;; FIXME (rudi 2012-05-02): consider replacing the metaclass of class
522;;; java-object to be java-class here instead of allowing this subclass
523;;; relationship.  On the other hand, abcl ran for the longest time
524;;; without an implementation of validate-superclass, so this doesn't
525;;; introduce new sources for bugs.
526(defmethod mop:validate-superclass ((class java-class) (superclass built-in-class))
527  t)
528
529;;init java.lang.Object class
530(defconstant +java-lang-object-class+
531  (%register-java-class +java-lang-object+
532                        (mop::ensure-class (make-symbol "java.lang.Object")
533                                           :metaclass (find-class 'java-class)
534                                           :direct-superclasses (list (find-class 'java-object))
535                                           :java-class +java-lang-object+)))
536
537(defun jclass-additional-superclasses (jclass)
538  "Extension point to put additional CLOS classes on the CPL of a CLOS Java class"
539  (let ((supers nil))
540    (when (jclass-interface-p jclass)
541      (push (find-class 'java-object) supers))
542    supers))
543
544(defun ensure-java-class (jclass)
545  "Attempt to ensure that the Java class referenced by JCLASS exists in the current process of the implementation"
546  (let ((class (%find-java-class jclass)))
547    (if class
548        class
549        (%register-java-class
550         jclass (mop::ensure-class
551                 (make-symbol (jclass-name jclass))
552                 :metaclass (find-class 'java-class)
553                 :direct-superclasses
554                 (let ((supers
555                        (mapcar #'ensure-java-class
556                                (delete nil
557                                        (concatenate 'list
558                                                     (list (jclass-superclass jclass))
559                                                     (jclass-interfaces jclass))))))
560                   (append supers (jclass-additional-superclasses jclass)))
561                 :java-class jclass)))))
562
563(defmethod mop::compute-class-precedence-list ((class java-class))
564  "Sort classes this way:
565   1. Java classes (but not java.lang.Object)
566   2. Java interfaces
567   3. java.lang.Object
568   4. other classes
569   Rationale:
570   1. Concrete classes are the most specific.
571   2. Then come interfaces.
572     So if a generic function is specialized both on an interface and a concrete class,
573     the concrete class comes first.
574   3. because everything is an Object.
575   4. to handle base CLOS classes.
576   Note: Java interfaces are not sorted among themselves in any way, so if a
577   gf is specialized on two different interfaces and you apply it to an object that
578   implements both, it is unspecified which method will be called."
579  (let ((cpl (nreverse (mop::collect-superclasses* class))))
580    (flet ((score (class)
581             (if (not (typep class 'java-class))
582                 4
583                 (cond
584                   ((jcall (jmethod "java.lang.Object" "equals" "java.lang.Object")
585                           (java-class-jclass class) +java-lang-object+) 3)
586                   ((jclass-interface-p (java-class-jclass class)) 2)
587                   (t 1)))))
588      (stable-sort cpl #'(lambda (x y)
589                           (< (score x) (score y)))))))
590         
591(defmethod make-instance ((class java-class) &rest initargs &key &allow-other-keys)
592  (declare (ignore initargs))
593  (error "make-instance not supported for ~S" class))
594
595(defun jinput-stream (pathname)
596  "Returns a java.io.InputStream for resource denoted by PATHNAME"
597  (sys:get-input-stream pathname))
598
599(provide "JAVA")
600
Note: See TracBrowser for help on using the repository browser.