Did you know ... Search Documentation:
jpl.pl -- A Java interface for SWI Prolog 7.x
PublicShow source

The library(jpl) provides a bidirectional interface to a Java Virtual Machine.

See also
- http://jpl7.org/
Source jpl_new(+X, +Params, -V) is det
X can be:
  • an atomic classname, e.g. 'java.lang.String'
  • or an atomic descriptor, e.g. '[I' or 'Ljava.lang.String;'
  • or a suitable type, i.e. any class(_,_) or array(_), e.g. class([java,util],['Date'])

If X is an object (non-array) type or descriptor and Params is a list of values or references, then V is the result of an invocation of that type's most specifically-typed constructor to whose respective formal parameters the actual Params are assignable (and assigned).

If X is an array type or descriptor and Params is a list of values or references, each of which is (independently) assignable to the array element type, then V is a new array of as many elements as Params has members, initialised with the respective members of Params.

If X is an array type or descriptor and Params is a non-negative integer N, then V is a new array of that type, with N elements, each initialised to Java's appropriate default value for the type.

If V is literally {Term} then we attempt to convert a new org.jpl7.Term instance to a corresponding term; this is of little obvious use here, but is consistent with jpl_call/4 and jpl_get/3.

Source jpl_new_1(+Tx, +Params, -Vx)[private]
(serves only jpl_new/3)

Tx can be a class(_,_) or array(_) type.

Params must be a proper list of constructor parameters.

At exit, Vx is bound to a JPL reference to a new, initialised instance of Tx

Source jpl_new_array(+ElementType, +Length, -NewArray) is det[private]
binds NewArray to a jref to a newly created Java array of ElementType and Length
Source jpl_call(+X, +MethodName:atom, +Params:list(datum), -Result:datum) is det
X should be either
  • an object reference, e.g. <jref>(1552320) (for static or instance methods)
  • or a classname, e.g. 'java.util.Date' (for static methods only)
  • or a descriptor, e.g. 'Ljava.util.Date;' (for static methods only)
  • or type, e.g. class([java,util],['Date']) (for static methods only)

MethodName should be a method name (as an atom) (may involve dynamic overload resolution based on inferred types of params)

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 Params. This resolution mimics the corresponding static resolution performed by Java compilers.

Finally, an attempt will be made to unify Result with the method's returned value, or with @(void) (the compound term with name @ and argument void) if it has none.

Source jpl_call_instance(+ObjectType, +Object, +MethodName, +Params, +ActualParamTypes, +Arity, -Result)[private]
calls the MethodName-d method (instance or static) of Object (which is of ObjectType), which most specifically applies to Params, which we have found to be (respectively) of ActualParamTypes, and of which there are Arity, yielding Result.
Source jpl_call_static(+ClassType, +ClassObject, +MethodName, +Params, +ActualParamTypes, +Arity, -Result)[private]
calls the MethodName-d static method of the class (which is of ClassType, and which is represented by the java.lang.Class instance ClassObject) which most specifically applies to Params, which we have found to be (respectively) of ActualParamTypes, and of which there are Arity, yielding Result.
Source jpl_call_instance_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result)[private]
Source jpl_call_static_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result)[private]
Source jpl_get(+X, +Fspec, -V:datum) is det
X can be
  • a classname
  • or a descriptor
  • or an (object or array) type (for static fields)
  • or a non-array object (for static and non-static fields)
  • or an array (for 'length' pseudo field, or indexed element retrieval)

Fspec can be

  • an atomic field name
  • or an integral array index (to get an element from an array)
  • or a pair I-J of integers (to get a subrange of an array).

Finally, an attempt will be made to unify V with the retrieved value or object reference.

Examples

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].
Source jpl_get_static(+Type:type, +ClassObject:jref, +FieldName:atom, -Value:datum) is det[private]
ClassObject is an instance of java.lang.Class which represents the same class as Type; Value (Vx below) is guaranteed unbound on entry, and will, before exit, be unified with the retrieved value
Source jpl_get_instance(+Type, +Type, +Object, +FieldSpecifier, -Value) is det[private]
Source jpl_get_array_element(+ElementType:type, +Array:jref, +Index, -Vc) is det[private]
Array is a JPL reference to a Java array of ElementType; Vc is (unified with a JPL repn of) its Index-th (numbered from 0) element Java values are now converted to Prolog terms within foreign code
To be done
- more of this could be done within foreign code
Source jpl_get_array_elements(+ElementType, +Array, +N, +M, -Vs)[private]
serves only jpl_get_instance/5

Vs will always be unbound on entry

Source jpl_get_object_array_elements(+Array, +LoIndex, +HiIndex, -Vcs) is det[private]
Array should be a (zero-based) array of some object (array or non-array) type; LoIndex is an integer, 0 =< LoIndex < length(Array); HiIndex is an integer, LoIndex-1 =< HiIndex < length(Array); at call, Vcs will be unbound; at exit, Vcs will be a list of (references to) the array's elements [LoIndex..HiIndex] inclusive
Source jpl_get_primitive_array_elements(+ElementType, +Array, +LoIndex, +HiIndex, -Vcs) is det[private]
Array should be a (zero-based) Java array of (primitive) ElementType; Vcs should be unbound on entry, and on exit will be a list of (JPL representations of the values of) the elements [LoIndex..HiIndex] inclusive
Source jpl_set(+X, +Fspec, +V) is det
sets the Fspec-th field of (class or object) X to value V iff it is assignable

