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

Last change on this file was 12831, checked in by astalla, 14 years ago

First stab at Java collections integration with the sequences protocol.

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