source: branches/1.1.x/src/org/armedbear/lisp/java.lisp

Last change on this file was 14127, checked in by ehuelsmann, 12 years ago

Reindent documentation string.

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