X can be

  • a class instance (for static or non-static fields)
  • or an array (for indexed element or subrange assignment)
  • or a classname, or a class(_,_) or array(_) type (for static fields)
  • but not a String (no fields to retrieve)

Fspec can be

  • an atomic field name (overloading through shadowing has yet to be handled properly)
  • or an array index I (X must be an array object: V is assigned to X[I])
  • or a pair I-J of integers (X must be an array object, V must be a list of values: successive members of V are assigned to X[I..J])

V must be a suitable value or object.

Source jpl_set_instance(+Type, +Type, +ObjectReference, +FieldName, +Value) is det[private]
ObjectReference is a JPL reference to a Java object of the class denoted by Type (which is passed twice for first agument indexing);

FieldName should name a public, non-final (static or non-static) field of this object, but could be anything, and is validated here;

Value should be assignable to the named field, but could be anything, and is validated here

Source jpl_set_static(+Type, +ClassObj, +FieldName, +Value) is det[private]
We can rely on:
  • Type being a class/2 type representing some accessible class
  • ClassObj being an instance of java.lang.Class which represents the same class as Type but FieldName could be anything, so we validate it here, look for a suitable (static) field of the target class, then call jpl_set_static_field/4 to attempt to assign Value (which could be anything) to it

NB this does not yet handle shadowed fields correctly.

Source jpl_set_array(+ElementType, +Array, +Offset, +DatumQty, +Datums) is det[private]
Datums, of which there are DatumQty, are stashed in successive elements of Array which is an array of ElementType starting at the Offset-th (numbered from 0) throws error(type_error(acyclic,_),context(jpl_datum_to_type/2,_))
Source jpl_set_array_1(+Values, +Type, +BufferIndex, +BufferPointer) is det[private]
successive members of Values are stashed as (primitive) Type from the BufferIndex-th element (numbered from 0) onwards of the buffer indicated by BufferPointer

NB this could be done more efficiently (?) within foreign code...

Source jpl_set_instance_field(+Type, +Obj, +FieldID, +V) is det[private]
We can rely on Type, Obj and FieldID being valid, and on V being assignable (if V is a quoted term then it is converted here)
Source jpl_set_static_field(+Type, +ClassObj, +FieldID, +V)[private]
We can rely on Type, ClassObj and FieldID being valid, and on V being assignable (if V is a quoted term then it is converted here).
Source jpl_get_default_jvm_opts(-Opts:list(atom)) is det
Returns (as a list of atoms) the options which will be passed to the JVM when it is initialised, e.g. ['-Xrs']
Source jpl_set_default_jvm_opts(+Opts:list(atom)) is det
Replaces the default JVM initialisation options with those supplied.
Source jpl_get_actual_jvm_opts(-Opts:list(atom)) is semidet
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.

Source jpl_classname_type_cache(-Classname:className, -Type:type)[private]
Classname is the atomic name of Type.

NB may denote a class which cannot be found.

Source jpl_class_tag_type_cache(-Class:jref, -Type:jpl_type)[private]
Class is a reference to an instance of java.lang.Class which denotes Type.

We index on Class (a jref) so as to keep these objects around even after an atom garbage collection (if needed once, they are likely to be needed again)

(Is it possble to have different Ref for the same ClassType, which happens once several ClassLoaders become involved?) (Most likely)

Source jpl_assert(+Fact:term)[private]
Assert a fact listed in jpl_assert_policy/2 with "yes" into the Prolog database.

From the SWI-Prolog manual:

"In SWI-Prolog, querying dynamic predicates has the same performance as static ones. The manipulation predicates are fast."

And:

"By default, a predicate declared dynamic (see dynamic/1) is shared by all threads. Each thread may assert, retract and run the dynamic predicate. Synchronisation inside Prolog guarantees the consistency of the predicate. Updates are logical: visible clauses are not affected by assert/retract after a query started on the predicate. In many cases primitives from section 10.4 should be used to ensure that application invariants on the predicate are maintained.
See also
- https://eu.swi-prolog.org/pldoc/man?section=db
- https://eu.swi-prolog.org/pldoc/man?section=threadlocal
Source jpl_tidy_iref_type_cache(+Iref) is det[private]
Delete the cached type info, if any, under Iref.

Called from jpl.c's jni_free_iref() via jni_tidy_iref_type_cache()

Source jpl_fergus_is_the_greatest(+Xs:list(T), -GreatestX:T)[private]
Xs is a list of things for which jpl_fergus_greater/2 defines a partial ordering; GreatestX is one of those, than which none is greater; fails if there is more than one such; this algorithm was contributed to c.l.p by Fergus Henderson in response to my "there must be a better way" challenge: there was, this is it
Source jpl_z3s_to_most_specific_z3(+Zs, -Z)[private]
Zs is a list of arity-matching, type-suitable z3(I,MID,Tfps).

Z is the single most specific element of Zs, i.e. that than which no other z3/3 has a more specialised signature (fails if there is more than one such).

Source jpl_z5s_to_most_specific_z5(+Zs, -Z)[private]
Zs is a list of arity-matching, type-suitable z5(I,Mods,MID,Tr,Tfps)

Z is the single most specific element of Zs, i.e. that than which no other z5/5 has a more specialised signature (fails if there is more than one such)

Source jpl_pl_lib_version(-Version)
Version is the fully qualified version identifier of the in-use Prolog component (jpl.pl) of JPL.

