% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \subsection{library(jpl): A Java interface for SWI Prolog 7.x} \label{sec:jpl} \begin{tags} \tag{See also} \url{http://jpl7.org/} \end{tags} The \file{library(jpl)} provides a bidirectional interface to a Java Virtual Machine.\vspace{0.7cm} \begin{description} \predicate[det]{jpl_new}{3}{+X, +Params, -V} \arg{X} can be: \begin{shortlist} \item an atomic classname, e.g. \verb$'java.lang.String'$ \item or an atomic descriptor, e.g. \verb$'[I'$ or \verb$'Ljava.lang.String;'$ \item or a suitable type, i.e. any \verb$class(_,_)$ or \verb$array(_)$, e.g. \verb$class([java,util],['Date'])$ \end{shortlist} If \arg{X} is an object (non-array) type or descriptor and \arg{Params} is a list of values or references, then \arg{V} is the result of an invocation of that type's most specifically-typed constructor to whose respective formal parameters the actual \arg{Params} are assignable (and assigned). If \arg{X} is an array type or descriptor and \arg{Params} is a list of values or references, each of which is (independently) assignable to the array element type, then \arg{V} is a new array of as many elements as \arg{Params} has members, initialised with the respective members of \arg{Params}. If \arg{X} is an array type or descriptor and \arg{Params} is a non-negative integer N, then \arg{V} is a new array of that type, with N elements, each initialised to Java's appropriate default value for the type. If \arg{V} is literally \verb${Term}$ then we attempt to convert a \verb$new org.jpl7.Term$ instance to a corresponding term; this is of little obvious use here, but is consistent with \predref{jpl_call}{4} and \predref{jpl_get}{3}. \predicate[det]{jpl_call}{4}{+X, +MethodName:atom, +Params:list(datum), -Result:datum} \arg{X} should be either \begin{itemize} \item an object reference, e.g. \verb$(1552320)$ (for static or instance methods) \item or a classname, e.g. \verb$'java.util.Date'$ (for static methods only) \item or a descriptor, e.g. \verb$'Ljava.util.Date;'$ (for static methods only) \item or type, e.g. \verb$class([java,util],['Date'])$ (for static methods only) \end{itemize} \arg{MethodName} should be a method name (as an atom) (may involve dynamic overload resolution based on inferred types of params) \arg{Params} should be a proper list (perhaps empty) of suitable actual parameters for the named method. The class or object may have several methods with the given name; JPL will resolve (per call) to the most appropriate method based on the quantity and inferred types of \arg{Params}. This resolution mimics the corresponding static resolution performed by Java compilers. Finally, an attempt will be made to unify \arg{Result} with the method's returned value, or with \verb$@(void)$ (the compound term with name \verb$@$ and argument \verb$void$) if it has none. \predicate[det]{jpl_get}{3}{+X, +Fspec, -V:datum} \arg{X} can be \begin{itemize} \item a classname \item or a descriptor \item or an (object or array) type (for static fields) \item or a non-array object (for static and non-static fields) \item or an array (for 'length' pseudo field, or indexed element retrieval) \end{itemize} \arg{Fspec} can be \begin{itemize} \item an atomic field name \item or an integral array index (to get an element from an array) \item or a pair I-J of integers (to get a subrange of an array). \end{itemize} Finally, an attempt will be made to unify \arg{V} with the retrieved value or object reference. Examples \begin{code} jpl_get('java.awt.Cursor', 'NE_RESIZE_CURSOR', Q). Q = 7. jpl_new(array(class([java,lang],['String'])), [for,while,do,if,then,else,try,catch,finally], A), jpl_get(A, 3-5, B). B = [if, then, else]. \end{code} \predicate[det]{jpl_set}{3}{+X, +Fspec, +V} sets the \arg{Fspec}-th field of (class or object) \arg{X} to value \arg{V} iff it is assignable \arg{X} can be \begin{itemize} \item a class instance (for static or non-static fields) \item or an array (for indexed element or subrange assignment) \item or a classname, or a \verb$class(_,_)$ or \verb$array(_)$ type (for static fields) \item but not a String (no fields to retrieve) \end{itemize} \arg{Fspec} can be \begin{itemize} \item an atomic field name (overloading through shadowing has yet to be handled properly) \item or an array index I (\arg{X} must be an array object: \arg{V} is assigned to \arg{X}[I]) \item or a pair I-J of integers (\arg{X} must be an array object, \arg{V} must be a list of values: successive members of \arg{V} are assigned to \arg{X}[I..J]) \end{itemize} \arg{V} must be a suitable value or object. \predicate[det]{jpl_get_default_jvm_opts}{1}{-Opts:list(atom)} Returns (as a list of atoms) the options which will be passed to the JVM when it is initialised, e.g. \verb$['-Xrs']$ \predicate[det]{jpl_set_default_jvm_opts}{1}{+Opts:list(atom)} Replaces the default JVM initialisation options with those supplied. \predicate[semidet]{jpl_get_actual_jvm_opts}{1}{-Opts:list(atom)} Returns (as a list of atoms) the options with which the JVM was initialised. Fails silently if a JVM has not yet been started, and can thus be used to test for this. \predicate{jpl_pl_lib_version}{1}{-Version} \arg{Version} is the fully qualified version identifier of the in-use Prolog component (\file{jpl.pl}) of JPL. It should exactly match the version identifiers of JPL's C (jpl.c) and Java (jpl.jar) components. Example \begin{code} ?- jpl_pl_lib_version(V). V = '7.6.1'. \end{code} \predicate{jpl_c_lib_version}{1}{-Version} \arg{Version} is the fully qualified version identifier of the in-use C component (jpl.c) of JPL. It should exactly match the version identifiers of JPL's Prolog (\file{jpl.pl}) and Java (jpl.jar) components. Example \begin{code} ?- jpl_c_lib_version(V). V = '7.4.0-alpha'. \end{code} \predicate{jpl_class_to_classname}{2}{+Class:jref, -ClassName:entityName} \arg{Class} is a reference to a class object. \arg{ClassName} is its canonical (?) source-syntax (dotted) name, e.g. \verb$'java.util.Date'$ NB not used outside jni_junk and jpl_test (is this (still) true?) NB oughta use the available caches (but their indexing doesn't suit) \file{TODO} This shouldn't exist as we have \predref{jpl_class_to_entityname}{2} ??? The implementation actually just calls \verb$Class.getName()$ to get the entity name (dotted name) \predicate{jpl_class_to_type}{2}{+Class:jref, -Type:jpl_type} The \arg{Class} is a reference to a (Java Universe) instance of \verb$java.lang.Class$. The \arg{Type} is the (Prolog Universe) JPL type term denoting the same type as does the instance of \arg{Class}. NB should ensure that, if not found in cache, then cache is updated. Intriguingly, getParameterTypes returns class objects (undocumented AFAIK) with names 'boolean', 'byte' etc. and even 'void' (?!) \predicate{jpl_classname_to_class}{2}{+EntityName:atom, -Class:jref} \arg{EntityName} is the entity name to be mapped to a class reference. \arg{Class} is a (canonical) reference to the corresponding class object. NB uses caches where the class has already been mapped once before. \predicate{jpl_entityname_to_type}{2}{+EntityName:atom, -Type:jpl_type} \arg{EntityName} is the entity name (an atom) denoting a Java type, to be mapped to a JPL type. This is the string returned by \verb$java.lang.Class.getName()$. \arg{Type} is the JPL type (a ground term) denoting the same Java type as \arg{EntityName} does. The Java type in question may be a reference type (class, abstract class, interface), and array type or a primitive, including "void". Examples: \begin{code} int int integer class([],[integer]) void void char char double double [D array(double) [[I array(array(int)) java.lang.String class([java,lang],['String']) [Ljava.lang.String; array(class([java,lang],['String'])) [[Ljava.lang.String; array(array(class([java, lang], ['String']))) [[[Ljava.util.Calendar; array(array(array(class([java,util],['Calendar'])))) foo.bar.Bling$Blong class([foo,bar],['Bling','Blong']) \end{code} NB uses caches where the class has already been mapped once before. \begin{tags} \tag{See also} \url{https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Class.html\#getName()} \end{tags} \predicate{jpl_type_to_entityname}{2}{+Type:jpl_type, -EntityName:atom} This is the converse of \predref{jpl_entityname_to_type}{2} \predicate{jpl_classname_to_type}{2}{+EntityName:atom, -Type:jpl_type} This is a wrapper around \predref{jpl_entityname_to_type}{2} to keep the old exported predicate alive. The name of this predicate does not fully reflect that it actually deals in entity names instead of just class names. Use \predref{jpl_entityname_to_type}{2} in preference. \predicate{jpl_type_to_classname}{2}{+Type:jpl_type, -EntityName:atom} This is a wrapper around \predref{jpl_type_to_entityname}{2} to keep the old exported predicate alive. The name of this predicate does not fully reflect that it actually deals in entity names instead of just class names. Use \predref{jpl_type_to_entityname}{2} in preference. \predicate{jpl_datum_to_type}{2}{+Datum:datum, -Type:type} \arg{Datum} must be a JPL representation of an instance of one (or more) Java types; \arg{Type} is the unique most specialised type of which \arg{Datum} denotes an instance; NB 3 is an instance of byte, char, short, int and long, of which byte and char are the joint, overlapping most specialised types, so this relates 3 to the pseudo subtype 'char_byte'; \begin{tags} \tag{See also} \predref{jpl_type_to_preferred_concrete_type}{2} for converting inferred types to instantiable types \end{tags} \predicate{jpl_object_to_class}{2}{+Object:jref, -Class:jref} fails silently if \arg{Object} is not a valid reference to a Java object \arg{Class} is a (canonical) reference to the (canonical) class object which represents the class of \arg{Object} NB what's the point of caching the type if we don't look there first? \predicate{jpl_object_to_type}{2}{+Object:jref, -Type:type} \arg{Object} must be a proper JPL reference to a Java object (i.e. a class or array instance, but not null, void or String). \arg{Type} is the JPL type of that object. \predicate[nondet]{jpl_primitive_type}{1}{-Type:atom} \arg{Type} is an atomic JPL representation of one of Java's primitive types. N.B: \const{void} is not included. \begin{code} ?- setof(Type, jpl_primitive_type(Type), Types). Types = [boolean, byte, char, double, float, int, long, short]. \end{code} \predicate{jpl_ref_to_type}{2}{+Ref:jref, -Type:type} \arg{Ref} must be a proper JPL reference (to an object, null or void). \arg{Type} is its type. \predicate{jpl_type_to_class}{2}{+Type:jpl_type, -Class:jref} \arg{Type} is the JPL type, a ground term designating a class or an array type. Incomplete types are now never cached (or otherwise passed around). jFindClass throws an exception if FCN can't be found. \predicate{jpl_is_class}{1}{@Term} True if \arg{Term} is a JPL reference to an instance of \verb$java.lang.Class$. \predicate{jpl_is_false}{1}{@Term} True if \arg{Term} is \verb$@(false)$, the JPL representation of the Java boolean value 'false'. \predicate{jpl_is_null}{1}{@Term} True if \arg{Term} is \verb$@(null)$, the JPL representation of Java's 'null' reference. \predicate{jpl_is_object}{1}{@Term} True if \arg{Term} is a well-formed JPL object reference. NB this checks only syntax, not whether the object exists. \predicate{jpl_is_object_type}{1}{@Term} True if \arg{Term} is an object (class or array) type, not e.g. a primitive, null or void. \predicate{jpl_is_ref}{1}{@Term} True if \arg{Term} is a well-formed JPL reference, either to a Java object or to Java's notional but important 'null' non-object. \predicate{jpl_is_true}{1}{@Term} True if \arg{Term} is \verb$@(true)$, the JPL representation of the Java boolean value 'true'. \predicate{jpl_is_type}{1}{@Term} True if \arg{Term} is a well-formed JPL type structure. \predicate{jpl_is_void}{1}{@Term} True if \arg{Term} is \verb$@(void)$, the JPL representation of the pseudo Java value 'void' (which is returned by \predref{jpl_call}{4} when invoked on void methods). NB you can try passing 'void' back to Java, but it won't ever be interested. \predicate[semidet]{jpl_false}{1}{-X:datum} \arg{X} is \verb$@(false)$, the JPL representation of the Java boolean value 'false'. \begin{tags} \tag{See also} \predref{jpl_is_false}{1} \end{tags} \predicate[semidet]{jpl_null}{1}{-X:datum} \arg{X} is \verb$@(null)$, the JPL representation of Java's 'null' reference. \begin{tags} \tag{See also} \predref{jpl_is_null}{1} \end{tags} \predicate[semidet]{jpl_true}{1}{-X:datum} \arg{X} is \verb$@(true)$, the JPL representation of the Java boolean value 'true'. \begin{tags} \tag{See also} \predref{jpl_is_true}{1} \end{tags} \predicate[semidet]{jpl_void}{1}{-X:datum} \arg{X} is \verb$@(void)$, the JPL representation of the pseudo Java value 'void'. \begin{tags} \tag{See also} \predref{jpl_is_void}{1} \end{tags} \predicate{jpl_array_to_length}{2}{+Array:jref, -Length:integer} \arg{Array} should be a JPL reference to a Java array of any type. \arg{Length} is the length of that array. This is a utility predicate, defined thus: \begin{code} jpl_array_to_length(A, N) :- ( jpl_ref_to_type(A, array(_)) -> jGetArrayLength(A, N) ). \end{code} \predicate{jpl_array_to_list}{2}{+Array:jref, -Elements:list(datum)} \arg{Array} should be a JPL reference to a Java array of any type. \arg{Elements} is a Prolog list of JPL representations of the array's elements (values or references, as appropriate). This is a utility predicate, defined thus: \begin{code} jpl_array_to_list(A, Es) :- jpl_array_to_length(A, Len), ( Len > 0 -> LoBound is 0, HiBound is Len-1, jpl_get(A, LoBound-HiBound, Es) ; Es = [] ). \end{code} \predicate{jpl_datums_to_array}{2}{+Datums:list(datum), -A:jref} \arg{A} will be a JPL reference to a new Java array, whose base type is the most specific Java type of which each member of \arg{Datums} is (directly or indirectly) an instance. NB this fails silently if \begin{itemize} \item \arg{Datums} is an empty list (no base type can be inferred) \item \arg{Datums} contains both a primitive value and an object (including array) reference (no common supertype) \end{itemize} \predicate{jpl_enumeration_element}{2}{+Enumeration:jref, -Element:datum} Generates each \arg{Element} from \arg{Enumeration}. \begin{itemize} \item if the element is a java.lang.String then \arg{Element} will be an atom \item if the element is null then \arg{Element} will (oughta) be null \item otherwise I reckon it has to be an object ref \end{itemize} \predicate{jpl_enumeration_to_list}{2}{+Enumeration:jref, -Elements:list(datum)} \arg{Enumeration} should be a JPL reference to an object which implements the \verb$Enumeration$ interface. \arg{Elements} is a Prolog list of JPL references to the enumerated objects. This is a utility predicate, defined thus: \begin{code} jpl_enumeration_to_list(Enumeration, Es) :- ( jpl_call(Enumeration, hasMoreElements, [], @(true)) -> jpl_call(Enumeration, nextElement, [], E), Es = [E|Es1], jpl_enumeration_to_list(Enumeration, Es1) ; Es = [] ). \end{code} \predicate[nondet]{jpl_hashtable_pair}{2}{+HashTable:jref, -KeyValuePair:pair(datum,datum)} Generates Key-Value pairs from the given \arg{HashTable}. NB String is converted to atom but Integer is presumably returned as an object ref (i.e. as elsewhere, no auto unboxing); NB this is anachronistic: the Map interface is preferred. \predicate{jpl_iterator_element}{2}{+Iterator:jref, -Element:datum} \arg{Iterator} should be a JPL reference to an object which implements the \verb$java.util.Iterator$ interface. \arg{Element} is the JPL representation of the next element in the iteration. This is a utility predicate, defined thus: \begin{code} jpl_iterator_element(I, E) :- ( jpl_call(I, hasNext, [], @(true)) -> ( jpl_call(I, next, [], E) ; jpl_iterator_element(I, E) ) ). \end{code} \predicate{jpl_list_to_array}{2}{+Datums:list(datum), -Array:jref} \arg{Datums} should be a proper Prolog list of JPL datums (values or references). If \arg{Datums} have a most specific common supertype, then \arg{Array} is a JPL reference to a new Java array, whose base type is that common supertype, and whose respective elements are the Java values or objects represented by \arg{Datums}. \predicate[semidet]{jpl_terms_to_array}{2}{+Terms:list(term), -Array:jref} \arg{Terms} should be a proper Prolog list of arbitrary terms. \arg{Array} is a JPL reference to a new Java array of \verb$org.jpl7.Term$, whose elements represent the respective members of the list. \predicate{jpl_array_to_terms}{2}{+JRef:jref, -Terms:list(term)} \arg{JRef} should be a JPL reference to a Java array of org.jpl7.Term instances (or ots subtypes); \arg{Terms} will be a list of the terms which the respective array elements represent. \predicate[nondet]{jpl_map_element}{2}{+Map:jref, -KeyValue:pair(datum,datum)} \arg{Map} must be a JPL Reference to an object which implements the \verb$java.util.Map$ interface This generates each Key-Value pair from the \arg{Map}, e.g. \begin{code} ?- jpl_call('java.lang.System', getProperties, [], Map), jpl_map_element(Map, E). Map = @(0x20b5c38), E = 'java.runtime.name'-'Java(TM) SE Runtime Environment' ; Map = @(0x20b5c38), E = 'sun.boot.library.path'-'C:\\Program Files\\Java\\jre7\\bin' etc. \end{code} This is a utility predicate, defined thus: \begin{code} jpl_map_element(Map, K-V) :- jpl_call(Map, entrySet, [], ES), jpl_set_element(ES, E), jpl_call(E, getKey, [], K), jpl_call(E, getValue, [], V). \end{code} \predicate[nondet]{jpl_set_element}{2}{+Set:jref, -Element:datum} \arg{Set} must be a JPL reference to an object which implements the \verb$java.util.Set$ interface. On backtracking, \arg{Element} is bound to a JPL representation of each element of \arg{Set}. This is a utility predicate, defined thus: \begin{code} jpl_set_element(S, E) :- jpl_call(S, iterator, [], I), jpl_iterator_element(I, E). \end{code} \predicate{jpl_servlet_byref}{3}{+Config, +Request, +Response} This serves the \textit{byref} servlet demo, exemplifying one tactic for implementing a servlet in Prolog by accepting the \arg{Request} and \arg{Response} objects as JPL references and accessing their members via JPL as required; \begin{tags} \tag{See also} \predref{jpl_servlet_byval}{3} \end{tags} \predicate{jpl_servlet_byval}{3}{+MultiMap, -ContentType:atom, -Body:atom} This exemplifies an alternative (to jpl_servlet_byref) tactic for implementing a servlet in Prolog; most Request fields are extracted in Java before this is called, and passed in as a multimap (a map, some of whose values are maps). \predicate{jpl_pl_syntax}{1}{-Syntax:atom} Unifies \arg{Syntax} with 'traditional' or 'modern' according to the mode in which SWI Prolog 7.x was started \end{description}