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

Last change on this file since 13710 was 13710, checked in by astalla, 12 years ago

First stab at restoring runtime-class.
Supported: extending a Java class, implementing interfaces, defining methods
of up to 7 non-primitive arguments returning void or a non-primitive object.
Unsupported: everything else, including fields, constructors, annotations,
primitive arguments and return values, and the LispObject[] call convention
for functions with more than 8 arguments.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 21.6 KB
Line 
1;;; java.lisp
2;;;
3;;; Copyright (C) 2003-2007 Peter Graves, Andras Simon
4;;; $Id: java.lisp 13710 2011-12-27 19:50:08Z astalla $
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(defun add-url-to-classpath (url &optional (classloader *classloader*))
40  (jcall "addUrl" classloader url))
41
42(defun add-urls-to-classpath (&rest urls)
43  (dolist (url urls)
44    (add-url-to-classpath url)))
45
46(defgeneric add-to-classpath (jar-or-jars &optional classloader)
47  (:documentation "Add JAR-OR-JARS to the JVM classpath optionally specifying the CLASSLOADER to add.
48
49JAR-OR-JARS is either a pathname designating a jar archive or the root
50directory to search for classes or a list of such values."))
51
52(defmethod add-to-classpath (jar-or-jars &optional (classloader (get-current-classloader)))
53  (%add-to-classpath jar-or-jars classloader))
54
55(defun jregister-handler (object event handler &key data count)
56  (%jregister-handler object event handler data count))
57
58(defun jinterface-implementation (interface &rest method-names-and-defs)
59  "Creates and returns an implementation of a Java interface with
60   methods calling Lisp closures as given in METHOD-NAMES-AND-DEFS.
61
62   INTERFACE is either a Java interface or a string naming one.
63
64   METHOD-NAMES-AND-DEFS is an alternating list of method names
65   (strings) and method definitions (closures).
66
67   For missing methods, a dummy implementation is provided that
68   returns nothing or null depending on whether the return type is
69   void or not. This is for convenience only, and a warning is issued
70   for each undefined method."
71  (let ((interface (jclass interface))
72        (implemented-methods
73         (loop for m in method-names-and-defs
74           for i from 0
75           if (evenp i)
76           do (assert (stringp m) (m) "Method names must be strings: ~s" m) and collect m
77           else
78           do (assert (or (symbolp m) (functionp m)) (m) "Methods must be function designators: ~s" m))))
79    (loop for method across
80      (jclass-methods interface :declared nil :public t)
81      for method-name = (jmethod-name method)
82      when (not (member method-name implemented-methods :test #'string=))
83      do
84      (let* ((void-p (string= (jclass-name (jmethod-return-type method)) "void"))
85             (arglist (when (plusp (length (jmethod-params method))) '(&rest ignore)))
86             (def `(lambda
87                     ,arglist
88                     ,(when arglist '(declare (ignore ignore)))
89                     ,(if void-p '(values) java:+null+))))
90        (warn "Implementing dummy method ~a for interface ~a"
91              method-name (jclass-name interface))
92        (push (coerce def 'function) method-names-and-defs)
93        (push method-name method-names-and-defs)))
94    (apply #'%jnew-proxy interface method-names-and-defs)))
95
96(defun jmake-invocation-handler (function)
97  (%jmake-invocation-handler function))
98
99(when (autoloadp 'jmake-proxy)
100  (fmakunbound 'jmake-proxy))
101
102(defgeneric jmake-proxy (interface implementation &optional lisp-this)
103  (:documentation "Returns a proxy Java object implementing the provided interface(s) using methods implemented in Lisp - 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."))
104
105(defun canonicalize-jproxy-interfaces (ifaces)
106  (if (listp ifaces)
107      (mapcar #'jclass ifaces)
108      (list (jclass ifaces))))
109
110
111(defmethod jmake-proxy (interface invocation-handler &optional lisp-this)
112  "Basic implementation that directly uses an invocation handler."
113  (%jmake-proxy (canonicalize-jproxy-interfaces interface) invocation-handler lisp-this))
114
115(defmethod jmake-proxy (interface (implementation function) &optional lisp-this)
116  "Implements a Java interface forwarding method calls to a Lisp function."
117  (%jmake-proxy (canonicalize-jproxy-interfaces interface) (jmake-invocation-handler implementation) lisp-this))
118
119(defmethod jmake-proxy (interface (implementation package) &optional lisp-this)
120  "Implements a Java interface mapping Java method names to symbols in a given package. 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."
121  (flet ((java->lisp (name)
122     (with-output-to-string (str)
123       (let ((last-lower-p nil))
124         (map nil (lambda (char)
125        (let ((upper-p (char= (char-upcase char) char)))
126          (when (and last-lower-p upper-p)
127            (princ "-" str))
128          (setf last-lower-p (not upper-p))
129          (princ (char-upcase char) str)))
130        name)))))
131    (%jmake-proxy (canonicalize-jproxy-interfaces interface)
132      (jmake-invocation-handler 
133       (lambda (obj method &rest args)
134         (let ((sym (find-symbol
135         (java->lisp method)
136         implementation)))
137           (unless sym
138       (error "Symbol ~A, implementation of method ~A, not found in ~A"
139          (java->lisp method)
140          method
141          implementation))
142       (if (fboundp sym)
143           (apply (symbol-function sym) obj method args)
144           (error "Function ~A, implementation of method ~A, not found in ~A"
145            sym method implementation)))))
146      lisp-this)))
147
148(defmethod jmake-proxy (interface (implementation hash-table) &optional lisp-this)
149  "Implements a Java interface using closures in an hash-table keyed by Java method name."
150  (%jmake-proxy (canonicalize-jproxy-interfaces interface)
151    (jmake-invocation-handler 
152     (lambda (obj method &rest args)
153       (let ((fn (gethash method implementation)))
154         (if fn
155       (apply fn obj args)
156       (error "Implementation for method ~A not found in ~A"
157        method implementation)))))
158    lisp-this))
159
160(defun jequal (obj1 obj2)
161  "Compares obj1 with obj2 using java.lang.Object.equals()"
162  (jcall (jmethod "java.lang.Object" "equals" "java.lang.Object")
163   obj1 obj2))
164
165(defun jobject-class (obj)
166  "Returns the Java class that OBJ belongs to"
167  (jcall (jmethod "java.lang.Object" "getClass") obj))
168
169(defun jclass-superclass (class)
170  "Returns the superclass of CLASS, or NIL if it hasn't got one"
171  (jcall (jmethod "java.lang.Class" "getSuperclass") (jclass class)))
172
173(defun jclass-interfaces (class)
174  "Returns the vector of interfaces of CLASS"
175  (jcall (jmethod "java.lang.Class" "getInterfaces") (jclass class)))
176
177(defun jclass-interface-p (class)
178  "Returns T if CLASS is an interface"
179  (jcall (jmethod "java.lang.Class" "isInterface") (jclass class)))
180
181(defun jclass-superclass-p (class-1 class-2)
182  "Returns T if CLASS-1 is a superclass or interface of CLASS-2"
183  (jcall (jmethod "java.lang.Class" "isAssignableFrom" "java.lang.Class")
184         (jclass class-1)
185         (jclass class-2)))
186
187(defun jclass-array-p (class)
188  "Returns T if CLASS is an array class"
189  (jcall (jmethod "java.lang.Class" "isArray") (jclass class)))
190
191(defun jarray-component-type (atype)
192  "Returns the component type of the array type ATYPE"
193  (assert (jclass-array-p atype))
194  (jcall (jmethod "java.lang.Class" "getComponentType") atype))
195
196(defun jarray-length (java-array)
197  (jstatic "getLength" "java.lang.reflect.Array" java-array)  )
198
199(defun (setf jarray-ref) (new-value java-array &rest indices)
200  (apply #'jarray-set java-array new-value indices))
201
202(defun jnew-array-from-array (element-type array)
203  "Returns a new Java array with base type ELEMENT-TYPE (a string or a class-ref)
204   initialized from ARRAY"
205  (flet
206    ((row-major-to-index (dimensions n)
207                         (loop for dims on dimensions
208                           with indices
209                           do
210                           (multiple-value-bind (m r) (floor n (apply #'* (cdr dims)))
211                             (push m indices)
212                             (setq n r))
213                           finally (return (nreverse indices)))))
214    (let* ((fill-pointer (when (array-has-fill-pointer-p array) (fill-pointer array)))
215           (dimensions (if fill-pointer (list fill-pointer) (array-dimensions array)))
216           (jarray (apply #'jnew-array element-type dimensions)))
217      (dotimes (i (if fill-pointer fill-pointer (array-total-size array)) jarray)
218        #+maybe_one_day
219        (setf (apply #'jarray-ref jarray (row-major-to-index dimensions i)) (row-major-aref array i))
220        (apply #'(setf jarray-ref) (row-major-aref array i) jarray (row-major-to-index dimensions i))))))
221
222(defun jnew-array-from-list (element-type list)
223  (let ((jarray (jnew-array element-type (length list)))
224  (i 0))
225    (dolist (x list)
226      (setf (jarray-ref jarray i) x
227      i (1+ i)))
228    jarray))
229
230(defun jarray-from-list (list)
231  "Return a Java array from LIST whose type is inferred from the first element.
232
233For more control over the type of the array, use JNEW-ARRAY-FROM-LIST."
234  (jnew-array-from-list
235   (jobject-class (first list))
236   list))
237
238(defun list-from-jarray (jarray)
239  "Returns a list with the elements of `jarray`."
240  (loop for i from 0 below (jarray-length jarray)
241        collect (jarray-ref jarray i)))
242
243(defun vector-from-jarray (jarray)
244  "Returns a vector with the elements of `jarray`."
245  (loop with vec = (make-array (jarray-length jarray))
246        for i from 0 below (jarray-length jarray)
247        do (setf (aref vec i) (jarray-ref jarray i))
248        finally (return vec)))
249
250(defun list-from-jenumeration (jenumeration)
251  "Returns a list with the elements returned by successive `nextElement`
252calls on the java.util.Enumeration `jenumeration`."
253  (loop while (jcall jenumeration
254                     (jmethod "java.util.Enumeration" "hasMoreElements"))
255        collect (jcall jenumeration
256                       (jmethod "java.util.Enumeration" "nextElement"))))
257
258(defun jclass-constructors (class)
259  "Returns a vector of constructors for CLASS"
260  (jcall (jmethod "java.lang.Class" "getConstructors") (jclass class)))
261
262(defun jconstructor-params (constructor)
263  "Returns a vector of parameter types (Java classes) for CONSTRUCTOR"
264  (jcall (jmethod "java.lang.reflect.Constructor" "getParameterTypes") constructor))
265
266(defun jclass-fields (class &key declared public)
267  "Returns a vector of all (or just the declared/public, if DECLARED/PUBLIC is true) fields of CLASS"
268  (let* ((getter (if declared "getDeclaredFields" "getFields"))
269         (fields (jcall (jmethod "java.lang.Class" getter) (jclass class))))
270    (if public (delete-if-not #'jmember-public-p fields) fields)))
271
272(defun jclass-field (class field-name)
273  "Returns the field named FIELD-NAME of CLASS"
274  (jcall (jmethod "java.lang.Class" "getField" "java.lang.String")
275         (jclass class) field-name))
276
277(defun jfield-type (field)
278  "Returns the type (Java class) of FIELD"
279  (jcall (jmethod "java.lang.reflect.Field" "getType") field))
280
281(defun jfield-name (field)
282  "Returns the name of FIELD as a Lisp string"
283  (jcall (jmethod "java.lang.reflect.Field" "getName") field))
284
285
286(defun (setf jfield) (newvalue class-ref-or-field field-or-instance
287          &optional (instance nil instance-supplied-p) unused-value)
288  (declare (ignore unused-value))
289  (if instance-supplied-p
290      (jfield class-ref-or-field field-or-instance instance newvalue)
291      (jfield class-ref-or-field field-or-instance nil newvalue)))
292
293(defun jclass-methods (class &key declared public)
294  "Return a vector of all (or just the declared/public, if DECLARED/PUBLIC is true) methods of CLASS"
295  (let* ((getter (if declared "getDeclaredMethods" "getMethods"))
296         (methods (jcall (jmethod "java.lang.Class" getter) (jclass class))))
297    (if public (delete-if-not #'jmember-public-p methods) methods)))
298
299(defun jmethod-params (method)
300  "Returns a vector of parameter types (Java classes) for METHOD"
301  (jcall (jmethod "java.lang.reflect.Method" "getParameterTypes") method))
302
303(defun jmethod-return-type (method)
304  "Returns the result type (Java class) of the METHOD"
305  (jcall (jmethod "java.lang.reflect.Method" "getReturnType") method))
306
307(defun jmethod-declaring-class (method)
308  "Returns the Java class declaring METHOD"
309  (jcall (jmethod "java.lang.reflect.Method" "getDeclaringClass") method))
310
311(defun jmethod-name (method)
312  "Returns the name of METHOD as a Lisp string"
313  (jcall (jmethod "java.lang.reflect.Method" "getName") method))
314
315(defun jinstance-of-p (obj class)
316  "OBJ is an instance of CLASS (or one of its subclasses)"
317  (and (java-object-p obj)
318       (jcall (jmethod "java.lang.Class" "isInstance" "java.lang.Object") (jclass class) obj)))
319
320(defun jmember-static-p (member)
321  "MEMBER is a static member of its declaring class"
322  (jstatic (jmethod "java.lang.reflect.Modifier" "isStatic" "int")
323           "java.lang.reflect.Modifier"
324           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
325
326(defun jmember-public-p (member)
327  "MEMBER is a public member of its declaring class"
328  (jstatic (jmethod "java.lang.reflect.Modifier" "isPublic" "int")
329           "java.lang.reflect.Modifier"
330           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
331
332(defun jmember-protected-p (member)
333  "MEMBER is a protected member of its declaring class"
334  (jstatic (jmethod "java.lang.reflect.Modifier" "isProtected" "int")
335           "java.lang.reflect.Modifier"
336           (jcall (jmethod "java.lang.reflect.Member" "getModifiers") member)))
337
338(defmethod make-load-form ((object java-object) &optional environment)
339  (declare (ignore environment))
340  (let ((class-name (jclass-name (jclass-of object))))
341    (cond
342     ((string= class-name "java.lang.reflect.Constructor")
343      `(java:jconstructor ,(jclass-name
344                            (jcall (jmethod "java.lang.reflect.Constructor"
345                                            "getDeclaringClass") object))
346                          ,@(loop for arg-type across
347                              (jcall
348                               (jmethod "java.lang.reflect.Constructor"
349                                        "getParameterTypes")
350                               object)
351                              collecting
352                              (jclass-name arg-type))))
353     ((string= class-name "java.lang.reflect.Method")
354      `(java:jmethod ,(jclass-name
355                       (jcall (jmethod "java.lang.reflect.Method"
356                                       "getDeclaringClass") object))
357                     ,(jmethod-name object)
358                     ,@(loop for arg-type across
359                         (jcall
360                          (jmethod "java.lang.reflect.Method"
361                                   "getParameterTypes")
362                          object)
363                         collecting
364                         (jclass-name arg-type))))
365     ((jinstance-of-p object "java.lang.Class")
366      `(java:jclass ,(jcall (jmethod "java.lang.Class" "getName") object)))
367     (t
368      (error "Unknown load-form for ~A" class-name)))))
369
370(defun jproperty-value (obj prop)
371  (%jget-property-value obj prop))
372
373(defun (setf jproperty-value) (value obj prop)
374  (%jset-property-value obj prop value))
375
376;;; higher-level operators
377
378(defmacro chain (target op &rest ops)
379  "Performs chained method invocations. `target' is the receiver object (when the first call is a virtual method call) or a list in the form (:static <jclass>) when the first method call is a static method call. `op' and each of the `ops' are either method designators or lists in the form (<method designator> &rest args), where a method designator is either a string naming a method, or a jmethod object. `chain' will perform the method call specified by `op' on `target'; then, for each of the `ops', `chain' will perform the specified method call using the object returned by the previous method call as the receiver, and will ultimately return the result of the last method call.
380  For example, the form:
381
382  (chain (:static \"java.lang.Runtime\") \"getRuntime\" (\"exec\" \"ls\"))
383
384  is equivalent to the following Java code:
385
386  java.lang.Runtime.getRuntime().exec(\"ls\");"
387  (labels ((canonicalize-op (op) (if (listp op) op (list op)))
388     (compose-arglist (target op) `(,(car op) ,target ,@(cdr op)))
389     (make-binding-for (form) `(,(gensym) ,form))
390     (make-binding (bindings next-op &aux (target (caar bindings)))
391       (cons (make-binding-for
392        `(jcall ,@(compose-arglist target
393                 (canonicalize-op next-op))))
394       bindings)))
395    (let* ((first (if (and (consp target) (eq (first target) :static))
396          `(jstatic ,@(compose-arglist (cadr target) (canonicalize-op op)))
397          `(jcall ,@(compose-arglist target (canonicalize-op op)))))
398     (bindings (nreverse
399          (reduce #'make-binding ops
400            :initial-value (list (make-binding-for first))))))
401      `(let* ,bindings
402   (declare (ignore ,@(mapcar #'car bindings)))))))
403
404(defmacro jmethod-let (bindings &body body)
405  (let ((args (gensym)))
406    `(let ,(mapcar (lambda (binding)
407         `(,(car binding) (jmethod ,@(cdr binding))))
408       bindings)
409       (macrolet ,(mapcar (lambda (binding)
410          `(,(car binding) (&rest ,args)
411             `(jcall ,,(car binding) ,@,args)))
412        bindings)
413   ,@body))))
414
415;;; print-object
416
417(defmethod print-object ((obj java:java-object) stream)
418  (write-string (sys::%write-to-string obj) stream))
419
420(defmethod print-object ((e java:java-exception) stream)
421  (if *print-escape*
422      (print-unreadable-object (e stream :type t :identity t)
423        (format stream "~A"
424                (java:jcall (java:jmethod "java.lang.Object" "toString")
425                            (java:java-exception-cause e))))
426      (format stream "Java exception '~A'."
427              (java:jcall (java:jmethod "java.lang.Object" "toString")
428                          (java:java-exception-cause e)))))
429
430;;; JAVA-CLASS support
431(defconstant +java-lang-object+ (jclass "java.lang.Object"))
432
433(defclass java-class (standard-class)
434  ((jclass :initarg :java-class
435     :initform (error "class is required")
436     :reader java-class-jclass)))
437
438;;init java.lang.Object class
439(defconstant +java-lang-object-class+
440  (%register-java-class +java-lang-object+
441      (mop::ensure-class (make-symbol "java.lang.Object")
442             :metaclass (find-class 'java-class)
443             :direct-superclasses (list (find-class 'java-object))
444             :java-class +java-lang-object+)))
445
446(defun jclass-additional-superclasses (jclass)
447  "Extension point to put additional CLOS classes on the CPL of a CLOS Java class."
448  (let ((supers nil))
449    (when (jclass-interface-p jclass)
450      (push (find-class 'java-object) supers))
451    supers))
452
453(defun ensure-java-class (jclass)
454  (let ((class (%find-java-class jclass)))
455    (if class
456  class
457  (%register-java-class
458   jclass (mop::ensure-class
459     (make-symbol (jclass-name jclass))
460     :metaclass (find-class 'java-class)
461     :direct-superclasses
462     (let ((supers
463      (mapcar #'ensure-java-class
464        (delete nil
465          (concatenate 'list
466                 (list (jclass-superclass jclass))
467                 (jclass-interfaces jclass))))))
468       (append supers (jclass-additional-superclasses jclass)))
469     :java-class jclass)))))
470
471(defmethod mop::compute-class-precedence-list ((class java-class))
472  "Sort classes this way:
473   1. Java classes (but not java.lang.Object)
474   2. Java interfaces
475   3. java.lang.Object
476   4. other classes
477   Rationale:
478   1. Concrete classes are the most specific.
479   2. Then come interfaces.
480     So if a generic function is specialized both on an interface and a concrete class,
481     the concrete class comes first.
482   3. because everything is an Object.
483   4. to handle base CLOS classes.
484   Note: Java interfaces are not sorted among themselves in any way, so if a
485   gf is specialized on two different interfaces and you apply it to an object that
486   implements both, it is unspecified which method will be called."
487  (let ((cpl (nreverse (mop::collect-superclasses* class))))
488    (flet ((score (class)
489       (if (not (typep class 'java-class))
490     4
491     (cond
492       ((jcall (jmethod "java.lang.Object" "equals" "java.lang.Object")
493         (java-class-jclass class) +java-lang-object+) 3)
494       ((jclass-interface-p (java-class-jclass class)) 2)
495       (t 1)))))
496      (stable-sort cpl #'(lambda (x y)
497         (< (score x) (score y)))))))
498   
499(defmethod make-instance ((class java-class) &rest initargs &key &allow-other-keys)
500  (declare (ignore initargs))
501  (error "make-instance not supported for ~S" class))
502
503(provide "JAVA")
Note: See TracBrowser for help on using the repository browser.