It should exactly match the version identifiers of JPL's C (jpl.c) and Java (jpl.jar) components.

Example

?- jpl_pl_lib_version(V).
V = '7.6.1'.
Source jpl_pl_lib_version(-Major, -Minor, -Patch, -Status)[private]
Major, Minor, Patch and Status are the respective components of the version identifier of the in-use C component (jpl.c) of JPL.

Example

?- jpl:jpl_pl_lib_version(Major, Minor, Patch, Status).
Major = 7,
Minor = 4,
Patch = 0,
Status = alpha.
Source jpl_c_lib_version(-Version)
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 (jpl.pl) and Java (jpl.jar) components.

Example

?- jpl_c_lib_version(V).
V = '7.4.0-alpha'.
Source jpl_java_lib_version(-Version)[private]
Version is the fully qualified version identifier of the in-use Java component (jpl.jar) of JPL.

Example

?- jpl:jpl_java_lib_version(V).
V = '7.4.0-alpha'.
Source jpl_java_lib_version(V)[private]
Source jpl_pl_lib_path(-Path:atom)[private]
Source jpl_c_lib_path(-Path:atom)[private]
Source jpl_java_lib_path(-Path:atom)[private]
Source jCallBooleanMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbool:boolean)[private]
Source jCallByteMethod(+Obj:jref, +MethodID:methodId, +Types, +Params:list(datum), -Rbyte:byte)[private]
Source jCallCharMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rchar:char)[private]
Source jCallDoubleMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rdouble:double)[private]
Source jCallFloatMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rfloat:float)[private]
Source jCallIntMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rint:int)[private]
Source jCallLongMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rlong:long)[private]
Source jCallObjectMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Robj:jref)[private]
Source jCallShortMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rshort:short)[private]
Source jCallStaticBooleanMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbool:boolean)[private]
Source jCallStaticByteMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbyte:byte)[private]
Source jCallStaticCharMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rchar:char)[private]
Source jCallStaticDoubleMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rdouble:double)[private]
Source jCallStaticFloatMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rfloat:float)[private]
Source jCallStaticIntMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rint:int)[private]
Source jCallStaticLongMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rlong:long)[private]
Source jCallStaticObjectMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Robj:jref)[private]
Source jCallStaticShortMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rshort:short)[private]
Source jCallStaticVoidMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum))[private]
Source jCallVoidMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum))[private]
Source jFindClass(+ClassName:findclassname, -Class:jref)[private]
Source jGetArrayLength(+Array:jref, -Size:int)[private]
Source jGetBooleanArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:boolean_buf)[private]
Source jGetBooleanField(+Obj:jref, +FieldID:fieldId, -Rbool:boolean)[private]
Source jGetByteArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:byte_buf)[private]
Source jGetByteField(+Obj:jref, +FieldID:fieldId, -Rbyte:byte)[private]
Source jGetCharArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:char_buf)[private]
Source jGetCharField(+Obj:jref, +FieldID:fieldId, -Rchar:char)[private]
Source jGetDoubleArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:double_buf)[private]
Source jGetDoubleField(+Obj:jref, +FieldID:fieldId, -Rdouble:double)[private]
Source jGetFieldID(+Class:jref, +Name:fieldName, +Type:type, -FieldID:fieldId)[private]
Source jGetFloatArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:float_buf)[private]
Source jGetFloatField(+Obj:jref, +FieldID:fieldId, -Rfloat:float)[private]
Source jGetIntArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:int_buf)[private]
Source jGetIntField(+Obj:jref, +FieldID:fieldId, -Rint:int)[private]
Source jGetLongArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:long_buf)[private]
Source jGetLongField(+Obj:jref, +FieldID:fieldId, -Rlong:long)[private]
Source jGetMethodID(+Class:jref, +Name:atom, +Type:type, -MethodID:methodId)[private]
Source jGetObjectArrayElement(+Array:jref, +Index:int, -Obj:jref)[private]
Source jGetObjectClass(+Object:jref, -Class:jref)[private]
Source jGetObjectField(+Obj:jref, +FieldID:fieldId, -RObj:jref)[private]
Source jGetShortArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:short_buf)[private]
Source jGetShortField(+Obj:jref, +FieldID:fieldId, -Rshort:short)[private]
Source jGetStaticBooleanField(+Class:jref, +FieldID:fieldId, -Rbool:boolean)[private]
Source jGetStaticByteField(+Class:jref, +FieldID:fieldId, -Rbyte:byte)[private]
Source jGetStaticCharField(+Class:jref, +FieldID:fieldId, -Rchar:char)[private]
Source jGetStaticDoubleField(+Class:jref, +FieldID:fieldId, -Rdouble:double)[private]
Source jGetStaticFieldID(+Class:jref, +Name:fieldName, +Type:type, -FieldID:fieldId)[private]
Source jGetStaticFloatField(+Class:jref, +FieldID:fieldId, -Rfloat:float)[private]
Source jGetStaticIntField(+Class:jref, +FieldID:fieldId, -Rint:int)[private]
Source jGetStaticLongField(+Class:jref, +FieldID:fieldId, -Rlong:long)[private]
Source jGetStaticMethodID(+Class:jref, +Name:methodName, +Type:type, -MethodID:methodId)[private]
Source jGetStaticObjectField(+Class:jref, +FieldID:fieldId, -RObj:jref)[private]
Source jGetStaticShortField(+Class:jref, +FieldID:fieldId, -Rshort:short)[private]
Source jGetSuperclass(+Class1:jref, -Class2:jref)[private]
Source jIsAssignableFrom(+Class1:jref, +Class2:jref)[private]
Source jNewBooleanArray(+Length:int, -Array:jref)[private]
Source jNewByteArray(+Length:int, -Array:jref)[private]
Source jNewCharArray(+Length:int, -Array:jref)[private]
Source jNewDoubleArray(+Length:int, -Array:jref)[private]
Source jNewFloatArray(+Length:int, -Array:jref)[private]
Source jNewIntArray(+Length:int, -Array:jref)[private]
Source jNewLongArray(+Length:int, -Array:jref)[private]
Source jNewObject(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Obj:jref)[private]
Source jNewObjectArray(+Len:int, +Class:jref, +InitVal:jref, -Array:jref)[private]
Source jNewShortArray(+Length:int, -Array:jref)[private]
Source jSetBooleanArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:boolean_buf)[private]
Source jSetBooleanField(+Obj:jref, +FieldID:fieldId, +Rbool:boolean)[private]
Source jSetByteArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:byte_buf)[private]
Source jSetByteField(+Obj:jref, +FieldID:fieldId, +Rbyte:byte)[private]
Source jSetCharArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:char_buf)[private]
Source jSetCharField(+Obj:jref, +FieldID:fieldId, +Rchar:char)[private]
Source jSetDoubleArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:double_buf)[private]
Source jSetDoubleField(+Obj:jref, +FieldID:fieldId, +Rdouble:double)[private]
Source jSetFloatArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:float_buf)[private]
Source jSetFloatField(+Obj:jref, +FieldID:fieldId, +Rfloat:float)[private]
Source jSetIntArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:int_buf)[private]
Source jSetIntField(+Obj:jref, +FieldID:fieldId, +Rint:int)[private]
Source jSetLongArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:long_buf)[private]
Source jSetLongField(+Obj:jref, +FieldID:fieldId, +Rlong:long)[private]
Source jSetObjectArrayElement(+Array:jref, +Index:int, +Obj:jref)[private]
Source jSetObjectField(+Obj:jref, +FieldID:fieldId, +RObj:jref)[private]
Source jSetShortArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:short_buf)[private]
Source jSetShortField(+Obj:jref, +FieldID:fieldId, +Rshort:short)[private]
Source jSetStaticBooleanField(+Class:jref, +FieldID:fieldId, +Rbool:boolean)[private]
Source jSetStaticByteField(+Class:jref, +FieldID:fieldId, +Rbyte:byte)[private]
Source jSetStaticCharField(+Class:jref, +FieldID:fieldId, +Rchar:char)[private]
Source jSetStaticDoubleField(+Class:jref, +FieldID:fieldId, +Rdouble:double)[private]
Source jSetStaticFloatField(+Class:jref, +FieldID:fieldId, +Rfloat:float)[private]
Source jSetStaticIntField(+Class:jref, +FieldID:fieldId, +Rint:int)[private]
Source jSetStaticLongField(+Class:jref, +FieldID:fieldId, +Rlong)[private]
Source jSetStaticObjectField(+Class:jref, +FieldID:fieldId, +Robj:jref)[private]
Source jSetStaticShortField(+Class:jref, +FieldID:fieldId, +Rshort:short)[private]
Source jni_params_put(+Params:list(datum), +Types:list(type), -ParamBuf:paramBuf)[private]
The old form used a static buffer, hence was not re-entrant; the new form allocates a buffer of one jvalue per arg, puts the (converted) args into respective elements, then returns it (the caller is responsible for freeing it).
Source jni_params_put_1(+Params:list(datum), +N:integer, +JPLTypes:list(type), +ParamBuf:paramBuf)[private]
Params is a (full or partial) list of args-not-yet-stashed.

Types are their (JPL) types (e.g. 'boolean').

N is the arg and buffer index (0+) at which the head of Params is to be stashed.

The old form used a static buffer and hence was non-reentrant; the new form uses a dynamically allocated buffer (which oughta be freed after use).

NB if the (user-provided) actual params were to be unsuitable for conversion to the method-required types, this would fail silently (without freeing the buffer); it's not clear whether the overloaded-method-resolution ensures that all args are convertible

Source jni_type_to_xput_code(+JspType, -JniXputCode)[private]
NB JniXputCode determines widening and casting in foreign code

NB the codes could be compiled into jni_method_spec_cache etc. instead of, or as well as, types (for - small - efficiency gain)

Source jpl_class_to_constructor_array(+Class:jref, -MethodArray:jref)[private]
NB might this be done more efficiently in foreign code? or in Java?
Source jpl_class_to_constructors(+Class:jref, -Methods:list(jref))[private]
Source jpl_class_to_field_array(+Class:jref, -FieldArray:jref)[private]
Source jpl_class_to_fields(+Class:jref, -Fields:list(jref))[private]
NB do this in Java (ditto for methods)?
Source jpl_class_to_method_array(+Class:jref, -MethodArray:jref)[private]
NB migrate into foreign code for efficiency?
Source jpl_class_to_methods(+Class:jref, -Methods:list(jref))[private]
NB also used for constructors.

NB do this in Java (ditto for fields)?

Source jpl_constructor_to_modifiers(+Method, -Modifiers)[private]
NB migrate into foreign code for efficiency?
Source jpl_constructor_to_name(+Method:jref, -Name:atom)[private]
It is a JNI convention that each constructor behaves (at least, for reflection), as a method whose name is '<init>'.
Source jpl_constructor_to_parameter_types(+Method:jref, -ParameterTypes:list(type))[private]
NB migrate to foreign code for efficiency?
Source jpl_constructor_to_return_type(+Method:jref, -Type:type)[private]
It is a JNI convention that, for the purposes of retrieving a MethodID, a constructor has a return type of 'void'.
Source jpl_field_spec(+Type:type, -Index:integer, -Name:atom, -Modifiers, -MID:mId, -FieldType:type)[private]
I'm unsure whether arrays have fields, but if they do, this will handle them correctly.
Source jpl_field_to_modifiers(+Field:jref, -Modifiers:ordset(modifier))[private]
Source jpl_field_to_name(+Field:jref, -Name:atom)[private]
Source jpl_field_to_type(+Field:jref, -Type:type)[private]
Source jpl_method_spec(+Type:type, -Index:integer, -Name:atom, -Arity:integer, -Modifiers:ordset(modifier), -MID:methodId, -ReturnType:type, -ParameterTypes:list(type))[private]
Generates pertinent details of all accessible methods of Type (class/2 or array/1), populating or using the cache as appropriate.
Source jpl_method_spec_1(+Class:jref, +CacheIndexType:partialType, +Constructors:list(method), +Methods:list(method))[private]
If the original type is e.g. array(byte) then CacheIndexType is array(_) else it is that type.
Source jpl_method_to_modifiers(+Method:jref, -ModifierSet:ordset(modifier))[private]
Source jpl_method_to_modifiers_1(+Method:jref, +ConstructorClass:jref, -ModifierSet:ordset(modifier))[private]
Source jpl_method_to_name(+Method:jref, -Name:atom)[private]
Source jpl_member_to_name_1(+Member:jref, +CM:jref, -Name:atom)[private]
Source jpl_method_to_parameter_types(+Method:jref, -Types:list(type))[private]
Source jpl_method_to_parameter_types_1(+XM:jref, +Cxm:jref, -Tfps:list(type))[private]
XM is (a JPL ref to) an instance of java.lang.reflect.[Constructor|Method]
Source jpl_method_to_return_type(+Method:jref, -Type:type)[private]
Source jpl_modifier_int_to_modifiers(+Int:integer, -ModifierSet:ordset(modifier))[private]
ModifierSet is an ordered (hence canonical) list, possibly empty (although I suspect never in practice?), of modifier atoms, e.g. [public,static]
Source jpl_cache_type_of_ref(+Type:type, +Ref:jref)[private]
Type must be a proper (concrete) JPL type

Ref must be a proper JPL reference (not void)

Type is memoed (if policy so dictates) as the type of the referenced object (unless it's null) by iref (so as not to disable atom-based GC)

NB obsolete lemmas must be watched-out-for and removed

Source jpl_class_to_ancestor_classes(+Class:jref, -AncestorClasses:list(jref))[private]
AncestorClasses will be a list of (JPL references to) instances of java.lang.Class denoting the "implements" lineage (?), nearest first (the first member denotes the class which Class directly implements, the next (if any) denotes the class which that class implements, and so on to java.lang.Object)
Source jpl_class_to_classname(+Class:jref, -ClassName:entityName)
Class is a reference to a class object.

ClassName is its canonical (?) source-syntax (dotted) name, e.g. '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)

TODO This shouldn't exist as we have jpl_class_to_entityname/2 ???

The implementation actually just calls Class.getName() to get the entity name (dotted name)

Source jpl_class_to_entityname(+Class:jref, -EntityName:atom)[private]
The Class is a reference to a class object. The EntityName is the string as returned by Class.getName().

This predicate actually calls Class.getName() on the class corresponding to Class.

See also
- https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Class.html#getName()
Source jpl_class_to_type(+Class:jref, -Type:jpl_type)
The Class is a reference to a (Java Universe) instance of java.lang.Class. The Type is the (Prolog Universe) JPL type term denoting the same type as does the instance of 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' (?!)

Source jpl_entityname_to_class(+EntityName:atom, -Class:jref)[private]
EntityName is the entity name to be mapped to a class reference.

Class is a (canonical) reference to the corresponding class object.

NB uses caches where the class is already encountered.

Source jpl_classname_to_class(+EntityName:atom, -Class:jref)
EntityName is the entity name to be mapped to a class reference.

Class is a (canonical) reference to the corresponding class object.

NB uses caches where the class has already been mapped once before.

Source jpl_entityname_to_type(+EntityName:atom, -Type:jpl_type)
EntityName is the entity name (an atom) denoting a Java type, to be mapped to a JPL type. This is the string returned by java.lang.Class.getName().

Type is the JPL type (a ground term) denoting the same Java type as 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:

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'])

NB uses caches where the class has already been mapped once before.

See also
- https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Class.html#getName()
Source jpl_type_to_entityname(+Type:jpl_type, -EntityName:atom)
This is the converse of jpl_entityname_to_type/2
Source jpl_classname_to_type(+EntityName:atom, -Type:jpl_type)
This is a wrapper around 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 jpl_entityname_to_type/2 in preference.

Source jpl_type_to_classname(+Type:jpl_type, -EntityName:atom)
This is a wrapper around 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 jpl_type_to_entityname/2 in preference.

Source jpl_datum_to_type(+Datum:datum, -Type:type)
Datum must be a JPL representation of an instance of one (or more) Java types;

Type is the unique most specialised type of which 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';

See also
- jpl_type_to_preferred_concrete_type/2 for converting inferred types to instantiable types
Source jpl_datums_to_types(+Datums:list(datum), -Types:list(type))[private]
Each member of Datums is a JPL value or reference, denoting an instance of some Java type, and the corresponding member of Types denotes the most specialised type of which it is an instance (including some I invented for the overlaps between e.g. char and short).
Source jpl_ground_is_type(+X:jpl_type)[private]
X, known to be ground, is (or at least superficially resembles :-) a JPL type.

A (more complete) alternative would be to try to transfrom the X into its entityname and see whether that works.

Source jpl_object_array_to_list(+Array:jref, -Values:list(datum))[private]
Values is a list of JPL values (primitive values or object references) representing the respective elements of Array.
Source jpl_object_array_to_list_1(+A, +I, +N, -Xs)[private]
Source jpl_object_to_class(+Object:jref, -Class:jref)
fails silently if Object is not a valid reference to a Java object

Class is a (canonical) reference to the (canonical) class object which represents the class of Object

NB what's the point of caching the type if we don't look there first?

Source jpl_object_to_type(+Object:jref, -Type:type)
Object must be a proper JPL reference to a Java object (i.e. a class or array instance, but not null, void or String).

Type is the JPL type of that object.

Source jpl_primitive_buffer_to_array(+Type, +Xc, +Bp, +I, +Size, -Vcs)[private]
Bp points to a buffer of (sufficient) Type values.

Vcs will be unbound on entry, and on exit will be a list of Size of them, starting at index I (the buffer is indexed from zero)

Source jpl_primitive_type(-Type:atom) is nondet
Type is an atomic JPL representation of one of Java's primitive types. N.B: void is not included.
?- setof(Type, jpl_primitive_type(Type), Types).
Types = [boolean, byte, char, double, float, int, long, short].
Source jpl_primitive_type_default_value(-Type:type, -Value:datum)[private]
Each element of any array of (primitive) Type created by jpl_new/3, or any instance of (primitive) Type created by jpl_new/3, will be initialised to Value (to mimic Java semantics).
Source jpl_primitive_type_term_to_value(+Type, +Term, -Val)[private]
Term, after widening iff appropriate, represents an instance of Type.

Val is the instance of Type which it represents (often the same thing).

NB currently used only by jpl_new_1 when creating an "instance" of a primitive type (which may be misguided completism - you can't do that in Java)

Source jpl_primitive_type_term_to_value_1(+Type, +RawValue, -WidenedValue)[private]
I'm not worried about structure duplication here.

NB this oughta be done in foreign code.

Source jpl_ref_to_type(+Ref:jref, -Type:type)
Ref must be a proper JPL reference (to an object, null or void).

Type is its type.

Source jpl_tag_to_type(+Tag:tag, -Type:type)[private]
Tag must be an (atomic) object tag.

Type is its type (either from the cache or by reflection). OBSOLETE

Source jpl_type_fits_type(+TypeX:type, +TypeY:type) is semidet[private]
TypeX and TypeY must each be proper JPL types.

This succeeds iff TypeX is assignable to TypeY.

Source jpl_type_fits_type_1(+T1:type, +T2:type)[private]
NB it doesn't matter that this leaves choicepoints; it serves only jpl_type_fits_type/2
Source jpl_type_fits_type_direct_xtra(-PseudoType:type, -ConcreteType:type)[private]
This defines the direct subtype-supertype relationships which involve the intersection pseudo types char_int, char_short and char_byte
Source jpl_type_fits_type_xprim(-Tp, -T) is nondet[private]
NB serves only jpl_type_fits_type_1/2
Source jpl_type_to_ancestor_types(+T:type, -Tas:list(type))[private]
This does not accommodate the assignability of null, but that's OK (?) since "type assignability" and "type ancestry" are not equivalent.
Source jpl_type_to_canonical_type(+Type:type, -CanonicalType:type)[private]
Type must be a type, not necessarily canonical.

CanonicalType will be equivalent and canonical.

Example

?- jpl:jpl_type_to_canonical_type(class([],[byte]), T).
T = byte.
Source jpl_type_to_class(+Type:jpl_type, -Class:jref)
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.

Source jpl_type_to_java_field_descriptor(+Type:jpl_type, -Descriptor:atom)[private]
Type (the JPL type, a Prolog term) is mapped to the corresponding stringy Java field descriptor (an atom)

TODO: I'd cache this, but I'd prefer more efficient indexing on types (hashed?)

Source jpl_type_to_java_method_descriptor(+Type:jpl_type, -Descriptor:atom)[private]
Type (the JPL type, a Prolog term) is mapped to the corresponding stringy Java method descriptor (an atom)

TODO: Caching might be nice (but is it worth it?)

Source jpl_type_to_java_findclass_descriptor(+Type:jpl_type, -Descriptor:atom)[private]
Type (the JPL type, a Prolog term) is mapped to the corresponding stringy Java findclass descriptor (an atom) to be used for JNI's "FindClass" function.
Source jpl_type_to_super_type(+Type:type, -SuperType:type)[private]
Type should be a proper JPL type.

SuperType is the (at most one) type which it directly implements (if it's a class).

If Type denotes a class, this works only if that class can be found.

Source jpl_type_to_preferred_concrete_type(+Type:type, -ConcreteType:type)[private]
Type must be a canonical JPL type, possibly an inferred pseudo type such as char_int or array(char_byte)

ConcreteType is the preferred concrete (Java-instantiable) type.

Example

?- jpl_type_to_preferred_concrete_type(array(char_byte), T).
T = array(byte).

NB introduced 16/Apr/2005 to fix bug whereby jpl_list_to_array([1,2,3],A) failed because the lists's inferred type of array(char_byte) is not Java-instantiable

Source jpl_types_fit_type(+Types:list(type), +Type:type)[private]
Each member of Types is (independently) (if that means anything) assignable to Type.

Used in dynamic type check when attempting to e.g. assign list of values to array.

Source jpl_types_fit_types(+Types1:list(type), +Types2:list(type))[private]
Each member type of Types1 "fits" the respective member type of Types2.
Source jpl_value_to_type(+Value:datum, -Type:type)[private]
Value must be a proper JPL datum other than a ref i.e. primitive, String or void

Type is its unique most specific type, which may be one of the pseudo types char_byte, char_short or char_int.

Source jpl_value_to_type_1(+Value:datum, -Type:type) is semidet[private]
Type is the unique most specific JPL type of which Value represents an instance.

Called solely by jpl_value_to_type/2, which commits to first solution.

NB some integer values are of JPL-peculiar uniquely most specific subtypes, i.e. char_byte, char_short, char_int but all are understood by JPL's internal utilities which call this proc.

NB we regard float as subtype of double.

NB objects and refs always have straightforward types.

Source jpl_is_class(@Term)
True if Term is a JPL reference to an instance of java.lang.Class.
Source jpl_is_false(@Term)
True if Term is @(false), the JPL representation of the Java boolean value 'false'.
Source jpl_is_fieldID(-X)[private]
X is a JPL field ID structure (jfieldID/1)..

NB JPL internal use only.

NB applications should not be messing with these.

NB a var arg may get bound.

Source jpl_is_methodID(-X)[private]
X is a JPL method ID structure (jmethodID/1).

NB JPL internal use only.

NB applications should not be messing with these.

NB a var arg may get bound.

Source jpl_is_null(@Term)
True if Term is @(null), the JPL representation of Java's 'null' reference.
Source jpl_is_object(@Term)
True if Term is a well-formed JPL object reference.

NB this checks only syntax, not whether the object exists.

Source jpl_is_object_type(@Term)
True if Term is an object (class or array) type, not e.g. a primitive, null or void.
Source jpl_is_ref(@Term)
True if Term is a well-formed JPL reference, either to a Java object or to Java's notional but important 'null' non-object.
Source jpl_is_true(@Term)
True if Term is @(true), the JPL representation of the Java boolean value 'true'.
Source jpl_is_type(@Term)
True if Term is a well-formed JPL type structure.
Source jpl_is_void(@Term)
True if Term is @(void), the JPL representation of the pseudo Java value 'void' (which is returned by jpl_call/4 when invoked on void methods).

NB you can try passing 'void' back to Java, but it won't ever be interested.

Source jpl_false(-X:datum) is semidet
X is @(false), the JPL representation of the Java boolean value 'false'.
See also
- jpl_is_false/1
Source jpl_null(-X:datum) is semidet
X is @(null), the JPL representation of Java's 'null' reference.
See also
- jpl_is_null/1
Source jpl_true(-X:datum) is semidet
X is @(true), the JPL representation of the Java boolean value 'true'.
See also
- jpl_is_true/1
Source jpl_void(-X:datum) is semidet
X is @(void), the JPL representation of the pseudo Java value 'void'.
See also
- jpl_is_void/1
Source jpl_array_to_length(+Array:jref, -Length:integer)
Array should be a JPL reference to a Java array of any type.

Length is the length of that array. This is a utility predicate, defined thus:

jpl_array_to_length(A, N) :-
    (   jpl_ref_to_type(A, array(_))
    ->  jGetArrayLength(A, N)
    ).
Source jpl_array_to_list(+Array:jref, -Elements:list(datum))
Array should be a JPL reference to a Java array of any type.

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:

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 = []
    ).
Source jpl_datums_to_array(+Datums:list(datum), -A:jref)
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 Datums is (directly or indirectly) an instance.

NB this fails silently if

  • Datums is an empty list (no base type can be inferred)
  • Datums contains both a primitive value and an object (including array) reference (no common supertype)
Source jpl_enumeration_element(+Enumeration:jref, -Element:datum)
Generates each Element from Enumeration.
  • if the element is a java.lang.String then Element will be an atom
  • if the element is null then Element will (oughta) be null
  • otherwise I reckon it has to be an object ref
Source jpl_enumeration_to_list(+Enumeration:jref, -Elements:list(datum))
Enumeration should be a JPL reference to an object which implements the Enumeration interface.

Elements is a Prolog list of JPL references to the enumerated objects. This is a utility predicate, defined thus:

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 = []
    ).
Source jpl_hashtable_pair(+HashTable:jref, -KeyValuePair:pair(datum,datum)) is nondet
Generates Key-Value pairs from the given 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.

Source jpl_iterator_element(+Iterator:jref, -Element:datum)
Iterator should be a JPL reference to an object which implements the java.util.Iterator interface.

Element is the JPL representation of the next element in the iteration. This is a utility predicate, defined thus:

jpl_iterator_element(I, E) :-
    (   jpl_call(I, hasNext, [], @(true))
    ->  (   jpl_call(I, next, [], E)
        ;   jpl_iterator_element(I, E)
        )
    ).
Source jpl_list_to_array(+Datums:list(datum), -Array:jref)
Datums should be a proper Prolog list of JPL datums (values or references).

If Datums have a most specific common supertype, then 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 Datums.

Source jpl_terms_to_array(+Terms:list(term), -Array:jref) is semidet
Terms should be a proper Prolog list of arbitrary terms.

Array is a JPL reference to a new Java array of org.jpl7.Term, whose elements represent the respective members of the list.

Source jpl_array_to_terms(+JRef:jref, -Terms:list(term))
JRef should be a JPL reference to a Java array of org.jpl7.Term instances (or ots subtypes); Terms will be a list of the terms which the respective array elements represent.
Source jpl_map_element(+Map:jref, -KeyValue:pair(datum,datum)) is nondet
Map must be a JPL Reference to an object which implements the java.util.Map interface

This generates each Key-Value pair from the Map, e.g.

?- jpl_call('java.lang.System', getProperties, [], Map), jpl_map_element(Map, E).
Map = @<jref>(0x20b5c38),
E = 'java.runtime.name'-'Java(TM) SE Runtime Environment' ;
Map = @<jref>(0x20b5c38),
E = 'sun.boot.library.path'-'C:\\Program Files\\Java\\jre7\\bin'
etc.

This is a utility predicate, defined thus:

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).
Source jpl_set_element(+Set:jref, -Element:datum) is nondet
Set must be a JPL reference to an object which implements the java.util.Set interface.

On backtracking, Element is bound to a JPL representation of each element of Set. This is a utility predicate, defined thus:

jpl_set_element(S, E) :-
    jpl_call(S, iterator, [], I),
    jpl_iterator_element(I, E).
Source jpl_servlet_byref(+Config, +Request, +Response)
This serves the byref servlet demo, exemplifying one tactic for implementing a servlet in Prolog by accepting the Request and Response objects as JPL references and accessing their members via JPL as required;
See also
- jpl_servlet_byval/3
Source jpl_servlet_byval(+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).
Source is_pair(?T:term)[private]
I define a half-decent "pair" as having a ground key (any val).
Source to_atom(+Term, -Atom)[private]
Unifies Atom with a printed representation of Term.
To be done
- Sort of quoting requirements and use format(codes(Codes),...)
Source jpl_pl_syntax(-Syntax:atom)
Unifies Syntax with 'traditional' or 'modern' according to the mode in which SWI Prolog 7.x was started
Source add_search_path(+Var, +Value) is det[private]
Add value to the end of search-path Var. Value is normally a directory. Does not change the environment if Dir is already in Var.
Arguments:
Value- Path to add in OS notation.
Source check_java_environment[private]
Verify the Java environment. Preferably we would create, but most Unix systems do not allow putenv("LD_LIBRARY_PATH=..." in the current process. A suggesting found on the net is to modify LD_LIBRARY_PATH right at startup and next execv() yourself, but this doesn't work if we want to load Java on demand or if Prolog itself is embedded in another application.

So, after reading lots of pages on the web, I decided checking the environment and producing a sensible error message is the best we can do.

Please not that Java2 doesn't require $CLASSPATH to be set, so we do not check for that.

Source check_shared_object(+Lib, -File, -EnvVar, -AbsFile) is semidet[private]
True if AbsFile is existing .so/.dll file for Lib.
Arguments:
File- Full name of Lib (i.e. libjpl.so or jpl.dll)
EnvVar- Search-path for shared objects.
Source library_search_path(-Dirs:list, -EnvVar) is det[private]
Dirs is the list of directories searched for shared objects/DLLs. EnvVar is the variable in which the search path os stored.
Source add_jpl_to_classpath[private]
Add jpl.jar to CLASSPATH to facilitate callbacks. If jpl.jar is already in CLASSPATH, do nothing. Note that this may result in the user picking up a different version of jpl.jar. We'll assume the user is right in this case.
To be done
- Should we warn if both classpath and jar return a result that is different? What is different? According to same_file/2 or content?
Source libjpl(-Spec) is det[private]
Return the spec for loading the JPL shared object. This shared object must be called libjpl.so as the Java System.loadLibrary() call used by jpl.jar adds the lib* prefix.

In Windows we should not use foreign(jpl) as this eventually calls LoadLibrary() with an absolute path, disabling the Windows DLL search process for the dependent jvm.dll and possibly other Java dll dependencies.

Source add_jpl_to_ldpath(+JPL) is det[private]
Add the directory holding jpl.so to search path for dynamic libraries. This is needed for callback from Java. Java appears to use its own search and the new value of the variable is picked up correctly.
Source add_java_to_ldpath is det[private]
Adds the directories holding jvm.dll to the %PATH%. This appears to work on Windows. Unfortunately most Unix systems appear to inspect the content of LD_LIBRARY_PATH (DYLD_LIBRARY_PATH on MacOS) only once.
Source extend_dll_search_path(+Dir)[private]
Add Dir to search for DLL files. We use win_add_dll_directory/1, but this doesn't seem to work on Wine, so we also add these directories to %PATH% on this platform.
Source extend_java_library_path(+OsDir)[private]
Add Dir (in OS notation) to the Java -Djava.library.path init options.
Source java_dirs// is det[private]
DCG that produces existing candidate directories holding Java related DLLs
Source java_home(-Home) is semidet[private]
Find the home location of Java.
Arguments:
Home- JAVA home in OS notation