View source with raw comments or as raw
    1/*  Part of JPL -- SWI-Prolog/Java interface
    2
    3    Author:        Paul Singleton, Fred Dushin and Jan Wielemaker
    4    E-mail:        paul@jbgb.com
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2004-2020, Paul Singleton
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(jpl,
   36    [   jpl_get_default_jvm_opts/1,
   37        jpl_set_default_jvm_opts/1,
   38        jpl_get_actual_jvm_opts/1,
   39        jpl_pl_lib_version/1,
   40        jpl_c_lib_version/1,
   41        jpl_pl_syntax/1,
   42        jpl_new/3,
   43        jpl_call/4,
   44        jpl_get/3,
   45        jpl_set/3,
   46        jpl_servlet_byref/3,
   47        jpl_servlet_byval/3,
   48        jpl_class_to_classname/2,
   49        jpl_class_to_type/2,
   50        jpl_classname_to_class/2,
   51        jpl_classname_to_type/2, % name does not reflect that it deals with entity names
   52        jpl_datum_to_type/2,
   53        jpl_entityname_to_type/2, % new alias for jpl_classname_to_type/2
   54        jpl_false/1,
   55        jpl_is_class/1,
   56        jpl_is_false/1,
   57        jpl_is_null/1,
   58        jpl_is_object/1,
   59        jpl_is_object_type/1,
   60        jpl_is_ref/1,
   61        jpl_is_true/1,
   62        jpl_is_type/1,
   63        jpl_is_void/1,
   64        jpl_null/1,
   65        jpl_object_to_class/2,
   66        jpl_object_to_type/2,
   67        jpl_primitive_type/1,
   68        jpl_ref_to_type/2,
   69        jpl_true/1,
   70        jpl_type_to_class/2,
   71        jpl_type_to_classname/2, % name does not reflect that it deals with entity names
   72        jpl_type_to_entityname/2, % new alias for jpl_type_to_classname/2
   73        jpl_void/1,
   74        jpl_array_to_length/2,
   75        jpl_array_to_list/2,
   76        jpl_datums_to_array/2,
   77        jpl_enumeration_element/2,
   78        jpl_enumeration_to_list/2,
   79        jpl_hashtable_pair/2,
   80        jpl_iterator_element/2,
   81        jpl_list_to_array/2,
   82        jpl_terms_to_array/2,
   83        jpl_array_to_terms/2,
   84        jpl_map_element/2,
   85        jpl_set_element/2
   86   ]).   87:- autoload(library(apply),[maplist/2]).   88:- use_module(library(debug),[debugging/1,debug/3]).   89:- autoload(library(lists),
   90	    [member/2,nth0/3,nth1/3,append/3,flatten/2,select/3]).   91:- autoload(library(shlib),[load_foreign_library/1]).

A Java interface for SWI Prolog 7.x

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

See also
- http://jpl7.org/ */
  100% suppress debugging this library
  101:- set_prolog_flag(generate_debug_info, false).
 jpl_new(+X, +Params, -V) is det
X can be:

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.

  132jpl_new(X, Params, V) :-
  133    (   var(X)
  134    ->  throwme(jpl_new,x_is_var)
  135    ;   jpl_is_type(X)                  % NB Should check for "instantiable type"? Also accepts "double" for example.
  136    ->  Type = X
  137    ;   atom(X)                         % an atom not captured by jpl_is_type/1 e.g. 'java.lang.String', '[L', even "void"
  138    ->  (   jpl_entityname_to_type(X, Type)
  139        ->  true
  140        ;   throwme(jpl_new,x_not_classname(X))
  141        )
  142    ;   throwme(jpl_new,x_not_instantiable(X))
  143    ),
  144    jpl_new_1(Type, Params, Vx),
  145    (   nonvar(V),
  146        V = {Term}  % yucky way of requesting Term->term conversion
  147    ->  (   jni_jref_to_term(Vx, TermX)    % fails if Vx is not a JRef to a org.jpl7.Term
  148        ->  Term = TermX
  149        ;   throwme(jpl_new,not_a_jpl_term(Vx))
  150        )
  151    ;   V = Vx
  152    ).
 jpl_new_1(+Tx, +Params, -Vx)
(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

  165jpl_new_1(class(Ps,Cs), Params, Vx) :-
  166    !,                                      % green (see below)
  167    Tx = class(Ps,Cs),
  168    (   var(Params)
  169    ->  throwme(jpl_new_class,params_is_var)
  170    ;   \+ is_list(Params)
  171    ->  throwme(jpl_new_class,params_is_not_list(Params))
  172    ;   true
  173    ),
  174    length(Params, A),          % the "arity" of the required constructor
  175    jpl_type_to_class(Tx, Cx),  % throws Java exception if class is not found
  176    N = '<init>',               % JNI's constructor naming convention for GetMethodID()
  177    Tr = void,                  % all constructors have this return "type"
  178    findall(
  179        z3(I,MID,Tfps),
  180        jpl_method_spec(Tx, I, N, A, _Mods, MID, Tr, Tfps), % cached
  181        Z3s
  182    ),
  183    (   Z3s == []               % no constructors which require the given qty of parameters?
  184    ->  (   jpl_call(Cx, isInterface, [], @(true))
  185        ->  throwme(jpl_new_class,class_is_interface(Tx))
  186        ;   throwme(jpl_new_class,class_without_constructor(Tx,A))
  187        )
  188    ;   (   catch(
  189                jpl_datums_to_types(Params, Taps),  % infer actual parameter types
  190                % 2020-07-21: make catcher's 1st context arg an "anonvar" instead of a overspecified predicate indicator
  191                error(type_error(acyclic,Te),context(_,Msg)),
  192                throwme(jpl_new_class,acyclic(Te,Msg)) % rethrow
  193            )
  194        ->  true
  195        ;   throwme(jpl_new_class,bad_jpl_datum(Params))
  196        ),
  197        findall(
  198            z3(I,MID,Tfps),                 % select constructors to which actual parameters are assignable
  199            (   member(z3(I,MID,Tfps), Z3s),
  200                jpl_types_fit_types(Taps, Tfps) % assignability test: actual parameter types "fit" formal parameter types?
  201            ),
  202            Z3sA
  203        ),
  204        (   Z3sA == []                      % no type-assignable constructors?
  205        ->  (   Z3s = [_]
  206            ->  throwme(jpl_new_class,single_constructor_mismatch(Tx/A))
  207            ;   throwme(jpl_new_class,any_constructor_mismatch(Params))
  208            )
  209        ;   Z3sA = [z3(I,MID,Tfps)]
  210        ->  true
  211        ;   jpl_z3s_to_most_specific_z3(Z3sA, z3(I,MID,Tfps))
  212        ->  true
  213        ;   throwme(jpl_new_class,constructor_multimatch(Params))
  214        )
  215    ),
  216    catch(
  217        jNewObject(Cx, MID, Tfps, Params, Vx),
  218        error(java_exception(_), 'java.lang.InstantiationException'),
  219        throwme(jpl_new_class,class_is_abstract(Tx)) % Rethrow
  220    ),
  221    jpl_cache_type_of_ref(Tx, Vx).          % since we know it
  222
  223jpl_new_1(array(T), Params, Vx) :-
  224    !,
  225    (   var(Params)
  226    ->  throwme(jpl_new_array,params_is_var)
  227    ;   integer(Params)         % integer I -> array[0..I-1] of default values
  228    ->  (   Params >= 0
  229        ->  Len is Params
  230        ;   throwme(jpl_new_array,params_is_negative(Params))
  231        )
  232    ;   is_list(Params)     % [V1,..VN] -> array[0..N-1] of respective values
  233    ->  length(Params, Len)
  234    ),
  235    jpl_new_array(T, Len, Vx), % NB may throw out-of-memory exception
  236    (   nth0(I, Params, Param),     % nmember fails silently when Params is integer
  237        jpl_set(Vx, I, Param),
  238        fail
  239    ;   true
  240    ),
  241    jpl_cache_type_of_ref(array(T), Vx).   % since we know it
  242
  243jpl_new_1(T, _Params, _Vx) :-       % doomed attempt to create new primitive type instance (formerly a dubious completist feature :-)
  244    jpl_primitive_type(T),
  245    !,
  246    throwme(jpl_new_primitive,primitive_type_requested(T)).
  247  % (   var(Params)
  248  % ->  throwme(jpl_new_primitive,params_is_var)
  249  % ;   Params == []
  250  % ->  jpl_primitive_type_default_value(T, Vx)
  251  % ;   Params = [Param]
  252  % ->  jpl_primitive_type_term_to_value(T, Param, Vx)
  253  % ;   throwme(jpl_new_primitive,params_is_bad(Params))
  254  % ).
  255
  256jpl_new_1(T, _, _) :- throwme(jpl_new_catchall,catchall(T)).
 jpl_new_array(+ElementType, +Length, -NewArray) is det
binds NewArray to a jref to a newly created Java array of ElementType and Length
  263jpl_new_array(boolean, Len, A) :-
  264    jNewBooleanArray(Len, A).
  265jpl_new_array(byte, Len, A) :-
  266    jNewByteArray(Len, A).
  267jpl_new_array(char, Len, A) :-
  268    jNewCharArray(Len, A).
  269jpl_new_array(short, Len, A) :-
  270    jNewShortArray(Len, A).
  271jpl_new_array(int, Len, A) :-
  272    jNewIntArray(Len, A).
  273jpl_new_array(long, Len, A) :-
  274    jNewLongArray(Len, A).
  275jpl_new_array(float, Len, A) :-
  276    jNewFloatArray(Len, A).
  277jpl_new_array(double, Len, A) :-
  278    jNewDoubleArray(Len, A).
  279jpl_new_array(array(T), Len, A) :-
  280    jpl_type_to_class(array(T), C),
  281    jNewObjectArray(Len, C, @(null), A).        % initialise each element to null
  282jpl_new_array(class(Ps,Cs), Len, A) :-
  283    jpl_type_to_class(class(Ps,Cs), C),
  284    jNewObjectArray(Len, C, @(null), A).
 jpl_call(+X, +MethodName:atom, +Params:list(datum), -Result:datum) is det
X should be either

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.

  306jpl_call(X, Mspec, Params, R) :-
  307    (   jpl_object_to_type(X, Type)         % the usual case (goal fails safely if X is var or rubbish)
  308    ->  Obj = X,
  309        Kind = instance
  310    ;   var(X)
  311    ->  throwme(jpl_call,arg1_is_var)
  312    ;   atom(X)
  313    ->  (   jpl_entityname_to_type(X, Type)     % does this attempt to load the class?
  314        ->  (   jpl_type_to_class(Type, ClassObj)
  315            ->  Kind = static
  316            ;   throwme(jpl_call,no_such_class(X))
  317            )
  318        ;   throwme(jpl_call,arg1_is_bad(X))
  319        )
  320    ;   X = class(_,_)
  321    ->  Type = X,
  322        jpl_type_to_class(Type, ClassObj),
  323        Kind = static
  324    ;   X = array(_)
  325    ->  throwme(jpl_call,arg1_is_array(X))
  326    ;   throwme(jpl_call,arg1_is_bad(X))
  327    ),
  328    (   atom(Mspec)                 % the usual case, i.e. a method name
  329    ->  true
  330    ;   var(Mspec)
  331    ->  throwme(jpl_call,mspec_is_var)
  332    ;   throwme(jpl_call,mspec_is_bad(Mspec))
  333    ),
  334    (   is_list(Params)
  335    ->  (   catch(
  336                jpl_datums_to_types(Params, Taps),
  337                % 2020-07-21: make catcher's 1st context arg an "anonvar" instead of a overspecified predicate indicator
  338                error(type_error(acyclic,Te),context(_,Msg)),
  339                throwme(jpl_call,acyclic(Te,Msg)) % rethrow
  340            )
  341        ->  true
  342
  343        ;   throwme(jpl_call,nonconvertible_params(Params))
  344        ),
  345        length(Params, A)
  346    ;   var(Params)
  347    ->  throwme(jpl_call,arg3_is_var)
  348    ;   throwme(jpl_call,arg3_is_bad(Params))
  349    ),
  350    (   Kind == instance
  351    ->  jpl_call_instance(Type, Obj, Mspec, Params, Taps, A, Rx)
  352    ;   jpl_call_static(Type, ClassObj, Mspec, Params, Taps, A, Rx)
  353    ),
  354    (   nonvar(R),
  355        R = {Term}  % yucky way of requesting Term->term conversion
  356    ->  (   jni_jref_to_term(Rx, TermX)    % fails if Rx isn't a JRef to a org.jpl7.Term
  357        ->  Term = TermX
  358        ;   throwme(jpl_call,not_a_jpl_term(Rx))
  359        )
  360    ;   R = Rx
  361    ).
 jpl_call_instance(+ObjectType, +Object, +MethodName, +Params, +ActualParamTypes, +Arity, -Result)
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.
  371jpl_call_instance(Type, Obj, Mname, Params, Taps, A, Rx) :-
  372    findall(                    % get remaining details of all accessible methods of Obj's class (as denoted by Type)
  373        z5(I,Mods,MID,Tr,Tfps),
  374        jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
  375        Z5s
  376    ),
  377    (   Z5s = []
  378    ->  throwme(jpl_call_instance,no_such_method(Mname/A))
  379    ;   findall(
  380            z5(I,Mods,MID,Tr,Tfps),             % those to which Params is assignable
  381            (   member(z5(I,Mods,MID,Tr,Tfps), Z5s),
  382                jpl_types_fit_types(Taps, Tfps) % assignability test: actual param types "fit" formal param types
  383            ),
  384            Z5sA                                % Params-assignable methods
  385        ),
  386        (   Z5sA == []
  387        ->  throwme(jpl_call_instance,param_not_assignable(Params))
  388        ;   Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
  389        ->  true                                % exactly one applicable method
  390        ;   jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
  391        ->  true                                % exactly one most-specific applicable method
  392        ;   throwme(jpl_call_instance,multiple_most_specific(Mname/Params))
  393        )
  394    ),
  395    (   member(static, Mods)                                        % if the chosen method is static
  396    ->  jpl_object_to_class(Obj, ClassObj),                         % get a java.lang.Class instance which personifies Obj's class
  397        jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx) % call static method w.r.t. associated Class object
  398    ;   jpl_call_instance_method(Tr, Obj, MID, Tfps, Params, Rx)    % else call (non-static) method w.r.t. object itself
  399    ).
 jpl_call_static(+ClassType, +ClassObject, +MethodName, +Params, +ActualParamTypes, +Arity, -Result)
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.
  410jpl_call_static(Type, ClassObj, Mname, Params, Taps, A, Rx) :-
  411    findall(                    % get all accessible static methods of the class denoted by Type and ClassObj
  412        z5(I,Mods,MID,Tr,Tfps),
  413        (   jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
  414            member(static, Mods)
  415        ),
  416        Z5s
  417    ),
  418    (   Z5s = []
  419    ->  throwme(jpl_call_static,no_such_method(Mname))
  420    ;   findall(
  421            z5(I,Mods,MID,Tr,Tfps),
  422            (   member(z5(I,Mods,MID,Tr,Tfps), Z5s),
  423                jpl_types_fit_types(Taps, Tfps) % assignability test: actual param types "fit" formal param types
  424            ),
  425            Z5sA                                % Params-assignable methods
  426        ),
  427        (   Z5sA == []
  428        ->  throwme(jpl_call_static,param_not_assignable(Params))
  429        ;   Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
  430        ->  true                % exactly one applicable method
  431        ;   jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
  432        ->  true                % exactly one most-specific applicable method
  433        ;   throwme(jpl_call_instance,multiple_most_specific(Mname/Params))
  434        )
  435    ),
  436    jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx).
 jpl_call_instance_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result)
  441jpl_call_instance_method(void, Class, MID, Tfps, Ps, R) :-
  442    jCallVoidMethod(Class, MID, Tfps, Ps),
  443    jpl_void(R).
  444jpl_call_instance_method(boolean, Class, MID, Tfps, Ps, R) :-
  445    jCallBooleanMethod(Class, MID, Tfps, Ps, R).
  446jpl_call_instance_method(byte, Class, MID, Tfps, Ps, R) :-
  447    jCallByteMethod(Class, MID, Tfps, Ps, R).
  448jpl_call_instance_method(char, Class, MID, Tfps, Ps, R) :-
  449    jCallCharMethod(Class, MID, Tfps, Ps, R).
  450jpl_call_instance_method(short, Class, MID, Tfps, Ps, R) :-
  451    jCallShortMethod(Class, MID, Tfps, Ps, R).
  452jpl_call_instance_method(int, Class, MID, Tfps, Ps, R) :-
  453    jCallIntMethod(Class, MID, Tfps, Ps, R).
  454jpl_call_instance_method(long, Class, MID, Tfps, Ps, R) :-
  455    jCallLongMethod(Class, MID, Tfps, Ps, R).
  456jpl_call_instance_method(float, Class, MID, Tfps, Ps, R) :-
  457    jCallFloatMethod(Class, MID, Tfps, Ps, R).
  458jpl_call_instance_method(double, Class, MID, Tfps, Ps, R) :-
  459    jCallDoubleMethod(Class, MID, Tfps, Ps, R).
  460jpl_call_instance_method(array(_), Class, MID, Tfps, Ps, R) :-
  461    jCallObjectMethod(Class, MID, Tfps, Ps, R).
  462jpl_call_instance_method(class(_,_), Class, MID, Tfps, Ps, R) :-
  463    jCallObjectMethod(Class, MID, Tfps, Ps, R).
 jpl_call_static_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result)
  468jpl_call_static_method(void, Class, MID, Tfps, Ps, R) :-
  469    jCallStaticVoidMethod(Class, MID, Tfps, Ps),
  470    jpl_void(R).
  471jpl_call_static_method(boolean, Class, MID, Tfps, Ps, R) :-
  472    jCallStaticBooleanMethod(Class, MID, Tfps, Ps, R).
  473jpl_call_static_method(byte, Class, MID, Tfps, Ps, R) :-
  474    jCallStaticByteMethod(Class, MID, Tfps, Ps, R).
  475jpl_call_static_method(char, Class, MID, Tfps, Ps, R) :-
  476    jCallStaticCharMethod(Class, MID, Tfps, Ps, R).
  477jpl_call_static_method(short, Class, MID, Tfps, Ps, R) :-
  478    jCallStaticShortMethod(Class, MID, Tfps, Ps, R).
  479jpl_call_static_method(int, Class, MID, Tfps, Ps, R) :-
  480    jCallStaticIntMethod(Class, MID, Tfps, Ps, R).
  481jpl_call_static_method(long, Class, MID, Tfps, Ps, R) :-
  482    jCallStaticLongMethod(Class, MID, Tfps, Ps, R).
  483jpl_call_static_method(float, Class, MID, Tfps, Ps, R) :-
  484    jCallStaticFloatMethod(Class, MID, Tfps, Ps, R).
  485jpl_call_static_method(double, Class, MID, Tfps, Ps, R) :-
  486    jCallStaticDoubleMethod(Class, MID, Tfps, Ps, R).
  487jpl_call_static_method(array(_), Class, MID, Tfps, Ps, R) :-
  488    jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
  489jpl_call_static_method(class(_,_), Class, MID, Tfps, Ps, R) :-
  490    jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
 jpl_get(+X, +Fspec, -V:datum) is det
X can be

Fspec can be

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].
  522jpl_get(X, Fspec, V) :-
  523    (   jpl_object_to_type(X, Type)
  524    ->  Obj = X,
  525        jpl_get_instance(Type, Type, Obj, Fspec, Vx)   % pass Type twice for FAI
  526    ;   var(X)
  527    ->  throwme(jpl_get,arg1_is_var)
  528    ;   jpl_is_type(X)          % e.g. class([java,lang],['String']), array(int)
  529    ->  Type = X,
  530        (   jpl_type_to_class(Type, ClassObj)
  531        ->  jpl_get_static(Type, ClassObj, Fspec, Vx)
  532        ;   throwme(jpl_get,named_class_not_found(Type))
  533        )
  534    ;   atom(X)
  535    ->  (   jpl_entityname_to_type(X, Type)     % does this attempt to load the class? (NO!)
  536        ->  (   jpl_type_to_class(Type, ClassObj)
  537            ->  jpl_get_static(Type, ClassObj, Fspec, Vx)
  538            ;   throwme(jpl_get,named_class_not_found(Type))
  539            )
  540        ;   throwme(jpl_get,arg1_is_bad(X))
  541        )
  542    ;   throwme(jpl_get,arg1_is_bad_2(X))
  543    ),
  544    (   nonvar(V),
  545        V = {Term}  % yucky way of requesting Term->term conversion
  546    ->  (   jni_jref_to_term(Vx, TermX)    % fails if Rx is not a JRef to a org.jpl7.Term
  547        ->  Term = TermX
  548        ;   throwme(jpl_get,not_a_jpl_term(X))
  549        )
  550    ;   V = Vx
  551    ).
 jpl_get_static(+Type:type, +ClassObject:jref, +FieldName:atom, -Value:datum) is det
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
  563jpl_get_static(Type, ClassObj, Fname, Vx) :-
  564    (   atom(Fname)             % assume it's a field name
  565    ->  true
  566    ;   var(Fname)
  567    ->  throwme(jpl_get_static,arg2_is_var)
  568    ;   throwme(jpl_get_static,arg2_is_bad(Fname))
  569    ),
  570  % get static fields of the denoted class
  571    findall(
  572        z4(I,Mods,FID,Tf),
  573        (   jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
  574            member(static, Mods)
  575        ),
  576        Z4s
  577    ),
  578    (   Z4s = []
  579    ->  throwme(jpl_get_static,no_such_field(Fname))
  580    ;   Z4s = [z4(I,_Mods,FID,Tf)]
  581    ->  jpl_get_static_field(Tf, ClassObj, FID, Vx)
  582    ;   throwme(jpl_get_static,multiple_fields(Fname))
  583    ).
 jpl_get_instance(+Type, +Type, +Object, +FieldSpecifier, -Value) is det
  589jpl_get_instance(class(_,_), Type, Obj, Fname, Vx) :-
  590    (   atom(Fname)                 % the usual case
  591    ->  true
  592    ;   var(Fname)
  593    ->  throwme(jpl_get_instance,arg2_is_var)
  594    ;   throwme(jpl_get_instance,arg2_is_bad(Fname))
  595    ),
  596    findall(
  597        z4(I,Mods,FID,Tf),
  598        jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
  599        Z4s
  600    ),
  601    (   Z4s = []
  602    ->  throwme(jpl_get_instance,no_such_field(Fname))
  603    ;   Z4s = [z4(I,Mods,FID,Tf)]
  604    ->  (   member(static, Mods)
  605        ->  jpl_object_to_class(Obj, ClassObj),
  606            jpl_get_static_field(Tf, ClassObj, FID, Vx)
  607        ;   jpl_get_instance_field(Tf, Obj, FID, Vx)
  608        )
  609    ;   throwme(jpl_get_instance,multiple_fields(Fname))
  610    ).
  611
  612
  613jpl_get_instance(array(ElementType), _, Array, Fspec, Vx) :-
  614    (   var(Fspec)
  615    ->  throwme(jpl_get_instance_array,arg2_is_var)
  616    ;   integer(Fspec)
  617    ->  (   Fspec < 0       % lo bound check
  618        ->  throwme(jpl_get_instance_array,arg2_is_bad(Fspec))
  619        ;   jGetArrayLength(Array, Len),
  620            Fspec >= Len    % hi bound check
  621        ->  throwme(jpl_get_instance_array,arg2_is_too_large(Fspec))
  622        ;   jpl_get_array_element(ElementType, Array, Fspec, Vx)
  623        )
  624    ;   Fspec = N-M     % NB should we support e.g. 3-2 -> [] ?
  625    ->  (   integer(N),
  626            integer(M)
  627        ->  (   N >= 0,
  628                M >= N
  629            ->  jGetArrayLength(Array, Len),
  630                (   N >= Len
  631                ->  throwme(jpl_get_instance_array,bad_range_low(N-M))
  632                ;   M >= Len
  633                ->  throwme(jpl_get_instance_array,bad_range_high(N-M))
  634                ;   jpl_get_array_elements(ElementType, Array, N, M, Vx)
  635                )
  636            ;   throwme(jpl_get_instance_array,bad_range_pair_values(N-M))
  637            )
  638        ;   throwme(jpl_get_instance_array,bad_range_pair_types(N-M))
  639        )
  640    ;   atom(Fspec)
  641    ->  (   Fspec == length             % special-case for this solitary array "method"
  642        ->  jGetArrayLength(Array, Vx)
  643        ;   throwme(jpl_get_instance_array,no_such_field(Fspec))
  644        )
  645    ;   throwme(jpl_get_instance_array,wrong_spec(Fspec))
  646    ).
 jpl_get_array_element(+ElementType:type, +Array:jref, +Index, -Vc) is det
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
  659jpl_get_array_element(Type, Array, Index, Vc) :-
  660    (   (   Type = class(_,_)
  661        ;   Type = array(_)
  662        )
  663    ->  jGetObjectArrayElement(Array, Index, Vr)
  664    ;   jpl_primitive_type(Type)
  665    ->  jni_type_to_xput_code(Type, Xc),
  666        jni_alloc_buffer(Xc, 1, Bp),        % one-element buf for a Type
  667        jpl_get_primitive_array_region(Type, Array, Index, 1, Bp),
  668        jni_fetch_buffer_value(Bp, 0, Vr, Xc),    % zero-th element
  669        jni_free_buffer(Bp)
  670    ),
  671    Vr = Vc.    % redundant since Vc is always (?) unbound at call
 jpl_get_array_elements(+ElementType, +Array, +N, +M, -Vs)
serves only jpl_get_instance/5

Vs will always be unbound on entry

  680jpl_get_array_elements(ElementType, Array, N, M, Vs) :-
  681    (   (   ElementType = class(_,_)
  682        ;   ElementType = array(_)
  683        )
  684    ->  jpl_get_object_array_elements(Array, N, M, Vs)
  685    ;   jpl_get_primitive_array_elements(ElementType, Array, N, M, Vs)
  686    ).
  687
  688
  689jpl_get_instance_field(boolean, Obj, FieldID, V) :-
  690    jGetBooleanField(Obj, FieldID, V).
  691jpl_get_instance_field(byte, Obj, FieldID, V) :-
  692    jGetByteField(Obj, FieldID, V).
  693jpl_get_instance_field(char, Obj, FieldID, V) :-
  694    jGetCharField(Obj, FieldID, V).
  695jpl_get_instance_field(short, Obj, FieldID, V) :-
  696    jGetShortField(Obj, FieldID, V).
  697jpl_get_instance_field(int, Obj, FieldID, V) :-
  698    jGetIntField(Obj, FieldID, V).
  699jpl_get_instance_field(long, Obj, FieldID, V) :-
  700    jGetLongField(Obj, FieldID, V).
  701jpl_get_instance_field(float, Obj, FieldID, V) :-
  702    jGetFloatField(Obj, FieldID, V).
  703jpl_get_instance_field(double, Obj, FieldID, V) :-
  704    jGetDoubleField(Obj, FieldID, V).
  705jpl_get_instance_field(class(_,_), Obj, FieldID, V) :-
  706    jGetObjectField(Obj, FieldID, V).
  707jpl_get_instance_field(array(_), Obj, FieldID, V) :-
  708    jGetObjectField(Obj, FieldID, V).
 jpl_get_object_array_elements(+Array, +LoIndex, +HiIndex, -Vcs) is det
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
  720jpl_get_object_array_elements(Array, Lo, Hi, Vcs) :-
  721    (   Lo =< Hi
  722    ->  Vcs = [Vc|Vcs2],
  723        jGetObjectArrayElement(Array, Lo, Vc),
  724        Next is Lo+1,
  725        jpl_get_object_array_elements(Array, Next, Hi, Vcs2)
  726    ;   Vcs = []
  727    ).
 jpl_get_primitive_array_elements(+ElementType, +Array, +LoIndex, +HiIndex, -Vcs) is det
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
  737jpl_get_primitive_array_elements(ElementType, Array, Lo, Hi, Vcs) :-
  738    Size is Hi-Lo+1,
  739    (   Size == 0
  740    ->  Vcs = []
  741    ;   jni_type_to_xput_code(ElementType, Xc),
  742        jni_alloc_buffer(Xc, Size, Bp),
  743        jpl_get_primitive_array_region(ElementType, Array, Lo, Size, Bp),
  744        jpl_primitive_buffer_to_array(ElementType, Xc, Bp, 0, Size, Vcs),
  745        jni_free_buffer(Bp)
  746    ).
  747
  748
  749jpl_get_primitive_array_region(boolean, Array, Lo, S, I) :-
  750    jGetBooleanArrayRegion(Array, Lo, S, jbuf(I,boolean)).
  751jpl_get_primitive_array_region(byte, Array, Lo, S, I) :-
  752    jGetByteArrayRegion(Array, Lo, S, jbuf(I,byte)).
  753jpl_get_primitive_array_region(char, Array, Lo, S, I) :-
  754    jGetCharArrayRegion(Array, Lo, S, jbuf(I,char)).
  755jpl_get_primitive_array_region(short, Array, Lo, S, I) :-
  756    jGetShortArrayRegion(Array, Lo, S, jbuf(I,short)).
  757jpl_get_primitive_array_region(int, Array, Lo, S, I) :-
  758    jGetIntArrayRegion(Array, Lo, S, jbuf(I,int)).
  759jpl_get_primitive_array_region(long, Array, Lo, S, I) :-
  760    jGetLongArrayRegion(Array, Lo, S, jbuf(I,long)).
  761jpl_get_primitive_array_region(float, Array, Lo, S, I) :-
  762    jGetFloatArrayRegion(Array, Lo, S, jbuf(I,float)).
  763jpl_get_primitive_array_region(double, Array, Lo, S, I) :-
  764    jGetDoubleArrayRegion(Array, Lo, S, jbuf(I,double)).
  765
  766
  767jpl_get_static_field(boolean, Array, FieldID, V) :-
  768    jGetStaticBooleanField(Array, FieldID, V).
  769jpl_get_static_field(byte, Array, FieldID, V) :-
  770    jGetStaticByteField(Array, FieldID, V).
  771jpl_get_static_field(char, Array, FieldID, V) :-
  772    jGetStaticCharField(Array, FieldID, V).
  773jpl_get_static_field(short, Array, FieldID, V) :-
  774    jGetStaticShortField(Array, FieldID, V).
  775jpl_get_static_field(int, Array, FieldID, V) :-
  776    jGetStaticIntField(Array, FieldID, V).
  777jpl_get_static_field(long, Array, FieldID, V) :-
  778    jGetStaticLongField(Array, FieldID, V).
  779jpl_get_static_field(float, Array, FieldID, V) :-
  780    jGetStaticFloatField(Array, FieldID, V).
  781jpl_get_static_field(double, Array, FieldID, V) :-
  782    jGetStaticDoubleField(Array, FieldID, V).
  783jpl_get_static_field(class(_,_), Array, FieldID, V) :-
  784    jGetStaticObjectField(Array, FieldID, V).
  785jpl_get_static_field(array(_), Array, FieldID, V) :-
  786    jGetStaticObjectField(Array, FieldID, V).
 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

Fspec can be

V must be a suitable value or object.

  806jpl_set(X, Fspec, V) :-
  807    (   jpl_object_to_type(X, Type)         % the usual case (test is safe if X is var or rubbish)
  808    ->  Obj = X,
  809        catch(
  810            jpl_set_instance(Type, Type, Obj, Fspec, V),    % first 'Type' is for FAI
  811            % 2020-07-21: make catcher's 1st context arg an "anonvar" instead of a overspecified predicate indicator
  812            error(type_error(acyclic,Te),context(_,Msg)),
  813            throwme(jpl_set,acyclic(Te,Msg)) % rethrow
  814        )
  815    ;   var(X)
  816    ->  throwme(jpl_set,arg1_is_var)
  817    ;   (   atom(X)
  818        ->  (   jpl_entityname_to_type(X, Type)          % it's a classname or descriptor...
  819            ->  true
  820            ;   throwme(jpl_set,classname_does_not_resolve(X))
  821            )
  822        ;   (   X = class(_,_)                          % it's a class type...
  823            ;   X = array(_)                            % ...or an array type
  824            )
  825        ->  Type = X
  826        ),
  827        (   jpl_type_to_class(Type, ClassObj)      % ...whose Class object is available
  828        ->  true
  829        ;   throwme(jpl_set,named_class_not_found(Type))
  830        )
  831    ->  catch(
  832            jpl_set_static(Type, ClassObj, Fspec, V),
  833            % 2020-07-21: make catcher's 1st context arg an "anonvar" instead of a overspecified predicate indicator
  834            error(type_error(acyclic,Te),context(_,Msg)),
  835            throwme(jpl_set,acyclic(Te,Msg)) % rethrow
  836        )
  837    ;   throwme(jpl_set,arg1_is_bad(X))
  838    ).
 jpl_set_instance(+Type, +Type, +ObjectReference, +FieldName, +Value) is det
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

  851jpl_set_instance(class(_,_), Type, Obj, Fname, V) :-    % a non-array object
  852    (   atom(Fname)                 % the usual case
  853    ->  true
  854    ;   var(Fname)
  855    ->  throwme(jpl_set_instance_class,arg2_is_var)
  856    ;   throwme(jpl_set_instance_class,arg2_is_bad(Fname))
  857    ),
  858    findall(
  859        z4(I,Mods,FID,Tf),
  860        jpl_field_spec(Type, I, Fname, Mods, FID, Tf),  % public fields of class denoted by Type
  861        Z4s
  862    ),
  863    (   Z4s = []
  864    ->  throwme(jpl_set_instance_class,no_such_field(Fname))
  865    ;   Z4s = [z4(I,Mods,FID,Tf)]
  866    ->  (   member(final, Mods)
  867        ->  throwme(jpl_set_instance_class,field_is_final(Fname))
  868        ;   jpl_datum_to_type(V, Tv)
  869        ->  (   jpl_type_fits_type(Tv, Tf)
  870            ->  (   member(static, Mods)
  871                ->  jpl_object_to_class(Obj, ClassObj),
  872                    jpl_set_static_field(Tf, ClassObj, FID, V)
  873                ;   jpl_set_instance_field(Tf, Obj, FID, V)         % oughta be jpl_set_instance_field?
  874                )
  875            ;   throwme(jpl_set_instance_class,incompatible_value(Tf,V))
  876            )
  877        ;   throwme(jpl_set_instance_class,arg3_is_bad(V))
  878        )
  879    ;   throwme(jpl_set_instance_class,multiple_fields(Fname))  % 'existence'? or some other sort of error maybe?
  880    ).
  881
  882
  883
  884jpl_set_instance(array(Type), _, Obj, Fspec, V) :-
  885    (   is_list(V)                  % a list of array element values
  886    ->  Vs = V
  887    ;   var(V)
  888    ->  throwme(jpl_set_instance_array,arg3_is_var)
  889    ;   Vs = [V]                    % a single array element value
  890    ),
  891    length(Vs, Iv),
  892    (   var(Fspec)
  893    ->  throwme(jpl_set_instance_array,arg2_is_var)
  894    ;   integer(Fspec)          % single-element assignment
  895    ->  (   Fspec < 0
  896        ->  throwme(jpl_set_instance_array,arg2_is_bad(Fspec))
  897        ;   Iv is 1
  898        ->  N is Fspec
  899        ;   Iv is 0
  900        ->  throwme(jpl_set_instance_array,no_values(Fspec,Vs))
  901        ;   throwme(jpl_set_instance_array,more_than_one_value(Fspec,Vs))
  902        )
  903    ;   Fspec = N-M             % element-sequence assignment
  904    ->  (   integer(N),
  905            integer(M)
  906        ->  (   N >= 0,
  907                Size is (M-N)+1,
  908                Size >= 0
  909            ->  (   Size == Iv
  910                ->  true
  911                ;   Size < Iv
  912                ->  throwme(jpl_set_instance_array,too_few_values(N-M,Vs))
  913                ;   throwme(jpl_set_instance_array,too_many_values(N-M,Vs))
  914                )
  915            ;   throwme(jpl_set_instance_array,bad_range_pair_values(N-M))
  916            )
  917        ;   throwme(jpl_set_instance_array,bad_range_pair_types(N-M))
  918        )
  919    ;   atom(Fspec)
  920    ->  (   Fspec == length
  921        ->  throwme(jpl_set_instance_array,cannot_assign_to_final_field)
  922        ;   throwme(jpl_set_instance_array,no_such_field(Fspec))
  923        )
  924    ;   throwme(jpl_set_instance_array,arg2_is_bad_2(Fspec))
  925    ),
  926    jpl_set_array(Type, Obj, N, Iv, Vs).
 jpl_set_static(+Type, +ClassObj, +FieldName, +Value) is det
We can rely on:

NB this does not yet handle shadowed fields correctly.

  941jpl_set_static(Type, ClassObj, Fname, V) :-
  942    (   atom(Fname)                     % the usual case
  943    ->  true
  944    ;   var(Fname)
  945    ->  throwme(jpl_set_static,arg2_is_unbound)
  946    ;   throwme(jpl_set_static,arg2_is_bad(Fname))
  947    ),
  948    findall(  % get all static fields of the denoted class
  949        z4(I,Mods,FID,Tf),
  950        (   jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
  951            member(static, Mods)
  952        ),
  953        Z4s
  954    ),
  955    (   Z4s = []
  956    ->  throwme(jpl_set_static,no_such_public_static_field(field,Fname))
  957    ;   Z4s = [z4(I,Mods,FID,Tf)]       % exactly one synonymous field?
  958    ->  (   member(final, Mods)
  959        ->  throwme(jpl_set_static,cannot_assign_final_field(Fname))
  960        ;   jpl_datum_to_type(V, Tv)
  961        ->  (   jpl_type_fits_type(Tv, Tf)
  962            ->  jpl_set_static_field(Tf, ClassObj, FID, V)
  963            ;   throwme(jpl_set_static,value_not_assignable(Tf,V))
  964            )
  965        ;   throwme(jpl_set_static,arg3_is_bad(field_value,V))
  966        )
  967    ;   throwme(jpl_set_static,multiple_matches(field,Fname))
  968    ).
 jpl_set_array(+ElementType, +Array, +Offset, +DatumQty, +Datums) is det
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,_))
  978jpl_set_array(T, A, N, I, Ds) :-
  979    (   jpl_datums_to_types(Ds, Tds)        % most specialised types of given values
  980    ->  (   jpl_types_fit_type(Tds, T)      % all assignable to element type?
  981        ->  true
  982        ;   throwme(jpl_set_array,not_all_values_assignable(T,Ds))
  983        )
  984    ;   throwme(jpl_set_array,not_all_values_convertible(T,Ds))
  985    ),
  986    (   (   T = class(_,_)
  987        ;   T = array(_)                    % array elements are objects
  988        )
  989    ->  (   nth0(J, Ds, D),                 % for each datum
  990            Nd is N+J,                      % compute array index
  991            (   D = {Tq}                    % quoted term?
  992            ->  jni_term_to_jref(Tq, D2)    % convert to a JPL reference to a corresponding org.jpl7.Term object
  993            ;   D = D2
  994            ),
  995            jSetObjectArrayElement(A, Nd, D2),
  996            fail                            % iterate
  997        ;   true
  998        )
  999    ;   jpl_primitive_type(T)               % array elements are primitive values
 1000    ->  jni_type_to_xput_code(T, Xc),
 1001        jni_alloc_buffer(Xc, I, Bp),        % I-element buf of required primitive type
 1002        jpl_set_array_1(Ds, T, 0, Bp),
 1003        jpl_set_elements(T, A, N, I, Bp),
 1004        jni_free_buffer(Bp)
 1005    ;
 1006        % T is neither a class, nor an array type nor a primitive type
 1007        throwme(jpl_set_array,element_type_unknown(array_element_type,T))
 1008    ).
 jpl_set_array_1(+Values, +Type, +BufferIndex, +BufferPointer) is det
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...

 1019jpl_set_array_1([], _, _, _).
 1020jpl_set_array_1([V|Vs], Tprim, Ib, Bp) :-
 1021    jni_type_to_xput_code(Tprim, Xc),
 1022    jni_stash_buffer_value(Bp, Ib, V, Xc),
 1023    Ibnext is Ib+1,
 1024    jpl_set_array_1(Vs, Tprim, Ibnext, Bp).
 1025
 1026
 1027jpl_set_elements(boolean, Obj, N, I, Bp) :-
 1028    jSetBooleanArrayRegion(Obj, N, I, jbuf(Bp,boolean)).
 1029jpl_set_elements(char, Obj, N, I, Bp) :-
 1030    jSetCharArrayRegion(Obj, N, I, jbuf(Bp,char)).
 1031jpl_set_elements(byte, Obj, N, I, Bp) :-
 1032    jSetByteArrayRegion(Obj, N, I, jbuf(Bp,byte)).
 1033jpl_set_elements(short, Obj, N, I, Bp) :-
 1034    jSetShortArrayRegion(Obj, N, I, jbuf(Bp,short)).
 1035jpl_set_elements(int, Obj, N, I, Bp) :-
 1036    jSetIntArrayRegion(Obj, N, I, jbuf(Bp,int)).
 1037jpl_set_elements(long, Obj, N, I, Bp) :-
 1038    jSetLongArrayRegion(Obj, N, I, jbuf(Bp,long)).
 1039jpl_set_elements(float, Obj, N, I, Bp) :-
 1040    jSetFloatArrayRegion(Obj, N, I, jbuf(Bp,float)).
 1041jpl_set_elements(double, Obj, N, I, Bp) :-
 1042    jSetDoubleArrayRegion(Obj, N, I, jbuf(Bp,double)).
 jpl_set_instance_field(+Type, +Obj, +FieldID, +V) is det
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)
 1050jpl_set_instance_field(boolean, Obj, FieldID, V) :-
 1051    jSetBooleanField(Obj, FieldID, V).
 1052jpl_set_instance_field(byte, Obj, FieldID, V) :-
 1053    jSetByteField(Obj, FieldID, V).
 1054jpl_set_instance_field(char, Obj, FieldID, V) :-
 1055    jSetCharField(Obj, FieldID, V).
 1056jpl_set_instance_field(short, Obj, FieldID, V) :-
 1057    jSetShortField(Obj, FieldID, V).
 1058jpl_set_instance_field(int, Obj, FieldID, V) :-
 1059    jSetIntField(Obj, FieldID, V).
 1060jpl_set_instance_field(long, Obj, FieldID, V) :-
 1061    jSetLongField(Obj, FieldID, V).
 1062jpl_set_instance_field(float, Obj, FieldID, V) :-
 1063    jSetFloatField(Obj, FieldID, V).
 1064jpl_set_instance_field(double, Obj, FieldID, V) :-
 1065    jSetDoubleField(Obj, FieldID, V).
 1066jpl_set_instance_field(class(_,_), Obj, FieldID, V) :-  % also handles byval term assignments
 1067    (   V = {T}                     % quoted term?
 1068    ->  jni_term_to_jref(T, V2)     % convert to a JPL reference to a corresponding org.jpl7.Term object
 1069    ;   V = V2
 1070    ),
 1071    jSetObjectField(Obj, FieldID, V2).
 1072jpl_set_instance_field(array(_), Obj, FieldID, V) :-
 1073    jSetObjectField(Obj, FieldID, V).
 jpl_set_static_field(+Type, +ClassObj, +FieldID, +V)
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).
 1081jpl_set_static_field(boolean, Obj, FieldID, V) :-
 1082    jSetStaticBooleanField(Obj, FieldID, V).
 1083jpl_set_static_field(byte, Obj, FieldID, V) :-
 1084    jSetStaticByteField(Obj, FieldID, V).
 1085jpl_set_static_field(char, Obj, FieldID, V) :-
 1086    jSetStaticCharField(Obj, FieldID, V).
 1087jpl_set_static_field(short, Obj, FieldID, V) :-
 1088    jSetStaticShortField(Obj, FieldID, V).
 1089jpl_set_static_field(int, Obj, FieldID, V) :-
 1090    jSetStaticIntField(Obj, FieldID, V).
 1091jpl_set_static_field(long, Obj, FieldID, V) :-
 1092    jSetStaticLongField(Obj, FieldID, V).
 1093jpl_set_static_field(float, Obj, FieldID, V) :-
 1094    jSetStaticFloatField(Obj, FieldID, V).
 1095jpl_set_static_field(double, Obj, FieldID, V) :-
 1096    jSetStaticDoubleField(Obj, FieldID, V).
 1097jpl_set_static_field(class(_,_), Obj, FieldID, V) :-    % also handles byval term assignments
 1098    (   V = {T}                         % quoted term?
 1099    ->  jni_term_to_jref(T, V2)         % convert to a JPL reference to a corresponding org.jpl7.Term object
 1100    ;   V = V2
 1101    ),
 1102    jSetStaticObjectField(Obj, FieldID, V2).
 1103jpl_set_static_field(array(_), Obj, FieldID, V) :-
 1104    jSetStaticObjectField(Obj, FieldID, V).
 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']
 1112jpl_get_default_jvm_opts(Opts) :-
 1113    jni_get_default_jvm_opts(Opts).
 jpl_set_default_jvm_opts(+Opts:list(atom)) is det
Replaces the default JVM initialisation options with those supplied.
 1120jpl_set_default_jvm_opts(Opts) :-
 1121    is_list(Opts),
 1122    length(Opts, N),
 1123    jni_set_default_jvm_opts(N, Opts).
 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.

 1132jpl_get_actual_jvm_opts(Opts) :-
 1133    jni_get_actual_jvm_opts(Opts).
 1134
 1135% ===========================================================================
 1136% Caching
 1137% ===========================================================================
 1138
 1139% In principle the predicates subject to assert/1 must be declared with the
 1140% dynamic/1 directive. However, they are automatically declared as "dynamic"
 1141% if they appear in an assert/1 call first. Anyway, we declare then dynamic
 1142% right here!
 1143
 1144:- dynamic jpl_field_spec_cache/6.      % document this...
 1145:- dynamic jpl_field_spec_is_cached/1.  % document this...
 1146:- dynamic jpl_method_spec_cache/8. 1147:- dynamic jpl_method_spec_is_cached/1. 1148:- dynamic jpl_iref_type_cache/2.
 jpl_classname_type_cache(-Classname:className, -Type:type)
Classname is the atomic name of Type.

NB may denote a class which cannot be found.

 1156:- dynamic jpl_classname_type_cache/2.
 jpl_class_tag_type_cache(-Class:jref, -Type:jpl_type)
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)

 1170:- dynamic jpl_class_tag_type_cache/2.
 jpl_assert(+Fact:term)
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
 1195jpl_assert(Fact) :-
 1196    (   jpl_assert_policy(Fact, yes)
 1197    ->  assertz(Fact)
 1198    ;   true
 1199    ).
 1200
 1201% ---
 1202% policies
 1203% ---
 1204
 1205jpl_assert_policy(jpl_field_spec_cache(_,_,_,_,_,_), yes).
 1206jpl_assert_policy(jpl_field_spec_is_cached(_), YN) :-
 1207   jpl_assert_policy(jpl_field_spec_cache(_,_,_,_,_,_), YN).
 1208
 1209jpl_assert_policy(jpl_method_spec_cache(_,_,_,_,_,_,_,_), yes).
 1210jpl_assert_policy(jpl_method_spec_is_cached(_), YN) :-
 1211   jpl_assert_policy(jpl_method_spec_cache(_,_,_,_,_,_,_,_), YN).
 1212
 1213jpl_assert_policy(jpl_class_tag_type_cache(_,_), yes).
 1214jpl_assert_policy(jpl_classname_type_cache(_,_), yes).
 1215jpl_assert_policy(jpl_iref_type_cache(_,_), no).   % must correspond to JPL_CACHE_TYPE_OF_REF in jpl.c
 jpl_tidy_iref_type_cache(+Iref) is det
Delete the cached type info, if any, under Iref.

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

 1223jpl_tidy_iref_type_cache(Iref) :-
 1224  % write('[decaching types for iref='), write(Iref), write(']'), nl,
 1225    retractall(jpl_iref_type_cache(Iref,_)),
 1226    true.
 1227
 1228jpl_fergus_find_candidate([], Candidate, Candidate, []).
 1229jpl_fergus_find_candidate([X|Xs], Candidate0, Candidate, Rest) :-
 1230    (   jpl_fergus_greater(X, Candidate0)
 1231    ->  Candidate1 = X,
 1232        Rest = [Candidate0|Rest1]
 1233    ;   Candidate1 = Candidate0,
 1234        Rest = [X|Rest1]
 1235    ),
 1236    jpl_fergus_find_candidate(Xs, Candidate1, Candidate, Rest1).
 1237
 1238
 1239jpl_fergus_greater(z5(_,_,_,_,Tps1), z5(_,_,_,_,Tps2)) :-
 1240    jpl_types_fit_types(Tps1, Tps2).
 1241jpl_fergus_greater(z3(_,_,Tps1), z3(_,_,Tps2)) :-
 1242    jpl_types_fit_types(Tps1, Tps2).
 jpl_fergus_is_the_greatest(+Xs:list(T), -GreatestX:T)
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
 1253jpl_fergus_is_the_greatest([X|Xs], Greatest) :-
 1254    jpl_fergus_find_candidate(Xs, X, Greatest, Rest),
 1255    forall(
 1256        member(R, Rest),
 1257        jpl_fergus_greater(Greatest, R)
 1258    ).
 jpl_z3s_to_most_specific_z3(+Zs, -Z)
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).

 1268jpl_z3s_to_most_specific_z3(Zs, Z) :-
 1269    jpl_fergus_is_the_greatest(Zs, Z).
 jpl_z5s_to_most_specific_z5(+Zs, -Z)
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)

 1279jpl_z5s_to_most_specific_z5(Zs, Z) :-
 1280    jpl_fergus_is_the_greatest(Zs, Z).
 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'.
 1296jpl_pl_lib_version(VersionString) :-
 1297    jpl_pl_lib_version(Major, Minor, Patch, Status),
 1298    atomic_list_concat([Major,'.',Minor,'.',Patch,'-',Status], VersionString).
 jpl_pl_lib_version(-Major, -Minor, -Patch, -Status)
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.
 1315jpl_pl_lib_version(7, 6, 1, stable).  % jref as blob
 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'.
 jpl_java_lib_version(-Version)
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'.
 jpl_java_lib_version(V)
 1344jpl_java_lib_version(V) :-
 1345    jpl_call('org.jpl7.JPL', version_string, [], V).
 jpl_pl_lib_path(-Path:atom)
 1350jpl_pl_lib_path(Path) :-
 1351    module_property(jpl, file(Path)).
 jpl_c_lib_path(-Path:atom)
 1356jpl_c_lib_path(Path) :-
 1357    shlib:current_library(_, _, Path, jpl, _),
 1358    !.
 jpl_java_lib_path(-Path:atom)
 1363jpl_java_lib_path(Path) :-
 1364    jpl_call('org.jpl7.JPL', jarPath, [], Path).
 jCallBooleanMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbool:boolean)
 1369jCallBooleanMethod(Obj, MethodID, Types, Params, Rbool) :-
 1370    jni_params_put(Params, Types, ParamBuf),
 1371    jni_func(39, Obj, MethodID, ParamBuf, Rbool).
 jCallByteMethod(+Obj:jref, +MethodID:methodId, +Types, +Params:list(datum), -Rbyte:byte)
 1377jCallByteMethod(Obj, MethodID, Types, Params, Rbyte) :-
 1378    jni_params_put(Params, Types, ParamBuf),
 1379    jni_func(42, Obj, MethodID, ParamBuf, Rbyte).
 jCallCharMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rchar:char)
 1385jCallCharMethod(Obj, MethodID, Types, Params, Rchar) :-
 1386    jni_params_put(Params, Types, ParamBuf),
 1387    jni_func(45, Obj, MethodID, ParamBuf, Rchar).
 jCallDoubleMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rdouble:double)
 1392jCallDoubleMethod(Obj, MethodID, Types, Params, Rdouble) :-
 1393    jni_params_put(Params, Types, ParamBuf),
 1394    jni_func(60, Obj, MethodID, ParamBuf, Rdouble).
 jCallFloatMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rfloat:float)
 1399jCallFloatMethod(Obj, MethodID, Types, Params, Rfloat) :-
 1400    jni_params_put(Params, Types, ParamBuf),
 1401    jni_func(57, Obj, MethodID, ParamBuf, Rfloat).
 jCallIntMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rint:int)
 1406jCallIntMethod(Obj, MethodID, Types, Params, Rint) :-
 1407    jni_params_put(Params, Types, ParamBuf),
 1408    jni_func(51, Obj, MethodID, ParamBuf, Rint).
 jCallLongMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rlong:long)
 1413jCallLongMethod(Obj, MethodID, Types, Params, Rlong) :-
 1414    jni_params_put(Params, Types, ParamBuf),
 1415    jni_func(54, Obj, MethodID, ParamBuf, Rlong).
 jCallObjectMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Robj:jref)
 1420jCallObjectMethod(Obj, MethodID, Types, Params, Robj) :-
 1421    jni_params_put(Params, Types, ParamBuf),
 1422    jni_func(36, Obj, MethodID, ParamBuf, Robj).
 jCallShortMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rshort:short)
 1427jCallShortMethod(Obj, MethodID, Types, Params, Rshort) :-
 1428    jni_params_put(Params, Types, ParamBuf),
 1429    jni_func(48, Obj, MethodID, ParamBuf, Rshort).
 jCallStaticBooleanMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbool:boolean)
 1434jCallStaticBooleanMethod(Class, MethodID, Types, Params, Rbool) :-
 1435    jni_params_put(Params, Types, ParamBuf),
 1436    jni_func(119, Class, MethodID, ParamBuf, Rbool).
 jCallStaticByteMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rbyte:byte)
 1441jCallStaticByteMethod(Class, MethodID, Types, Params, Rbyte) :-
 1442    jni_params_put(Params, Types, ParamBuf),
 1443    jni_func(122, Class, MethodID, ParamBuf, Rbyte).
 jCallStaticCharMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rchar:char)
 1448jCallStaticCharMethod(Class, MethodID, Types, Params, Rchar) :-
 1449    jni_params_put(Params, Types, ParamBuf),
 1450    jni_func(125, Class, MethodID, ParamBuf, Rchar).
 jCallStaticDoubleMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rdouble:double)
 1455jCallStaticDoubleMethod(Class, MethodID, Types, Params, Rdouble) :-
 1456    jni_params_put(Params, Types, ParamBuf),
 1457    jni_func(140, Class, MethodID, ParamBuf, Rdouble).
 jCallStaticFloatMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rfloat:float)
 1462jCallStaticFloatMethod(Class, MethodID, Types, Params, Rfloat) :-
 1463    jni_params_put(Params, Types, ParamBuf),
 1464    jni_func(137, Class, MethodID, ParamBuf, Rfloat).
 jCallStaticIntMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rint:int)
 1469jCallStaticIntMethod(Class, MethodID, Types, Params, Rint) :-
 1470    jni_params_put(Params, Types, ParamBuf),
 1471    jni_func(131, Class, MethodID, ParamBuf, Rint).
 jCallStaticLongMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rlong:long)
 1476jCallStaticLongMethod(Class, MethodID, Types, Params, Rlong) :-
 1477    jni_params_put(Params, Types, ParamBuf),
 1478    jni_func(134, Class, MethodID, ParamBuf, Rlong).
 jCallStaticObjectMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Robj:jref)
 1483jCallStaticObjectMethod(Class, MethodID, Types, Params, Robj) :-
 1484    jni_params_put(Params, Types, ParamBuf),
 1485    jni_func(116, Class, MethodID, ParamBuf, Robj).
 jCallStaticShortMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Rshort:short)
 1490jCallStaticShortMethod(Class, MethodID, Types, Params, Rshort) :-
 1491    jni_params_put(Params, Types, ParamBuf),
 1492    jni_func(128, Class, MethodID, ParamBuf, Rshort).
 jCallStaticVoidMethod(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum))
 1497jCallStaticVoidMethod(Class, MethodID, Types, Params) :-
 1498    jni_params_put(Params, Types, ParamBuf),
 1499    jni_void(143, Class, MethodID, ParamBuf).
 jCallVoidMethod(+Obj:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum))
 1504jCallVoidMethod(Obj, MethodID, Types, Params) :-
 1505    jni_params_put(Params, Types, ParamBuf),
 1506    jni_void(63, Obj, MethodID, ParamBuf).
 jFindClass(+ClassName:findclassname, -Class:jref)
 1511jFindClass(ClassName, Class) :-
 1512    jni_func(6, ClassName, Class).
 jGetArrayLength(+Array:jref, -Size:int)
 1517jGetArrayLength(Array, Size) :-
 1518    jni_func(171, Array, Size).
 jGetBooleanArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:boolean_buf)
 1523jGetBooleanArrayRegion(Array, Start, Len, Buf) :-
 1524    jni_void(199, Array, Start, Len, Buf).
 jGetBooleanField(+Obj:jref, +FieldID:fieldId, -Rbool:boolean)
 1529jGetBooleanField(Obj, FieldID, Rbool) :-
 1530    jni_func(96, Obj, FieldID, Rbool).
 jGetByteArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:byte_buf)
 1535jGetByteArrayRegion(Array, Start, Len, Buf) :-
 1536    jni_void(200, Array, Start, Len, Buf).
 jGetByteField(+Obj:jref, +FieldID:fieldId, -Rbyte:byte)
 1541jGetByteField(Obj, FieldID, Rbyte) :-
 1542    jni_func(97, Obj, FieldID, Rbyte).
 jGetCharArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:char_buf)
 1547jGetCharArrayRegion(Array, Start, Len, Buf) :-
 1548    jni_void(201, Array, Start, Len, Buf).
 jGetCharField(+Obj:jref, +FieldID:fieldId, -Rchar:char)
 1553jGetCharField(Obj, FieldID, Rchar) :-
 1554    jni_func(98, Obj, FieldID, Rchar).
 jGetDoubleArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:double_buf)
 1559jGetDoubleArrayRegion(Array, Start, Len, Buf) :-
 1560    jni_void(206, Array, Start, Len, Buf).
 jGetDoubleField(+Obj:jref, +FieldID:fieldId, -Rdouble:double)
 1565jGetDoubleField(Obj, FieldID, Rdouble) :-
 1566    jni_func(103, Obj, FieldID, Rdouble).
 jGetFieldID(+Class:jref, +Name:fieldName, +Type:type, -FieldID:fieldId)
 1571jGetFieldID(Class, Name, Type, FieldID) :-
 1572    jpl_type_to_java_field_descriptor(Type, FD),
 1573    jni_func(94, Class, Name, FD, FieldID).
 jGetFloatArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:float_buf)
 1578jGetFloatArrayRegion(Array, Start, Len, Buf) :-
 1579    jni_void(205, Array, Start, Len, Buf).
 jGetFloatField(+Obj:jref, +FieldID:fieldId, -Rfloat:float)
 1584jGetFloatField(Obj, FieldID, Rfloat) :-
 1585    jni_func(102, Obj, FieldID, Rfloat).
 jGetIntArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:int_buf)
 1590jGetIntArrayRegion(Array, Start, Len, Buf) :-
 1591    jni_void(203, Array, Start, Len, Buf).
 jGetIntField(+Obj:jref, +FieldID:fieldId, -Rint:int)
 1596jGetIntField(Obj, FieldID, Rint) :-
 1597    jni_func(100, Obj, FieldID, Rint).
 jGetLongArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:long_buf)
 1602jGetLongArrayRegion(Array, Start, Len, Buf) :-
 1603    jni_void(204, Array, Start, Len, Buf).
 jGetLongField(+Obj:jref, +FieldID:fieldId, -Rlong:long)
 1608jGetLongField(Obj, FieldID, Rlong) :-
 1609    jni_func(101, Obj, FieldID, Rlong).
 jGetMethodID(+Class:jref, +Name:atom, +Type:type, -MethodID:methodId)
 1614jGetMethodID(Class, Name, Type, MethodID) :-
 1615    jpl_type_to_java_method_descriptor(Type, MD),
 1616    jni_func(33, Class, Name, MD, MethodID).
 jGetObjectArrayElement(+Array:jref, +Index:int, -Obj:jref)
 1621jGetObjectArrayElement(Array, Index, Obj) :-
 1622    jni_func(173, Array, Index, Obj).
 jGetObjectClass(+Object:jref, -Class:jref)
 1627jGetObjectClass(Object, Class) :-
 1628    jni_func(31, Object, Class).
 jGetObjectField(+Obj:jref, +FieldID:fieldId, -RObj:jref)
 1633jGetObjectField(Obj, FieldID, Robj) :-
 1634    jni_func(95, Obj, FieldID, Robj).
 jGetShortArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:short_buf)
 1639jGetShortArrayRegion(Array, Start, Len, Buf) :-
 1640    jni_void(202, Array, Start, Len, Buf).
 jGetShortField(+Obj:jref, +FieldID:fieldId, -Rshort:short)
 1645jGetShortField(Obj, FieldID, Rshort) :-
 1646    jni_func(99, Obj, FieldID, Rshort).
 jGetStaticBooleanField(+Class:jref, +FieldID:fieldId, -Rbool:boolean)
 1651jGetStaticBooleanField(Class, FieldID, Rbool) :-
 1652    jni_func(146, Class, FieldID, Rbool).
 jGetStaticByteField(+Class:jref, +FieldID:fieldId, -Rbyte:byte)
 1657jGetStaticByteField(Class, FieldID, Rbyte) :-
 1658    jni_func(147, Class, FieldID, Rbyte).
 jGetStaticCharField(+Class:jref, +FieldID:fieldId, -Rchar:char)
 1663jGetStaticCharField(Class, FieldID, Rchar) :-
 1664    jni_func(148, Class, FieldID, Rchar).
 jGetStaticDoubleField(+Class:jref, +FieldID:fieldId, -Rdouble:double)
 1669jGetStaticDoubleField(Class, FieldID, Rdouble) :-
 1670    jni_func(153, Class, FieldID, Rdouble).
 jGetStaticFieldID(+Class:jref, +Name:fieldName, +Type:type, -FieldID:fieldId)
 1675jGetStaticFieldID(Class, Name, Type, FieldID) :-
 1676    jpl_type_to_java_field_descriptor(Type, TD),               % cache this?
 1677    jni_func(144, Class, Name, TD, FieldID).
 jGetStaticFloatField(+Class:jref, +FieldID:fieldId, -Rfloat:float)
 1682jGetStaticFloatField(Class, FieldID, Rfloat) :-
 1683    jni_func(152, Class, FieldID, Rfloat).
 jGetStaticIntField(+Class:jref, +FieldID:fieldId, -Rint:int)
 1688jGetStaticIntField(Class, FieldID, Rint) :-
 1689    jni_func(150, Class, FieldID, Rint).
 jGetStaticLongField(+Class:jref, +FieldID:fieldId, -Rlong:long)
 1694jGetStaticLongField(Class, FieldID, Rlong) :-
 1695    jni_func(151, Class, FieldID, Rlong).
 jGetStaticMethodID(+Class:jref, +Name:methodName, +Type:type, -MethodID:methodId)
 1700jGetStaticMethodID(Class, Name, Type, MethodID) :-
 1701    jpl_type_to_java_method_descriptor(Type, TD),
 1702    jni_func(113, Class, Name, TD, MethodID).
 jGetStaticObjectField(+Class:jref, +FieldID:fieldId, -RObj:jref)
 1707jGetStaticObjectField(Class, FieldID, Robj) :-
 1708    jni_func(145, Class, FieldID, Robj).
 jGetStaticShortField(+Class:jref, +FieldID:fieldId, -Rshort:short)
 1713jGetStaticShortField(Class, FieldID, Rshort) :-
 1714    jni_func(149, Class, FieldID, Rshort).
 jGetSuperclass(+Class1:jref, -Class2:jref)
 1719jGetSuperclass(Class1, Class2) :-
 1720    jni_func(10, Class1, Class2).
 jIsAssignableFrom(+Class1:jref, +Class2:jref)
 1725jIsAssignableFrom(Class1, Class2) :-
 1726    jni_func(11, Class1, Class2, @(true)).
 jNewBooleanArray(+Length:int, -Array:jref)
 1731jNewBooleanArray(Length, Array) :-
 1732    jni_func(175, Length, Array).
 jNewByteArray(+Length:int, -Array:jref)
 1737jNewByteArray(Length, Array) :-
 1738    jni_func(176, Length, Array).
 jNewCharArray(+Length:int, -Array:jref)
 1743jNewCharArray(Length, Array) :-
 1744    jni_func(177, Length, Array).
 jNewDoubleArray(+Length:int, -Array:jref)
 1749jNewDoubleArray(Length, Array) :-
 1750    jni_func(182, Length, Array).
 jNewFloatArray(+Length:int, -Array:jref)
 1755jNewFloatArray(Length, Array) :-
 1756    jni_func(181, Length, Array).
 jNewIntArray(+Length:int, -Array:jref)
 1761jNewIntArray(Length, Array) :-
 1762    jni_func(179, Length, Array).
 jNewLongArray(+Length:int, -Array:jref)
 1767jNewLongArray(Length, Array) :-
 1768    jni_func(180, Length, Array).
 jNewObject(+Class:jref, +MethodID:methodId, +Types:list(type), +Params:list(datum), -Obj:jref)
 1773jNewObject(Class, MethodID, Types, Params, Obj) :-
 1774    jni_params_put(Params, Types, ParamBuf),
 1775    jni_func(30, Class, MethodID, ParamBuf, Obj).
 jNewObjectArray(+Len:int, +Class:jref, +InitVal:jref, -Array:jref)
 1780jNewObjectArray(Len, Class, InitVal, Array) :-
 1781    jni_func(172, Len, Class, InitVal, Array).
 jNewShortArray(+Length:int, -Array:jref)
 1786jNewShortArray(Length, Array) :-
 1787    jni_func(178, Length, Array).
 jSetBooleanArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:boolean_buf)
 1792jSetBooleanArrayRegion(Array, Start, Len, Buf) :-
 1793    jni_void(207, Array, Start, Len, Buf).
 jSetBooleanField(+Obj:jref, +FieldID:fieldId, +Rbool:boolean)
 1798jSetBooleanField(Obj, FieldID, Rbool) :-
 1799    jni_void(105, Obj, FieldID, Rbool).
 jSetByteArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:byte_buf)
 1804jSetByteArrayRegion(Array, Start, Len, Buf) :-
 1805    jni_void(208, Array, Start, Len, Buf).
 jSetByteField(+Obj:jref, +FieldID:fieldId, +Rbyte:byte)
 1810jSetByteField(Obj, FieldID, Rbyte) :-
 1811    jni_void(106, Obj, FieldID, Rbyte).
 jSetCharArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:char_buf)
 1816jSetCharArrayRegion(Array, Start, Len, Buf) :-
 1817    jni_void(209, Array, Start, Len, Buf).
 jSetCharField(+Obj:jref, +FieldID:fieldId, +Rchar:char)
 1822jSetCharField(Obj, FieldID, Rchar) :-
 1823    jni_void(107, Obj, FieldID, Rchar).
 jSetDoubleArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:double_buf)
 1828jSetDoubleArrayRegion(Array, Start, Len, Buf) :-
 1829    jni_void(214, Array, Start, Len, Buf).
 jSetDoubleField(+Obj:jref, +FieldID:fieldId, +Rdouble:double)
 1834jSetDoubleField(Obj, FieldID, Rdouble) :-
 1835    jni_void(112, Obj, FieldID, Rdouble).
 jSetFloatArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:float_buf)
 1840jSetFloatArrayRegion(Array, Start, Len, Buf) :-
 1841    jni_void(213, Array, Start, Len, Buf).
 jSetFloatField(+Obj:jref, +FieldID:fieldId, +Rfloat:float)
 1846jSetFloatField(Obj, FieldID, Rfloat) :-
 1847    jni_void(111, Obj, FieldID, Rfloat).
 jSetIntArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:int_buf)
 1852jSetIntArrayRegion(Array, Start, Len, Buf) :-
 1853    jni_void(211, Array, Start, Len, Buf).
 jSetIntField(+Obj:jref, +FieldID:fieldId, +Rint:int)
 1858jSetIntField(Obj, FieldID, Rint) :-
 1859    jni_void(109, Obj, FieldID, Rint).
 jSetLongArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:long_buf)
 1864jSetLongArrayRegion(Array, Start, Len, Buf) :-
 1865    jni_void(212, Array, Start, Len, Buf).
 jSetLongField(+Obj:jref, +FieldID:fieldId, +Rlong:long)
 1870jSetLongField(Obj, FieldID, Rlong) :-
 1871    jni_void(110, Obj, FieldID, Rlong).
 jSetObjectArrayElement(+Array:jref, +Index:int, +Obj:jref)
 1876jSetObjectArrayElement(Array, Index, Obj) :-
 1877    jni_void(174, Array, Index, Obj).
 jSetObjectField(+Obj:jref, +FieldID:fieldId, +RObj:jref)
 1882jSetObjectField(Obj, FieldID, Robj) :-
 1883    jni_void(104, Obj, FieldID, Robj).
 jSetShortArrayRegion(+Array:jref, +Start:int, +Len:int, +Buf:short_buf)
 1888jSetShortArrayRegion(Array, Start, Len, Buf) :-
 1889    jni_void(210, Array, Start, Len, Buf).
 jSetShortField(+Obj:jref, +FieldID:fieldId, +Rshort:short)
 1894jSetShortField(Obj, FieldID, Rshort) :-
 1895    jni_void(108, Obj, FieldID, Rshort).
 jSetStaticBooleanField(+Class:jref, +FieldID:fieldId, +Rbool:boolean)
 1900jSetStaticBooleanField(Class, FieldID, Rbool) :-
 1901    jni_void(155, Class, FieldID, Rbool).
 jSetStaticByteField(+Class:jref, +FieldID:fieldId, +Rbyte:byte)
 1906jSetStaticByteField(Class, FieldID, Rbyte) :-
 1907    jni_void(156, Class, FieldID, Rbyte).
 jSetStaticCharField(+Class:jref, +FieldID:fieldId, +Rchar:char)
 1912jSetStaticCharField(Class, FieldID, Rchar) :-
 1913    jni_void(157, Class, FieldID, Rchar).
 jSetStaticDoubleField(+Class:jref, +FieldID:fieldId, +Rdouble:double)
 1918jSetStaticDoubleField(Class, FieldID, Rdouble) :-
 1919    jni_void(162, Class, FieldID, Rdouble).
 jSetStaticFloatField(+Class:jref, +FieldID:fieldId, +Rfloat:float)
 1924jSetStaticFloatField(Class, FieldID, Rfloat) :-
 1925    jni_void(161, Class, FieldID, Rfloat).
 jSetStaticIntField(+Class:jref, +FieldID:fieldId, +Rint:int)
 1930jSetStaticIntField(Class, FieldID, Rint) :-
 1931    jni_void(159, Class, FieldID, Rint).
 jSetStaticLongField(+Class:jref, +FieldID:fieldId, +Rlong)
 1936jSetStaticLongField(Class, FieldID, Rlong) :-
 1937    jni_void(160, Class, FieldID, Rlong).
 jSetStaticObjectField(+Class:jref, +FieldID:fieldId, +Robj:jref)
 1942jSetStaticObjectField(Class, FieldID, Robj) :-
 1943    jni_void(154, Class, FieldID, Robj).
 jSetStaticShortField(+Class:jref, +FieldID:fieldId, +Rshort:short)
 1948jSetStaticShortField(Class, FieldID, Rshort) :-
 1949    jni_void(158, Class, FieldID, Rshort).
 jni_params_put(+Params:list(datum), +Types:list(type), -ParamBuf:paramBuf)
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).
 1959jni_params_put(As, Ts, ParamBuf)     :-
 1960    jni_ensure_jvm,                     % in case e.g. NewStringUTF() is called
 1961    length(As, N),
 1962    jni_type_to_xput_code(jvalue, Xc), % Xc will be 15
 1963    jni_alloc_buffer(Xc, N, ParamBuf),
 1964    jni_params_put_1(As, 0, Ts, ParamBuf).
 jni_params_put_1(+Params:list(datum), +N:integer, +JPLTypes:list(type), +ParamBuf:paramBuf)
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

 1983jni_params_put_1([], _, [], _).
 1984jni_params_put_1([A|As], N, [Tjni|Ts], ParamBuf) :-     % type checking?
 1985    (   jni_type_to_xput_code(Tjni, Xc)
 1986    ->  (   A = {Term}                                  % a quoted general term?
 1987        ->  jni_term_to_jref(Term, Ax)                  % convert it to a @(Tag) ref to a new Term instance
 1988        ;   A = Ax
 1989        ),
 1990        jni_param_put(N, Xc, Ax, ParamBuf)              % foreign
 1991    ;   fail                                            % oughta raise an exception?
 1992    ),
 1993    N2 is N+1,
 1994    jni_params_put_1(As, N2, Ts, ParamBuf).             % stash remaining params (if any)
 jni_type_to_xput_code(+JspType, -JniXputCode)
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)

 2004jni_type_to_xput_code(boolean,      1).     % JNI_XPUT_BOOLEAN
 2005jni_type_to_xput_code(byte,         2).     % JNI_XPUT_BYTE
 2006jni_type_to_xput_code(char,         3).     % JNI_XPUT_CHAR
 2007jni_type_to_xput_code(short,        4).     % JNI_XPUT_SHORT
 2008jni_type_to_xput_code(int,          5).     % JNI_XPUT_INT
 2009jni_type_to_xput_code(long,         6).     % JNI_XPUT_LONG
 2010jni_type_to_xput_code(float,        7).     % JNI_XPUT_FLOAT
 2011jni_type_to_xput_code(double,       8).     % JNI_XPUT_DOUBLE
 2012jni_type_to_xput_code(class(_,_),   12).    % JNI_XPUT_REF
 2013jni_type_to_xput_code(array(_),     12).    % JNI_XPUT_REF
 2014jni_type_to_xput_code(jvalue,       15).    % JNI_XPUT_JVALUE
 jpl_class_to_constructor_array(+Class:jref, -MethodArray:jref)
NB might this be done more efficiently in foreign code? or in Java?
 2021jpl_class_to_constructor_array(Cx, Ma) :-
 2022    jpl_entityname_to_class('java.lang.Class', CC),      % cacheable?
 2023    jGetMethodID( CC, getConstructors, method([],array(class([java,lang,reflect],['Constructor']))), MID), % cacheable?
 2024    jCallObjectMethod(Cx, MID, [], [], Ma).
 jpl_class_to_constructors(+Class:jref, -Methods:list(jref))
 2029jpl_class_to_constructors(Cx, Ms) :-
 2030    jpl_class_to_constructor_array(Cx, Ma),
 2031    jpl_object_array_to_list(Ma, Ms).
 jpl_class_to_field_array(+Class:jref, -FieldArray:jref)
 2036jpl_class_to_field_array(Cx, Fa) :-
 2037    jpl_entityname_to_class('java.lang.Class', CC),      % cacheable?
 2038    jGetMethodID(CC, getFields, method([],array(class([java,lang,reflect],['Field']))), MID),  % cacheable?
 2039    jCallObjectMethod(Cx, MID, [], [], Fa).
 jpl_class_to_fields(+Class:jref, -Fields:list(jref))
NB do this in Java (ditto for methods)?
 2046jpl_class_to_fields(C, Fs) :-
 2047    jpl_class_to_field_array(C, Fa),
 2048    jpl_object_array_to_list(Fa, Fs).
 jpl_class_to_method_array(+Class:jref, -MethodArray:jref)
NB migrate into foreign code for efficiency?
 2055jpl_class_to_method_array(Cx, Ma) :-
 2056    jpl_entityname_to_class('java.lang.Class', CC),      % cacheable?
 2057    jGetMethodID(CC, getMethods, method([],array(class([java,lang,reflect],['Method']))), MID),  % cacheable?
 2058    jCallObjectMethod(Cx, MID, [], [], Ma).
 jpl_class_to_methods(+Class:jref, -Methods:list(jref))
NB also used for constructors.

NB do this in Java (ditto for fields)?

 2067jpl_class_to_methods(Cx, Ms) :-
 2068    jpl_class_to_method_array(Cx, Ma),
 2069    jpl_object_array_to_list(Ma, Ms).
 jpl_constructor_to_modifiers(+Method, -Modifiers)
NB migrate into foreign code for efficiency?
 2076jpl_constructor_to_modifiers(X, Ms) :-
 2077    jpl_entityname_to_class('java.lang.reflect.Constructor', Cx),   % cached?
 2078    jpl_method_to_modifiers_1(X, Cx, Ms).
 jpl_constructor_to_name(+Method:jref, -Name:atom)
It is a JNI convention that each constructor behaves (at least, for reflection), as a method whose name is '<init>'.
 2086jpl_constructor_to_name(_X, '<init>').
 jpl_constructor_to_parameter_types(+Method:jref, -ParameterTypes:list(type))
NB migrate to foreign code for efficiency?
 2093jpl_constructor_to_parameter_types(X, Tfps) :-
 2094    jpl_entityname_to_class('java.lang.reflect.Constructor', Cx),   % cached?
 2095    jpl_method_to_parameter_types_1(X, Cx, Tfps).
 jpl_constructor_to_return_type(+Method:jref, -Type:type)
It is a JNI convention that, for the purposes of retrieving a MethodID, a constructor has a return type of 'void'.
 2103jpl_constructor_to_return_type(_X, void).
 jpl_field_spec(+Type:type, -Index:integer, -Name:atom, -Modifiers, -MID:mId, -FieldType:type)
I'm unsure whether arrays have fields, but if they do, this will handle them correctly.
 2110jpl_field_spec(T, I, N, Mods, MID, Tf) :-
 2111    (   jpl_field_spec_is_cached(T)
 2112    ->  jpl_field_spec_cache(T, I, N, Mods, MID, Tf)
 2113    ;   jpl_type_to_class(T, C),
 2114        jpl_class_to_fields(C, Fs),
 2115        (   T = array(_BaseType)    % regardless of base type...
 2116        ->  Tci = array(_)          % ...the "cache index" type is this
 2117        ;   Tci = T
 2118        ),
 2119        jpl_field_spec_1(C, Tci, Fs),
 2120        jpl_assert(jpl_field_spec_is_cached(Tci)),
 2121        jpl_field_spec_cache(Tci, I, N, Mods, MID, Tf)
 2122    ).
 2123
 2124
 2125jpl_field_spec_1(C, Tci, Fs) :-
 2126    (   nth1(I, Fs, F),
 2127        jpl_field_to_name(F, N),
 2128        jpl_field_to_modifiers(F, Mods),
 2129        jpl_field_to_type(F, Tf),
 2130        (   member(static, Mods)
 2131        ->  jGetStaticFieldID(C, N, Tf, MID)
 2132        ;   jGetFieldID(C, N, Tf, MID)
 2133        ),
 2134        jpl_assert(jpl_field_spec_cache(Tci,I,N,Mods,MID,Tf)),
 2135        fail
 2136    ;   true
 2137    ).
 jpl_field_to_modifiers(+Field:jref, -Modifiers:ordset(modifier))
 2143jpl_field_to_modifiers(F, Ms) :-
 2144    jpl_entityname_to_class('java.lang.reflect.Field', Cf),
 2145    jpl_method_to_modifiers_1(F, Cf, Ms).
 jpl_field_to_name(+Field:jref, -Name:atom)
 2150jpl_field_to_name(F, N) :-
 2151    jpl_entityname_to_class('java.lang.reflect.Field', Cf),
 2152    jpl_member_to_name_1(F, Cf, N).
 jpl_field_to_type(+Field:jref, -Type:type)
 2157jpl_field_to_type(F, Tf) :-
 2158    jpl_entityname_to_class('java.lang.reflect.Field', Cf),
 2159    jGetMethodID(Cf, getType, method([],class([java,lang],['Class'])), MID),
 2160    jCallObjectMethod(F, MID, [], [], Cr),
 2161    jpl_class_to_type(Cr, Tf).
 jpl_method_spec(+Type:type, -Index:integer, -Name:atom, -Arity:integer, -Modifiers:ordset(modifier), -MID:methodId, -ReturnType:type, -ParameterTypes:list(type))
Generates pertinent details of all accessible methods of Type (class/2 or array/1), populating or using the cache as appropriate.
 2169jpl_method_spec(T, I, N, A, Mods, MID, Tr, Tfps) :-
 2170    (   jpl_method_spec_is_cached(T)
 2171    ->  jpl_method_spec_cache(T, I, N, A, Mods, MID, Tr, Tfps)
 2172    ;   jpl_type_to_class(T, C),
 2173        jpl_class_to_constructors(C, Xs),
 2174        jpl_class_to_methods(C, Ms),
 2175        (   T = array(_BaseType)    % regardless of base type...
 2176        ->  Tci = array(_)          % ...the "cache index" type is this
 2177        ;   Tci = T
 2178        ),
 2179        jpl_method_spec_1(C, Tci, Xs, Ms),
 2180        jpl_assert(jpl_method_spec_is_cached(Tci)),
 2181        jpl_method_spec_cache(Tci, I, N, A, Mods, MID, Tr, Tfps)
 2182    ).
 jpl_method_spec_1(+Class:jref, +CacheIndexType:partialType, +Constructors:list(method), +Methods:list(method))
If the original type is e.g. array(byte) then CacheIndexType is array(_) else it is that type.
 2189jpl_method_spec_1(C, Tci, Xs, Ms) :-
 2190    (   (   nth1(I, Xs, X),     % generate constructors, numbered from 1
 2191            jpl_constructor_to_name(X, N),
 2192            jpl_constructor_to_modifiers(X, Mods),
 2193            jpl_constructor_to_return_type(X, Tr),
 2194            jpl_constructor_to_parameter_types(X, Tfps)
 2195        ;   length(Xs, J0),
 2196            nth1(J, Ms, M),     % generate members, continuing numbering
 2197            I is J0+J,
 2198            jpl_method_to_name(M, N),
 2199            jpl_method_to_modifiers(M, Mods),
 2200            jpl_method_to_return_type(M, Tr),
 2201            jpl_method_to_parameter_types(M, Tfps)
 2202        ),
 2203        length(Tfps, A), % arity
 2204        (   member(static, Mods)
 2205        ->  jGetStaticMethodID(C, N, method(Tfps,Tr), MID)
 2206        ;   jGetMethodID(C, N, method(Tfps,Tr), MID)
 2207        ),
 2208        jpl_assert(jpl_method_spec_cache(Tci,I,N,A,Mods,MID,Tr,Tfps)),
 2209        fail
 2210    ;   true
 2211    ).
 jpl_method_to_modifiers(+Method:jref, -ModifierSet:ordset(modifier))
 2217jpl_method_to_modifiers(M, Ms) :-
 2218    jpl_entityname_to_class('java.lang.reflect.Method', Cm),
 2219    jpl_method_to_modifiers_1(M, Cm, Ms).
 jpl_method_to_modifiers_1(+Method:jref, +ConstructorClass:jref, -ModifierSet:ordset(modifier))
 2224jpl_method_to_modifiers_1(XM, Cxm, Ms) :-
 2225    jGetMethodID(Cxm, getModifiers, method([],int), MID),
 2226    jCallIntMethod(XM, MID, [], [], I),
 2227    jpl_modifier_int_to_modifiers(I, Ms).
 jpl_method_to_name(+Method:jref, -Name:atom)
 2232jpl_method_to_name(M, N) :-
 2233    jpl_entityname_to_class('java.lang.reflect.Method', CM),
 2234    jpl_member_to_name_1(M, CM, N).
 jpl_member_to_name_1(+Member:jref, +CM:jref, -Name:atom)
 2239jpl_member_to_name_1(M, CM, N) :-
 2240    jGetMethodID(CM, getName, method([],class([java,lang],['String'])), MID),
 2241    jCallObjectMethod(M, MID, [], [], N).
 jpl_method_to_parameter_types(+Method:jref, -Types:list(type))
 2246jpl_method_to_parameter_types(M, Tfps) :-
 2247    jpl_entityname_to_class('java.lang.reflect.Method', Cm),
 2248    jpl_method_to_parameter_types_1(M, Cm, Tfps).
 jpl_method_to_parameter_types_1(+XM:jref, +Cxm:jref, -Tfps:list(type))
XM is (a JPL ref to) an instance of java.lang.reflect.[Constructor|Method]
 2255jpl_method_to_parameter_types_1(XM, Cxm, Tfps) :-
 2256    jGetMethodID(Cxm, getParameterTypes, method([],array(class([java,lang],['Class']))), MID),
 2257    jCallObjectMethod(XM, MID, [], [], Atp),
 2258    jpl_object_array_to_list(Atp, Ctps),
 2259    jpl_classes_to_types(Ctps, Tfps).
 jpl_method_to_return_type(+Method:jref, -Type:type)
 2264jpl_method_to_return_type(M, Tr) :-
 2265    jpl_entityname_to_class('java.lang.reflect.Method', Cm),
 2266    jGetMethodID(Cm, getReturnType, method([],class([java,lang],['Class'])), MID),
 2267    jCallObjectMethod(M, MID, [], [], Cr),
 2268    jpl_class_to_type(Cr, Tr).
 2269
 2270
 2271jpl_modifier_bit(public,        0x001).
 2272jpl_modifier_bit(private,       0x002).
 2273jpl_modifier_bit(protected,     0x004).
 2274jpl_modifier_bit(static,        0x008).
 2275jpl_modifier_bit(final,         0x010).
 2276jpl_modifier_bit(synchronized,  0x020).
 2277jpl_modifier_bit(volatile,      0x040).
 2278jpl_modifier_bit(transient,     0x080).
 2279jpl_modifier_bit(native,        0x100).
 2280jpl_modifier_bit(interface,     0x200).
 2281jpl_modifier_bit(abstract,      0x400).
 jpl_modifier_int_to_modifiers(+Int:integer, -ModifierSet:ordset(modifier))
ModifierSet is an ordered (hence canonical) list, possibly empty (although I suspect never in practice?), of modifier atoms, e.g. [public,static]
 2290jpl_modifier_int_to_modifiers(I, Ms) :-
 2291    setof(
 2292        M,                                  %  should use e.g. set_of_all/3
 2293        B^( jpl_modifier_bit(M, B),
 2294            (B /\ I) =\= 0
 2295        ),
 2296        Ms
 2297    ).
 jpl_cache_type_of_ref(+Type:type, +Ref:jref)
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

 2311jpl_cache_type_of_ref(T, Ref) :-
 2312    (   jpl_assert_policy(jpl_iref_type_cache(_,_), no)
 2313    ->  true
 2314    ;   \+ ground(T)                            % shouldn't happen (implementation error)
 2315    ->  write('[jpl_cache_type_of_ref/2: arg 1 is not ground]'), nl,    % oughta throw an exception
 2316        fail
 2317    ;   Ref == @(null)                          % a null ref? (this is valid)
 2318    ->  true                                    % silently ignore it
 2319    ;   (   jpl_iref_type_cache(Ref, TC)        % we expect TC == T
 2320        ->  (   T == TC
 2321            ->  true
 2322            ; % write('[JPL: found obsolete tag-type lemma...]'), nl,   % or keep statistics? (why?)
 2323                retractall(jpl_iref_type_cache(Ref,_)),
 2324                jpl_assert(jpl_iref_type_cache(Ref,T))
 2325            )
 2326        ;   jpl_assert(jpl_iref_type_cache(Ref,T))
 2327        )
 2328    ).
 jpl_class_to_ancestor_classes(+Class:jref, -AncestorClasses:list(jref))
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)
 2339jpl_class_to_ancestor_classes(C, Cas) :-
 2340    (   jpl_class_to_super_class(C, Ca)
 2341    ->  Cas = [Ca|Cas2],
 2342        jpl_class_to_ancestor_classes(Ca, Cas2)
 2343    ;   Cas = []
 2344    ).
 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)

 2363jpl_class_to_classname(C, CN) :-
 2364    jpl_call(C, getName, [], CN).
 jpl_class_to_entityname(+Class:jref, -EntityName:atom)
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()
 2376jpl_class_to_entityname(Class, EntityName) :-
 2377    jpl_entityname_to_class('java.lang.Class', CC),      % cached?
 2378    jGetMethodID(CC, getName, method([],class([java,lang],['String'])), MIDgetName), % does this ever change?
 2379    jCallObjectMethod(Class, MIDgetName, [], [], S),
 2380    S = EntityName.
 2381
 2382
 2383jpl_class_to_super_class(C, Cx) :-
 2384    jGetSuperclass(C, Cx),
 2385    Cx \== @(null),         % as returned when C is java.lang.Object, i.e. no superclass
 2386    jpl_cache_type_of_ref(class([java,lang],['Class']), Cx).
 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' (?!)

 2400jpl_class_to_type(Class, Type) :-
 2401    assertion(blob(Class,jref)),               % "Class" cannot be uninstantiated and must be blob jref
 2402    (   jpl_class_tag_type_cache(Class, Tx)    % found in cache!
 2403    ->  true
 2404    ;   jpl_class_to_entityname(Class, EN),   % uncached ??
 2405        jpl_entityname_to_type(EN, Tr),
 2406        jpl_type_to_canonical_type(Tr, Tx),             % map e.g. class([],[byte]) -> byte (TODO: Looks like a dirty fix; I would say this is not needed now)
 2407        jpl_assert(jpl_class_tag_type_cache(Class,Tx))
 2408    ->  true    % the elseif goal should be determinate, but just in case... TODO: Replace by a once
 2409    ),
 2410    Type = Tx.
 2411
 2412
 2413jpl_classes_to_types([], []).
 2414jpl_classes_to_types([C|Cs], [T|Ts]) :-
 2415    jpl_class_to_type(C, T),
 2416    jpl_classes_to_types(Cs, Ts).
 jpl_entityname_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 is already encountered.

 2427jpl_entityname_to_class(EntityName, Class) :-
 2428    jpl_entityname_to_type(EntityName, T),    % cached
 2429    jpl_type_to_class(T, Class).               % cached
 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.

 2439jpl_classname_to_class(EntityName, Class) :-
 2440    jpl_entityname_to_class(EntityName, Class). % wrapper for historical usage/export
 2441
 2442% =========================================================
 2443% Java Entity Name (atom) <----> JPL Type (Prolog term)
 2444% =========================================================
 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()
 2479jpl_entityname_to_type(EntityName, Type) :-
 2480    assertion(atomic(EntityName)),
 2481    (jpl_classname_type_cache(EntityName, Tx)
 2482    ->  (Tx = Type)
 2483    ;   jpl_entityname_to_type_with_caching(EntityName, Type)).
 2484
 2485jpl_entityname_to_type_with_caching(EN, T) :-
 2486    (atom_codes(EN,Cs),phrase(jpl_entityname(T), Cs))
 2487    ->  jpl_assert(jpl_classname_type_cache(EN,T)).
 jpl_type_to_entityname(+Type:jpl_type, -EntityName:atom)
This is the converse of jpl_entityname_to_type/2
 2493jpl_type_to_entityname(Type, EntityName) :-
 2494    assertion(ground(Type)),
 2495    phrase(jpl_entityname(Type), Cs),
 2496    atom_codes(EntityName, Cs).
 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.

 2507jpl_classname_to_type(EntityName, Type) :-
 2508   jpl_entityname_to_type(EntityName, Type).
 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.

 2519% N.B. This predicate is exported, but internally it is only used to generate
 2520% exception information.
 2521
 2522jpl_type_to_classname(Type, EntityName) :-
 2523    jpl_type_to_entityname(Type, EntityName).
 2524
 2525% =========================================================
 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
 2540jpl_datum_to_type(D, T) :-
 2541    (   jpl_value_to_type(D, T)
 2542    ->  true
 2543    ;   jpl_ref_to_type(D, T)
 2544    ->  true
 2545    ;   nonvar(D),
 2546        D = {Term}
 2547    ->  (   cyclic_term(Term)
 2548        ->  throwme(jpl_datum_to_type,is_cyclic(Term))
 2549        ;   atom(Term)
 2550        ->  T = class([org,jpl7],['Atom'])
 2551        ;   integer(Term)
 2552        ->  T = class([org,jpl7],['Integer'])
 2553        ;   float(Term)
 2554        ->  T = class([org,jpl7],['Float'])
 2555        ;   var(Term)
 2556        ->  T = class([org,jpl7],['Variable'])
 2557        ;   T = class([org,jpl7],['Compound'])
 2558        )
 2559    ).
 2560
 2561
 2562jpl_datums_to_most_specific_common_ancestor_type([D], T) :-
 2563    jpl_datum_to_type(D, T).
 2564jpl_datums_to_most_specific_common_ancestor_type([D1,D2|Ds], T0) :-
 2565    jpl_datum_to_type(D1, T1),
 2566    jpl_type_to_ancestor_types(T1, Ts1),
 2567    jpl_datums_to_most_specific_common_ancestor_type_1([D2|Ds], [T1|Ts1], [T0|_]).
 2568
 2569
 2570jpl_datums_to_most_specific_common_ancestor_type_1([], Ts, Ts).
 2571jpl_datums_to_most_specific_common_ancestor_type_1([D|Ds], Ts1, Ts0) :-
 2572    jpl_datum_to_type(D, Tx),
 2573    jpl_lineage_types_type_to_common_lineage_types(Ts1, Tx, Ts2),
 2574    jpl_datums_to_most_specific_common_ancestor_type_1(Ds, Ts2, Ts0).
 jpl_datums_to_types(+Datums:list(datum), -Types:list(type))
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).
 2585jpl_datums_to_types([], []).
 2586jpl_datums_to_types([D|Ds], [T|Ts]) :-
 2587    jpl_datum_to_type(D, T),
 2588    jpl_datums_to_types(Ds, Ts).
 jpl_ground_is_type(+X:jpl_type)
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.

 2598jpl_ground_is_type(X) :-
 2599    jpl_primitive_type(X),
 2600    !.
 2601jpl_ground_is_type(array(X)) :-
 2602    jpl_ground_is_type(X).
 2603jpl_ground_is_type(class(_,_)).  % Should one check that the anonymous params are list of atoms, with the second list nonempty?
 2604jpl_ground_is_type(method(_,_)). % Additional checks possible
 2605
 2606
 2607
 2608
 2609jpl_lineage_types_type_to_common_lineage_types(Ts, Tx, Ts0) :-
 2610    (   append(_, [Tx|Ts2], Ts)
 2611    ->  [Tx|Ts2] = Ts0
 2612    ;   jpl_type_to_super_type(Tx, Tx2)
 2613    ->  jpl_lineage_types_type_to_common_lineage_types(Ts, Tx2, Ts0)
 2614    ).
 2615
 2616
 2617jpl_non_var_is_object_type(class(_,_)).
 2618
 2619jpl_non_var_is_object_type(array(_)).
 jpl_object_array_to_list(+Array:jref, -Values:list(datum))
Values is a list of JPL values (primitive values or object references) representing the respective elements of Array.
 2627jpl_object_array_to_list(A, Vs) :-
 2628    jpl_array_to_length(A, N),
 2629    jpl_object_array_to_list_1(A, 0, N, Vs).
 jpl_object_array_to_list_1(+A, +I, +N, -Xs)
 2634jpl_object_array_to_list_1(A, I, N, Xs) :-
 2635    (   I == N
 2636    ->  Xs = []
 2637    ;   jGetObjectArrayElement(A, I, X),
 2638        Xs = [X|Xs2],
 2639        J is I+1,
 2640        jpl_object_array_to_list_1(A, J, N, Xs2)
 2641    ).
 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?

 2653jpl_object_to_class(Obj, C) :-
 2654    jpl_is_object(Obj),
 2655    jGetObjectClass(Obj, C),
 2656    jpl_cache_type_of_ref(class([java,lang],['Class']), C).
 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.

 2666jpl_object_to_type(Ref, Type) :-
 2667    jpl_is_object(Ref),
 2668    (   jpl_iref_type_cache(Ref, T)
 2669    ->  true                                % T is Tag's type
 2670    ;   jpl_object_to_class(Ref, Cobj),     % else get ref to class obj
 2671        jpl_class_to_type(Cobj, T),         % get type of class it denotes
 2672        jpl_assert(jpl_iref_type_cache(Ref,T))
 2673    ),
 2674    Type = T.
 2675
 2676
 2677jpl_object_type_to_super_type(T, Tx) :-
 2678    (   (   T = class(_,_)
 2679        ;   T = array(_)
 2680        )
 2681    ->  jpl_type_to_class(T, C),
 2682        jpl_class_to_super_class(C, Cx),
 2683        Cx \== @(null),
 2684        jpl_class_to_type(Cx, Tx)
 2685    ).
 jpl_primitive_buffer_to_array(+Type, +Xc, +Bp, +I, +Size, -Vcs)
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)

 2696jpl_primitive_buffer_to_array(T, Xc, Bp, I, Size, [Vc|Vcs]) :-
 2697    jni_fetch_buffer_value(Bp, I, Vc, Xc),
 2698    Ix is I+1,
 2699    (   Ix < Size
 2700    ->  jpl_primitive_buffer_to_array(T, Xc, Bp, Ix, Size, Vcs)
 2701    ;   Vcs = []
 2702    ).
 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].
 2715jpl_primitive_type(boolean).
 2716jpl_primitive_type(char).
 2717jpl_primitive_type(byte).
 2718jpl_primitive_type(short).
 2719jpl_primitive_type(int).   % N.B. "int" not "integer"
 2720jpl_primitive_type(long).
 2721jpl_primitive_type(float).
 2722jpl_primitive_type(double).
 jpl_primitive_type_default_value(-Type:type, -Value:datum)
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).
 2731jpl_primitive_type_default_value(boolean, @(false)).
 2732jpl_primitive_type_default_value(char,    0).
 2733jpl_primitive_type_default_value(byte,    0).
 2734jpl_primitive_type_default_value(short,   0).
 2735jpl_primitive_type_default_value(int,     0).
 2736jpl_primitive_type_default_value(long,    0).
 2737jpl_primitive_type_default_value(float,   0.0).
 2738jpl_primitive_type_default_value(double,  0.0).
 2739
 2740
 2741jpl_primitive_type_super_type(T, Tx) :-
 2742    (   jpl_type_fits_type_direct_prim(T, Tx)
 2743    ;   jpl_type_fits_type_direct_xtra(T, Tx)
 2744    ).
 jpl_primitive_type_term_to_value(+Type, +Term, -Val)
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)

 2757jpl_primitive_type_term_to_value(Type, Term, Val) :-
 2758    once(jpl_primitive_type_term_to_value_1(Type, Term, Val)). % make deterministic
 jpl_primitive_type_term_to_value_1(+Type, +RawValue, -WidenedValue)
I'm not worried about structure duplication here.

NB this oughta be done in foreign code.

 2766jpl_primitive_type_term_to_value_1(boolean, @(false), @(false)).
 2767jpl_primitive_type_term_to_value_1(boolean, @(true), @(true)).
 2768jpl_primitive_type_term_to_value_1(char, I, I) :-
 2769    integer(I),
 2770    I >= 0,
 2771    I =< 65535.         %  (2**16)-1.
 2772jpl_primitive_type_term_to_value_1(byte, I, I) :-
 2773    integer(I),
 2774    I >= 128,           % -(2**7)
 2775    I =< 127.           %  (2**7)-1
 2776jpl_primitive_type_term_to_value_1(short, I, I) :-
 2777    integer(I),
 2778    I >= -32768,        % -(2**15)
 2779    I =<  32767.        %  (2**15)-1
 2780jpl_primitive_type_term_to_value_1(int, I, I) :-
 2781    integer(I),
 2782    I >= -2147483648,   % -(2**31)
 2783    I =<  2147483647.   %  (2**31)-1
 2784jpl_primitive_type_term_to_value_1(long, I, I) :-
 2785    integer(I),
 2786    I >= -9223372036854775808,  % -(2**63)
 2787    I =<  9223372036854775807.  %  (2**63)-1
 2788jpl_primitive_type_term_to_value_1(float, V, F) :-
 2789    (   integer(V)
 2790    ->  F is float(V)
 2791    ;   float(V)
 2792    ->  F = V
 2793    ).
 2794jpl_primitive_type_term_to_value_1(double, V, F) :-
 2795    (   integer(V)
 2796    ->  F is float(V)
 2797    ;   float(V)
 2798    ->  F = V
 2799    ).
 2800
 2801
 2802jpl_primitive_type_to_ancestor_types(T, Ts) :-
 2803    (   jpl_primitive_type_super_type(T, Ta)
 2804    ->  Ts = [Ta|Tas],
 2805        jpl_primitive_type_to_ancestor_types(Ta, Tas)
 2806    ;   Ts = []
 2807    ).
 2808
 2809
 2810jpl_primitive_type_to_super_type(T, Tx) :-
 2811    jpl_primitive_type_super_type(T, Tx).
 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.

 2820jpl_ref_to_type(Ref, T) :-
 2821    (   Ref == @(null)
 2822    ->  T = null
 2823    ;   Ref == @(void)
 2824    ->  T = void
 2825    ;   jpl_object_to_type(Ref, T)
 2826    ).
 jpl_tag_to_type(+Tag:tag, -Type:type)
Tag must be an (atomic) object tag.

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

 2836jpl_tag_to_type(Tag, Type) :-
 2837    jni_tag_to_iref(Tag, Iref),
 2838    (   jpl_iref_type_cache(Iref, T)
 2839    ->  true                                % T is Tag's type
 2840    ;   jpl_object_to_class(@(Tag), Cobj), % else get ref to class obj
 2841        jpl_class_to_type(Cobj, T),         % get type of class it denotes
 2842        jpl_assert(jpl_iref_type_cache(Iref,T))
 2843    ),
 2844    Type = T.
 jpl_type_fits_type(+TypeX:type, +TypeY:type) is semidet
TypeX and TypeY must each be proper JPL types.

This succeeds iff TypeX is assignable to TypeY.

 2853jpl_type_fits_type(Tx, Ty) :-
 2854    once(jpl_type_fits_type_1(Tx, Ty)). % make deterministic
 jpl_type_fits_type_1(+T1:type, +T2:type)
NB it doesn't matter that this leaves choicepoints; it serves only jpl_type_fits_type/2
 2861jpl_type_fits_type_1(T, T).
 2862jpl_type_fits_type_1(class(Ps1,Cs1), class(Ps2,Cs2)) :-
 2863    jpl_type_to_class(class(Ps1,Cs1), C1),
 2864    jpl_type_to_class(class(Ps2,Cs2), C2),
 2865    jIsAssignableFrom(C1, C2).
 2866jpl_type_fits_type_1(array(T1), class(Ps2,Cs2)) :-
 2867    jpl_type_to_class(array(T1), C1),
 2868    jpl_type_to_class(class(Ps2,Cs2), C2),
 2869    jIsAssignableFrom(C1, C2).
 2870jpl_type_fits_type_1(array(T1), array(T2)) :-
 2871    jpl_type_to_class(array(T1), C1),
 2872    jpl_type_to_class(array(T2), C2),
 2873    jIsAssignableFrom(C1, C2).
 2874jpl_type_fits_type_1(null, class(_,_)).
 2875jpl_type_fits_type_1(null, array(_)).
 2876jpl_type_fits_type_1(T1, T2) :-
 2877    jpl_type_fits_type_xprim(T1, T2).
 2878
 2879
 2880jpl_type_fits_type_direct_prim(float, double).
 2881jpl_type_fits_type_direct_prim(long,  float).
 2882jpl_type_fits_type_direct_prim(int,   long).
 2883jpl_type_fits_type_direct_prim(char,  int).
 2884jpl_type_fits_type_direct_prim(short, int).
 2885jpl_type_fits_type_direct_prim(byte,  short).
 2886
 2887
 2888jpl_type_fits_type_direct_xprim(Tp, Tq) :-
 2889    jpl_type_fits_type_direct_prim(Tp, Tq).
 2890jpl_type_fits_type_direct_xprim(Tp, Tq) :-
 2891    jpl_type_fits_type_direct_xtra(Tp, Tq).
 jpl_type_fits_type_direct_xtra(-PseudoType:type, -ConcreteType:type)
This defines the direct subtype-supertype relationships which involve the intersection pseudo types char_int, char_short and char_byte
 2899jpl_type_fits_type_direct_xtra(char_int,   int).    % char_int is a direct subtype of int
 2900jpl_type_fits_type_direct_xtra(char_int,   char).   % etc.
 2901jpl_type_fits_type_direct_xtra(char_short, short).
 2902jpl_type_fits_type_direct_xtra(char_short, char).
 2903jpl_type_fits_type_direct_xtra(char_byte,  byte).
 2904jpl_type_fits_type_direct_xtra(char_byte,  char).
 2905jpl_type_fits_type_direct_xtra(overlong,   float).  % 6/Oct/2006 experiment
 jpl_type_fits_type_xprim(-Tp, -T) is nondet
NB serves only jpl_type_fits_type_1/2
 2912jpl_type_fits_type_xprim(Tp, T) :-
 2913    jpl_type_fits_type_direct_xprim(Tp, Tq),
 2914    (   Tq = T
 2915    ;   jpl_type_fits_type_xprim(Tq, T)
 2916    ).
 jpl_type_to_ancestor_types(+T:type, -Tas:list(type))
This does not accommodate the assignability of null, but that's OK (?) since "type assignability" and "type ancestry" are not equivalent.
 2924jpl_type_to_ancestor_types(T, Tas) :-
 2925    (   (   T = class(_,_)
 2926        ;   T = array(_)
 2927        )
 2928    ->  jpl_type_to_class(T, C),
 2929        jpl_class_to_ancestor_classes(C, Cas),
 2930        jpl_classes_to_types(Cas, Tas)
 2931    ;   jpl_primitive_type_to_ancestor_types(T, Tas)
 2932    ->  true
 2933    ).
 jpl_type_to_canonical_type(+Type:type, -CanonicalType:type)
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.
 2948jpl_type_to_canonical_type(array(T), array(Tc)) :-
 2949    !,
 2950    jpl_type_to_canonical_type(T, Tc).
 2951jpl_type_to_canonical_type(class([],[void]), void) :-
 2952    !.
 2953jpl_type_to_canonical_type(class([],[N]), N) :-
 2954    jpl_primitive_type(N),
 2955    !.
 2956jpl_type_to_canonical_type(class(Ps,Cs), class(Ps,Cs)) :-
 2957    !.
 2958jpl_type_to_canonical_type(void, void) :-
 2959    !.
 2960jpl_type_to_canonical_type(P, P) :-
 2961    jpl_primitive_type(P).
 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.

 2972jpl_type_to_class(Type, Class) :-
 2973    (ground(Type)
 2974    -> true
 2975    ; throwme(jpl_type_to_class,arg1_is_var)), % outta here if not ground
 2976    (jpl_class_tag_type_cache(RefB, Type)
 2977    ->  true
 2978    ;   (   jpl_type_to_java_findclass_descriptor(Type, FCN)
 2979        ->  jFindClass(FCN, RefB),       % which caches type of RefB
 2980            jpl_cache_type_of_ref(class([java,lang],['Class']), RefB)    % 9/Nov/2004 bugfix (?)
 2981        ),
 2982        jpl_assert(jpl_class_tag_type_cache(RefB,Type))
 2983    ),
 2984    Class = RefB.
 jpl_type_to_java_field_descriptor(+Type:jpl_type, -Descriptor:atom)
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?)

 2994jpl_type_to_java_field_descriptor(T, FD) :-
 2995    % once(phrase(jpl_field_descriptor(T,slashy), Cs)), % make deterministic
 2996    phrase(jpl_field_descriptor(T,slashy), Cs), % make deterministic
 2997    atom_codes(FD, Cs).
 jpl_type_to_java_method_descriptor(+Type:jpl_type, -Descriptor:atom)
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?)

 3006jpl_type_to_java_method_descriptor(T, MD) :-
 3007    % once(phrase(jpl_method_descriptor(T), Cs)), % make deterministic (should not be needed)
 3008    phrase(jpl_method_descriptor(T), Cs),
 3009    atom_codes(MD, Cs).
 jpl_type_to_java_findclass_descriptor(+Type:jpl_type, -Descriptor:atom)
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.
 3016jpl_type_to_java_findclass_descriptor(T, FCD) :-
 3017    % once(phrase(jpl_findclass_descriptor(T), Cs)), % make deterministic (should not be needed)
 3018    phrase(jpl_findclass_descriptor(T), Cs),
 3019    atom_codes(FCD, Cs).
 jpl_type_to_super_type(+Type:type, -SuperType:type)
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.

 3029jpl_type_to_super_type(T, Tx) :-
 3030    (   jpl_object_type_to_super_type(T, Tx)
 3031    ->  true
 3032    ;   jpl_primitive_type_to_super_type(T, Tx)
 3033    ->  true
 3034    ).
 jpl_type_to_preferred_concrete_type(+Type:type, -ConcreteType:type)
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

 3053jpl_type_to_preferred_concrete_type(T, Tc) :-
 3054    (   jpl_type_to_preferred_concrete_type_1(T, TcX)
 3055    ->  Tc = TcX
 3056    ).
 3057
 3058
 3059jpl_type_to_preferred_concrete_type_1(char_int, int).
 3060jpl_type_to_preferred_concrete_type_1(char_short, short).
 3061jpl_type_to_preferred_concrete_type_1(char_byte, byte).
 3062jpl_type_to_preferred_concrete_type_1(array(T), array(Tc)) :-
 3063    jpl_type_to_preferred_concrete_type_1(T, Tc).
 3064jpl_type_to_preferred_concrete_type_1(T, T).
 jpl_types_fit_type(+Types:list(type), +Type:type)
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.

 3073jpl_types_fit_type([], _).
 3074jpl_types_fit_type([T1|T1s], T2) :-
 3075    jpl_type_fits_type(T1, T2),
 3076    jpl_types_fit_type(T1s, T2).
 jpl_types_fit_types(+Types1:list(type), +Types2:list(type))
Each member type of Types1 "fits" the respective member type of Types2.
 3083jpl_types_fit_types([], []).
 3084jpl_types_fit_types([T1|T1s], [T2|T2s]) :-
 3085    jpl_type_fits_type(T1, T2),
 3086    jpl_types_fit_types(T1s, T2s).
 jpl_value_to_type(+Value:datum, -Type:type)
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.

 3097jpl_value_to_type(V, T) :-
 3098    ground(V),                          % critically assumed by jpl_value_to_type_1/2
 3099    (   jpl_value_to_type_1(V, Tv)      % 2nd arg must be unbound
 3100    ->  T = Tv
 3101    ).
 jpl_value_to_type_1(+Value:datum, -Type:type) is semidet
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.

 3118jpl_value_to_type_1(@(false), boolean) :- !.
 3119jpl_value_to_type_1(@(true), boolean) :- !.
 3120jpl_value_to_type_1(A, class([java,lang],['String'])) :-   % yes it's a "value"
 3121    atom(A),
 3122    !.
 3123jpl_value_to_type_1(I, T) :-
 3124    integer(I),
 3125    !,
 3126    (   I >= 0
 3127    ->  (   I  < 128                 ->  T = char_byte
 3128        ;   I  < 32768               ->  T = char_short
 3129        ;   I  < 65536               ->  T = char_int
 3130        ;   I  < 2147483648          ->  T = int
 3131        ;   I =< 9223372036854775807 ->  T = long
 3132        ;   T = overlong
 3133        )
 3134    ;   I >= -128                 ->  T = byte
 3135    ;   I >= -32768               ->  T = short
 3136    ;   I >= -2147483648          ->  T = int
 3137    ;   I >= -9223372036854775808 ->  T = long
 3138    ;   T = overlong
 3139    ).
 3140jpl_value_to_type_1(F, float) :-
 3141    float(F).
 jpl_is_class(@Term)
True if Term is a JPL reference to an instance of java.lang.Class.
 3148jpl_is_class(X) :-
 3149    jpl_is_object(X),
 3150    jpl_object_to_type(X, class([java,lang],['Class'])).
 jpl_is_false(@Term)
True if Term is @(false), the JPL representation of the Java boolean value 'false'.
 3157jpl_is_false(X) :-
 3158    X == @(false).
 jpl_is_fieldID(-X)
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.

 3171jpl_is_fieldID(jfieldID(X)) :-
 3172    integer(X).
 jpl_is_methodID(-X)
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.

 3185jpl_is_methodID(jmethodID(X)) :-   % NB a var arg may get bound...
 3186    integer(X).
 jpl_is_null(@Term)
True if Term is @(null), the JPL representation of Java's 'null' reference.
 3193jpl_is_null(X) :-
 3194    X == @(null).
 jpl_is_object(@Term)
True if Term is a well-formed JPL object reference.

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

 3203jpl_is_object(X) :-
 3204	blob(X, jref).
 jpl_is_object_type(@Term)
True if Term is an object (class or array) type, not e.g. a primitive, null or void.
 3211jpl_is_object_type(T) :-
 3212    \+ var(T),
 3213    jpl_non_var_is_object_type(T).
 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.
 3222jpl_is_ref(Term) :-
 3223    (	jpl_is_object(Term)
 3224    ->	true
 3225    ;	jpl_is_null(Term)
 3226    ->	true
 3227    ).
 jpl_is_true(@Term)
True if Term is @(true), the JPL representation of the Java boolean value 'true'.
 3235jpl_is_true(X) :-
 3236    X == @(true).
 jpl_is_type(@Term)
True if Term is a well-formed JPL type structure.
 3242jpl_is_type(X) :-
 3243    ground(X),
 3244    jpl_ground_is_type(X).
 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.

 3255jpl_is_void(X) :-
 3256    X == @(void).
 jpl_false(-X:datum) is semidet
X is @(false), the JPL representation of the Java boolean value 'false'.
See also
- jpl_is_false/1
 3265jpl_false(@(false)).
 jpl_null(-X:datum) is semidet
X is @(null), the JPL representation of Java's 'null' reference.
See also
- jpl_is_null/1
 3273jpl_null(@(null)).
 jpl_true(-X:datum) is semidet
X is @(true), the JPL representation of the Java boolean value 'true'.
See also
- jpl_is_true/1
 3282jpl_true(@(true)).
 jpl_void(-X:datum) is semidet
X is @(void), the JPL representation of the pseudo Java value 'void'.
See also
- jpl_is_void/1
 3292jpl_void(@(void)).
 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)
    ).
 3309jpl_array_to_length(A, N) :-
 3310    (   jpl_ref_to_type(A, array(_))    % can this be done cheaper e.g. in foreign code?
 3311    ->  jGetArrayLength(A, N)           % *must* be array, else undefined (crash?)
 3312    ).
 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 = []
    ).
 3334jpl_array_to_list(A, Es) :-
 3335    jpl_array_to_length(A, Len),
 3336    (   Len > 0
 3337    ->  LoBound is 0,
 3338        HiBound is Len-1,
 3339        jpl_get(A, LoBound-HiBound, Es)
 3340    ;   Es = []
 3341    ).
 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

 3356jpl_datums_to_array(Ds, A) :-
 3357    ground(Ds),
 3358    jpl_datums_to_most_specific_common_ancestor_type(Ds, T),    % T may be pseudo e.g. char_byte
 3359    jpl_type_to_preferred_concrete_type(T, Tc),    % bugfix added 16/Apr/2005
 3360    jpl_new(array(Tc), Ds, A).
 jpl_enumeration_element(+Enumeration:jref, -Element:datum)
Generates each Element from Enumeration.
 3371jpl_enumeration_element(En, E) :-
 3372    (   jpl_call(En, hasMoreElements, [], @(true))
 3373    ->  jpl_call(En, nextElement, [], Ex),
 3374        (   E = Ex
 3375        ;   jpl_enumeration_element(En, E)
 3376        )
 3377    ).
 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 = []
    ).
 3398jpl_enumeration_to_list(Enumeration, Es) :-
 3399    (   jpl_call(Enumeration, hasMoreElements, [], @(true))
 3400    ->  jpl_call(Enumeration, nextElement, [], E),
 3401        Es = [E|Es1],
 3402        jpl_enumeration_to_list(Enumeration, Es1)
 3403    ;   Es = []
 3404    ).
 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.

 3416jpl_hashtable_pair(HT, K-V) :-
 3417    jpl_call(HT, keys, [], Ek),
 3418    jpl_enumeration_to_list(Ek, Ks),
 3419    member(K, Ks),
 3420    jpl_call(HT, get, [K], V).
 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)
        )
    ).
 3440jpl_iterator_element(I, E) :-
 3441    (   jpl_call(I, hasNext, [], @(true))
 3442    ->  (   jpl_call(I, next, [], E)
 3443        ;   jpl_iterator_element(I, E)
 3444        )
 3445    ).
 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.

 3458jpl_list_to_array(Ds, A) :-
 3459    jpl_datums_to_array(Ds, A).
 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.

 3469jpl_terms_to_array(Ts, A) :-
 3470    jpl_terms_to_array_1(Ts, Ts2),
 3471    jpl_new(array(class([org,jpl7],['Term'])), Ts2, A).
 3472
 3473
 3474jpl_terms_to_array_1([], []).
 3475jpl_terms_to_array_1([T|Ts], [{T}|Ts2]) :-
 3476    jpl_terms_to_array_1(Ts, Ts2).
 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.
 3485jpl_array_to_terms(JRef, Terms) :-
 3486    jpl_call('org.jpl7.Util', termArrayToList, [JRef], {Terms}).
 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).
 3515jpl_map_element(Map, K-V) :-
 3516    jpl_call(Map, entrySet, [], ES),
 3517    jpl_set_element(ES, E),
 3518    jpl_call(E, getKey, [], K),
 3519    jpl_call(E, getValue, [], V).
 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).
 3536jpl_set_element(S, E) :-
 3537    jpl_call(S, iterator, [], I),
 3538    jpl_iterator_element(I, E).
 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
 3550jpl_servlet_byref(Config, Request, Response) :-
 3551    jpl_call(Config, getServletContext, [], Context),
 3552    jpl_call(Response, setStatus, [200], _),
 3553    jpl_call(Response, setContentType, ['text/html'], _),
 3554    jpl_call(Response, getWriter, [], W),
 3555    jpl_call(W, println, ['<html><head></head><body><h2>jpl_servlet_byref/3 says:</h2><pre>'], _),
 3556    jpl_call(W, println, ['\nservlet context stuff:'], _),
 3557    jpl_call(Context, getInitParameterNames, [], ContextInitParameterNameEnum),
 3558    jpl_enumeration_to_list(ContextInitParameterNameEnum, ContextInitParameterNames),
 3559    length(ContextInitParameterNames, NContextInitParameterNames),
 3560    atomic_list_concat(['\tContext.InitParameters = ',NContextInitParameterNames], NContextInitParameterNamesMsg),
 3561    jpl_call(W, println, [NContextInitParameterNamesMsg], _),
 3562    (   member(ContextInitParameterName, ContextInitParameterNames),
 3563        jpl_call(Context, getInitParameter, [ContextInitParameterName], ContextInitParameter),
 3564        atomic_list_concat(['\t\tContext.InitParameter[',ContextInitParameterName,'] = ',ContextInitParameter], ContextInitParameterMsg),
 3565        jpl_call(W, println, [ContextInitParameterMsg], _),
 3566        fail
 3567    ;   true
 3568    ),
 3569    jpl_call(Context, getMajorVersion, [], MajorVersion),
 3570    atomic_list_concat(['\tContext.MajorVersion = ',MajorVersion], MajorVersionMsg),
 3571    jpl_call(W, println, [MajorVersionMsg], _),
 3572    jpl_call(Context, getMinorVersion, [], MinorVersion),
 3573    atomic_list_concat(['\tContext.MinorVersion = ',MinorVersion], MinorVersionMsg),
 3574    jpl_call(W, println, [MinorVersionMsg], _),
 3575    jpl_call(Context, getServerInfo, [], ServerInfo),
 3576    atomic_list_concat(['\tContext.ServerInfo = ',ServerInfo], ServerInfoMsg),
 3577    jpl_call(W, println, [ServerInfoMsg], _),
 3578    jpl_call(W, println, ['\nservlet config stuff:'], _),
 3579    jpl_call(Config, getServletName, [], ServletName),
 3580    (   ServletName == @(null)
 3581    ->  ServletNameAtom = null
 3582    ;   ServletNameAtom = ServletName
 3583    ),
 3584    atomic_list_concat(['\tConfig.ServletName = ',ServletNameAtom], ServletNameMsg),
 3585    jpl_call(W, println, [ServletNameMsg], _),
 3586    jpl_call(Config, getInitParameterNames, [], ConfigInitParameterNameEnum),
 3587    jpl_enumeration_to_list(ConfigInitParameterNameEnum, ConfigInitParameterNames),
 3588    length(ConfigInitParameterNames, NConfigInitParameterNames),
 3589    atomic_list_concat(['\tConfig.InitParameters = ',NConfigInitParameterNames], NConfigInitParameterNamesMsg),
 3590    jpl_call(W, println, [NConfigInitParameterNamesMsg], _),
 3591    (   member(ConfigInitParameterName, ConfigInitParameterNames),
 3592        jpl_call(Config, getInitParameter, [ConfigInitParameterName], ConfigInitParameter),
 3593        atomic_list_concat(['\t\tConfig.InitParameter[',ConfigInitParameterName,'] = ',ConfigInitParameter], ConfigInitParameterMsg),
 3594        jpl_call(W, println, [ConfigInitParameterMsg], _),
 3595        fail
 3596    ;   true
 3597    ),
 3598    jpl_call(W, println, ['\nrequest stuff:'], _),
 3599    jpl_call(Request, getAttributeNames, [], AttributeNameEnum),
 3600    jpl_enumeration_to_list(AttributeNameEnum, AttributeNames),
 3601    length(AttributeNames, NAttributeNames),
 3602    atomic_list_concat(['\tRequest.Attributes = ',NAttributeNames], NAttributeNamesMsg),
 3603    jpl_call(W, println, [NAttributeNamesMsg], _),
 3604    (   member(AttributeName, AttributeNames),
 3605        jpl_call(Request, getAttribute, [AttributeName], Attribute),
 3606        jpl_call(Attribute, toString, [], AttributeString),
 3607        atomic_list_concat(['\t\tRequest.Attribute[',AttributeName,'] = ',AttributeString], AttributeMsg),
 3608        jpl_call(W, println, [AttributeMsg], _),
 3609        fail
 3610    ;   true
 3611    ),
 3612    jpl_call(Request, getCharacterEncoding, [], CharacterEncoding),
 3613    (   CharacterEncoding == @(null)
 3614    ->  CharacterEncodingAtom = ''
 3615    ;   CharacterEncodingAtom = CharacterEncoding
 3616    ),
 3617    atomic_list_concat(['\tRequest.CharacterEncoding',' = ',CharacterEncodingAtom], CharacterEncodingMsg),
 3618    jpl_call(W, println, [CharacterEncodingMsg], _),
 3619    jpl_call(Request, getContentLength, [], ContentLength),
 3620    atomic_list_concat(['\tRequest.ContentLength',' = ',ContentLength], ContentLengthMsg),
 3621    jpl_call(W, println, [ContentLengthMsg], _),
 3622    jpl_call(Request, getContentType, [], ContentType),
 3623    (   ContentType == @(null)
 3624    ->  ContentTypeAtom = ''
 3625    ;   ContentTypeAtom = ContentType
 3626    ),
 3627    atomic_list_concat(['\tRequest.ContentType',' = ',ContentTypeAtom], ContentTypeMsg),
 3628    jpl_call(W, println, [ContentTypeMsg], _),
 3629    jpl_call(Request, getParameterNames, [], ParameterNameEnum),
 3630    jpl_enumeration_to_list(ParameterNameEnum, ParameterNames),
 3631    length(ParameterNames, NParameterNames),
 3632    atomic_list_concat(['\tRequest.Parameters = ',NParameterNames], NParameterNamesMsg),
 3633    jpl_call(W, println, [NParameterNamesMsg], _),
 3634    (   member(ParameterName, ParameterNames),
 3635        jpl_call(Request, getParameter, [ParameterName], Parameter),
 3636        atomic_list_concat(['\t\tRequest.Parameter[',ParameterName,'] = ',Parameter], ParameterMsg),
 3637        jpl_call(W, println, [ParameterMsg], _),
 3638        fail
 3639    ;   true
 3640    ),
 3641    jpl_call(Request, getProtocol, [], Protocol),
 3642    atomic_list_concat(['\tRequest.Protocol',' = ',Protocol], ProtocolMsg),
 3643    jpl_call(W, println, [ProtocolMsg], _),
 3644    jpl_call(Request, getRemoteAddr, [], RemoteAddr),
 3645    atomic_list_concat(['\tRequest.RemoteAddr',' = ',RemoteAddr], RemoteAddrMsg),
 3646    jpl_call(W, println, [RemoteAddrMsg], _),
 3647    jpl_call(Request, getRemoteHost, [], RemoteHost),
 3648    atomic_list_concat(['\tRequest.RemoteHost',' = ',RemoteHost], RemoteHostMsg),
 3649    jpl_call(W, println, [RemoteHostMsg], _),
 3650    jpl_call(Request, getScheme, [], Scheme),
 3651    atomic_list_concat(['\tRequest.Scheme',' = ',Scheme], SchemeMsg),
 3652    jpl_call(W, println, [SchemeMsg], _),
 3653    jpl_call(Request, getServerName, [], ServerName),
 3654    atomic_list_concat(['\tRequest.ServerName',' = ',ServerName], ServerNameMsg),
 3655    jpl_call(W, println, [ServerNameMsg], _),
 3656    jpl_call(Request, getServerPort, [], ServerPort),
 3657    atomic_list_concat(['\tRequest.ServerPort',' = ',ServerPort], ServerPortMsg),
 3658    jpl_call(W, println, [ServerPortMsg], _),
 3659    jpl_call(Request, isSecure, [], @(Secure)),
 3660    atomic_list_concat(['\tRequest.Secure',' = ',Secure], SecureMsg),
 3661    jpl_call(W, println, [SecureMsg], _),
 3662    jpl_call(W, println, ['\nHTTP request stuff:'], _),
 3663    jpl_call(Request, getAuthType, [], AuthType),
 3664    (   AuthType == @(null)
 3665    ->  AuthTypeAtom = ''
 3666    ;   AuthTypeAtom = AuthType
 3667    ),
 3668    atomic_list_concat(['\tRequest.AuthType',' = ',AuthTypeAtom], AuthTypeMsg),
 3669    jpl_call(W, println, [AuthTypeMsg], _),
 3670    jpl_call(Request, getContextPath, [], ContextPath),
 3671    (   ContextPath == @(null)
 3672    ->  ContextPathAtom = ''
 3673    ;   ContextPathAtom = ContextPath
 3674    ),
 3675    atomic_list_concat(['\tRequest.ContextPath',' = ',ContextPathAtom], ContextPathMsg),
 3676    jpl_call(W, println, [ContextPathMsg], _),
 3677    jpl_call(Request, getCookies, [], CookieArray),
 3678    (   CookieArray == @(null)
 3679    ->  Cookies = []
 3680    ;   jpl_array_to_list(CookieArray, Cookies)
 3681    ),
 3682    length(Cookies, NCookies),
 3683    atomic_list_concat(['\tRequest.Cookies',' = ',NCookies], NCookiesMsg),
 3684    jpl_call(W, println, [NCookiesMsg], _),
 3685    (   nth0(NCookie, Cookies, Cookie),
 3686        atomic_list_concat(['\t\tRequest.Cookie[',NCookie,']'], CookieMsg),
 3687        jpl_call(W, println, [CookieMsg], _),
 3688        jpl_call(Cookie, getName, [], CookieName),
 3689        atomic_list_concat(['\t\t\tRequest.Cookie.Name = ',CookieName], CookieNameMsg),
 3690        jpl_call(W, println, [CookieNameMsg], _),
 3691        jpl_call(Cookie, getValue, [], CookieValue),
 3692        atomic_list_concat(['\t\t\tRequest.Cookie.Value = ',CookieValue], CookieValueMsg),
 3693        jpl_call(W, println, [CookieValueMsg], _),
 3694        jpl_call(Cookie, getPath, [], CookiePath),
 3695        (   CookiePath == @(null)
 3696        ->  CookiePathAtom = ''
 3697        ;   CookiePathAtom = CookiePath
 3698        ),
 3699        atomic_list_concat(['\t\t\tRequest.Cookie.Path = ',CookiePathAtom], CookiePathMsg),
 3700        jpl_call(W, println, [CookiePathMsg], _),
 3701        jpl_call(Cookie, getComment, [], CookieComment),
 3702        (   CookieComment == @(null)
 3703        ->  CookieCommentAtom = ''
 3704        ;   CookieCommentAtom = CookieComment
 3705        ),
 3706        atomic_list_concat(['\t\t\tRequest.Cookie.Comment = ',CookieCommentAtom], CookieCommentMsg),
 3707        jpl_call(W, println, [CookieCommentMsg], _),
 3708        jpl_call(Cookie, getDomain, [], CookieDomain),
 3709        (   CookieDomain == @(null)
 3710        ->  CookieDomainAtom = ''
 3711        ;   CookieDomainAtom = CookieDomain
 3712        ),
 3713        atomic_list_concat(['\t\t\tRequest.Cookie.Domain = ',CookieDomainAtom], CookieDomainMsg),
 3714        jpl_call(W, println, [CookieDomainMsg], _),
 3715        jpl_call(Cookie, getMaxAge, [], CookieMaxAge),
 3716        atomic_list_concat(['\t\t\tRequest.Cookie.MaxAge = ',CookieMaxAge], CookieMaxAgeMsg),
 3717        jpl_call(W, println, [CookieMaxAgeMsg], _),
 3718        jpl_call(Cookie, getVersion, [], CookieVersion),
 3719        atomic_list_concat(['\t\t\tRequest.Cookie.Version = ',CookieVersion], CookieVersionMsg),
 3720        jpl_call(W, println, [CookieVersionMsg], _),
 3721        jpl_call(Cookie, getSecure, [], @(CookieSecure)),
 3722        atomic_list_concat(['\t\t\tRequest.Cookie.Secure',' = ',CookieSecure], CookieSecureMsg),
 3723        jpl_call(W, println, [CookieSecureMsg], _),
 3724        fail
 3725    ;   true
 3726    ),
 3727    jpl_call(W, println, ['</pre></body></html>'], _),
 3728    true.
 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).
 3738jpl_servlet_byval(MM, CT, Ba) :-
 3739    CT = 'text/html',
 3740    multimap_to_atom(MM, MMa),
 3741    atomic_list_concat(['<html><head></head><body>','<h2>jpl_servlet_byval/3 says:</h2><pre>', MMa,'</pre></body></html>'], Ba).
 is_pair(?T:term)
I define a half-decent "pair" as having a ground key (any val).
 3748is_pair(Key-_Val) :-
 3749    ground(Key).
 3750
 3751
 3752is_pairs(List) :-
 3753    is_list(List),
 3754    maplist(is_pair, List).
 3755
 3756
 3757multimap_to_atom(KVs, A) :-
 3758    multimap_to_atom_1(KVs, '', Cz, []),
 3759    flatten(Cz, Cs),
 3760    atomic_list_concat(Cs, A).
 3761
 3762
 3763multimap_to_atom_1([], _, Cs, Cs).
 3764multimap_to_atom_1([K-V|KVs], T, Cs1, Cs0) :-
 3765    Cs1 = [T,K,' = '|Cs2],
 3766    (   is_list(V)
 3767    ->  (   is_pairs(V)
 3768        ->  V = V2
 3769        ;   findall(N-Ve, nth1(N, V, Ve), V2)
 3770        ),
 3771        T2 = ['    ',T],
 3772        Cs2 = ['\n'|Cs2a],
 3773        multimap_to_atom_1(V2, T2, Cs2a, Cs3)
 3774    ;   to_atom(V, AV),
 3775        Cs2 = [AV,'\n'|Cs3]
 3776    ),
 3777    multimap_to_atom_1(KVs, T, Cs3, Cs0).
 to_atom(+Term, -Atom)
Unifies Atom with a printed representation of Term.
To be done
- Sort of quoting requirements and use format(codes(Codes),...)
 3786to_atom(Term, Atom) :-
 3787    (   atom(Term)
 3788    ->  Atom = Term                % avoid superfluous quotes
 3789    ;   term_to_atom(Term, Atom)
 3790    ).
 jpl_pl_syntax(-Syntax:atom)
Unifies Syntax with 'traditional' or 'modern' according to the mode in which SWI Prolog 7.x was started
 3797jpl_pl_syntax(Syntax) :-
 3798	(	[] == '[]'
 3799	->	Syntax = traditional
 3800	;	Syntax = modern
 3801	).
 3802
 3803         /*******************************
 3804         *            MESSAGES          *
 3805         *******************************/
 3806
 3807:- multifile
 3808    prolog:error_message/3. 3809
 3810prolog:error_message(java_exception(Ex)) -->
 3811    (   { jpl_call(Ex, toString, [], Msg)
 3812        }
 3813    ->  [ 'Java exception: ~w'-[Msg] ]
 3814    ;   [ 'Java exception: ~w'-[Ex] ]
 3815    ).
 3816
 3817
 3818         /*******************************
 3819         *             PATHS            *
 3820         *******************************/
 3821
 3822:- multifile user:file_search_path/2. 3823:- dynamic   user:file_search_path/2. 3824
 3825user:file_search_path(jar, swi(lib)).
 3826
 3827classpath(DirOrJar) :-
 3828    getenv('CLASSPATH', ClassPath),
 3829    current_prolog_flag(path_sep, Sep),
 3830    atomic_list_concat(Elems, Sep, ClassPath),
 3831    member(DirOrJar, Elems).
 add_search_path(+Var, +Value) is det
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.
 3840add_search_path(Path, Dir) :-
 3841    (   getenv(Path, Old)
 3842    ->  current_prolog_flag(path_sep, Sep),
 3843        (   atomic_list_concat(Current, Sep, Old),
 3844            memberchk(Dir, Current)
 3845        ->  true            % already present
 3846        ;   atomic_list_concat([Old, Sep, Dir], New),
 3847            (   debugging(jpl(path))
 3848            ->  env_var_separators(A,Z),
 3849                debug(jpl(path), 'Set ~w~w~w to ~p', [A,Path,Z,New])
 3850            ;   true
 3851            ),
 3852            setenv(Path, New)
 3853        )
 3854    ;   setenv(Path, Dir)
 3855    ).
 3856
 3857env_var_separators('%','%') :-
 3858    current_prolog_flag(windows, true),
 3859    !.
 3860env_var_separators($,'').
 3861
 3862
 3863         /*******************************
 3864         *         LOAD THE JVM         *
 3865         *******************************/
 check_java_environment
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.

 3883check_java_environment :-
 3884    current_prolog_flag(apple, true),
 3885    !,
 3886    print_message(error, jpl(run(jpl_config_dylib))).
 3887check_java_environment :-
 3888    check_lib(jvm).
 3889
 3890check_lib(Name) :-
 3891    check_shared_object(Name, File, EnvVar, Absolute),
 3892    (   Absolute == (-)
 3893    ->  env_var_separators(A, Z),
 3894        format(string(Msg), 'Please add directory holding ~w to ~w~w~w',
 3895               [ File, A, EnvVar, Z ]),
 3896        throwme(check_lib,lib_not_found(Name,Msg))
 3897    ;   true
 3898    ).
 check_shared_object(+Lib, -File, -EnvVar, -AbsFile) is semidet
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.
 3907check_shared_object(Name, File, EnvVar, Absolute) :-
 3908    libfile(Name, File),
 3909    library_search_path(Path, EnvVar),
 3910    (   member(Dir, Path),
 3911        atomic_list_concat([Dir, File], /, Absolute),
 3912        exists_file(Absolute)
 3913    ->  true
 3914    ;   Absolute = (-)
 3915    ).
 3916
 3917libfile(Base, File) :-
 3918    current_prolog_flag(unix, true),
 3919    !,
 3920    atom_concat(lib, Base, F0),
 3921    current_prolog_flag(shared_object_extension, Ext),
 3922    file_name_extension(F0, Ext, File).
 3923libfile(Base, File) :-
 3924    current_prolog_flag(windows, true),
 3925    !,
 3926    current_prolog_flag(shared_object_extension, Ext),
 3927    file_name_extension(Base, Ext, File).
 library_search_path(-Dirs:list, -EnvVar) is det
Dirs is the list of directories searched for shared objects/DLLs. EnvVar is the variable in which the search path os stored.
 3935library_search_path(Path, EnvVar) :-
 3936    current_prolog_flag(shared_object_search_path, EnvVar),
 3937    current_prolog_flag(path_sep, Sep),
 3938    (   getenv(EnvVar, Env),
 3939        atomic_list_concat(Path, Sep, Env)
 3940    ->  true
 3941    ;   Path = []
 3942    ).
 add_jpl_to_classpath
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?
 3956add_jpl_to_classpath :-
 3957    classpath(Jar),
 3958    file_base_name(Jar, 'jpl.jar'),
 3959    !.
 3960add_jpl_to_classpath :-
 3961    classpath(Dir),
 3962    (   sub_atom(Dir, _, _, 0, /)
 3963    ->  atom_concat(Dir, 'jpl.jar', File)
 3964    ;   atom_concat(Dir, '/jpl.jar', File)
 3965    ),
 3966    access_file(File, read),
 3967    !.
 3968add_jpl_to_classpath :-
 3969    absolute_file_name(jar('jpl.jar'), JplJAR,
 3970                       [ access(read)
 3971                       ]),
 3972    !,
 3973    (   getenv('CLASSPATH', Old)
 3974    ->  current_prolog_flag(path_sep, Separator),
 3975        atomic_list_concat([JplJAR, Old], Separator, New)
 3976    ;   New = JplJAR
 3977    ),
 3978    setenv('CLASSPATH', New).
 libjpl(-Spec) is det
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.

 3992libjpl(File) :-
 3993    (   current_prolog_flag(unix, true)
 3994    ->  File = foreign(libjpl)
 3995    ;   File = foreign(jpl)                                    % Windows
 3996    ).
 add_jpl_to_ldpath(+JPL) is det
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.
 4005add_jpl_to_ldpath(JPL) :-
 4006    absolute_file_name(JPL, File,
 4007               [ file_type(executable),
 4008                 access(read),
 4009                 file_errors(fail)
 4010               ]),
 4011    !,
 4012    file_directory_name(File, Dir),
 4013    prolog_to_os_filename(Dir, OsDir),
 4014    extend_java_library_path(OsDir),
 4015    current_prolog_flag(shared_object_search_path, PathVar),
 4016    add_search_path(PathVar, OsDir).
 4017add_jpl_to_ldpath(_).
 add_java_to_ldpath is det
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.
 4026:- if(current_prolog_flag(windows,true)). 4027add_java_to_ldpath :-
 4028    current_prolog_flag(windows, true),
 4029    !,
 4030    phrase(java_dirs, Extra),
 4031    (   Extra \== []
 4032    ->  print_message(informational, extend_ld_path(Extra)),
 4033        maplist(extend_dll_search_path, Extra)
 4034    ;   true
 4035    ).
 4036:- endif. 4037add_java_to_ldpath.
 extend_dll_search_path(+Dir)
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.
 4046:- if(current_prolog_flag(windows,true)). 4047:- use_module(library(shlib), [win_add_dll_directory/1]). 4048extend_dll_search_path(Dir) :-
 4049    win_add_dll_directory(Dir),
 4050    (   current_prolog_flag(wine_version, _)
 4051    ->  prolog_to_os_filename(Dir, OSDir),
 4052        (   getenv('PATH', Path0)
 4053        ->  atomic_list_concat([Path0, OSDir], ';', Path),
 4054            setenv('PATH', Path)
 4055        ;   setenv('PATH', OSDir)
 4056        )
 4057    ;   true
 4058    ).
 4059:- endif.
 extend_java_library_path(+OsDir)
Add Dir (in OS notation) to the Java -Djava.library.path init options.
 4066extend_java_library_path(OsDir) :-
 4067    jpl_get_default_jvm_opts(Opts0),
 4068    (   select(PathOpt0, Opts0, Rest),
 4069        sub_atom(PathOpt0, 0, _, _, '-Djava.library.path=')
 4070    ->  current_prolog_flag(path_sep, Separator),
 4071        atomic_list_concat([PathOpt0, Separator, OsDir], PathOpt),
 4072        NewOpts = [PathOpt|Rest]
 4073    ;   atom_concat('-Djava.library.path=', OsDir, PathOpt),
 4074        NewOpts = [PathOpt|Opts0]
 4075    ),
 4076    debug(jpl(path), 'Setting Java options to ~p', [NewOpts]),
 4077    jpl_set_default_jvm_opts(NewOpts).
 java_dirs// is det
DCG that produces existing candidate directories holding Java related DLLs
 4084java_dirs -->
 4085    % JDK directories
 4086    java_dir(jvm, '/jre/bin/client'),
 4087    java_dir(jvm, '/jre/bin/server'),
 4088    java_dir(java, '/jre/bin'),
 4089    % JRE directories
 4090    java_dir(jvm, '/bin/client'),
 4091    java_dir(jvm, '/bin/server'),
 4092    java_dir(java, '/bin').
 4093
 4094java_dir(DLL, _SubPath) -->
 4095    { check_shared_object(DLL, _, _Var, Abs),
 4096      Abs \== (-)
 4097    },
 4098    !.
 4099java_dir(_DLL, SubPath) -->
 4100    { java_home(JavaHome),
 4101      atom_concat(JavaHome, SubPath, SubDir),
 4102      exists_directory(SubDir)
 4103    },
 4104    !,
 4105    [SubDir].
 4106java_dir(_, _) --> [].
 java_home(-Home) is semidet
Find the home location of Java.
Arguments:
Home- JAVA home in OS notation
 4115java_home_win_key(
 4116    jdk,
 4117    'HKEY_LOCAL_MACHINE/Software/JavaSoft/JDK'). % new style
 4118java_home_win_key(
 4119    jdk,
 4120    'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Development Kit').
 4121java_home_win_key(
 4122    jre,
 4123    'HKEY_LOCAL_MACHINE/Software/JavaSoft/JRE').
 4124java_home_win_key(
 4125    jre,
 4126    'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Runtime Environment').
 4127
 4128java_home(Home) :-
 4129    getenv('JAVA_HOME', Home),
 4130    exists_directory(Home),
 4131    !.
 4132:- if(current_prolog_flag(windows, true)). 4133java_home(Home) :-
 4134    java_home_win_key(_, Key0),    % TBD: user can't choose jre or jdk
 4135    catch(win_registry_get_value(Key0, 'CurrentVersion', Version), _, fail),
 4136    atomic_list_concat([Key0, Version], /, Key),
 4137    win_registry_get_value(Key, 'JavaHome', WinHome),
 4138    prolog_to_os_filename(Home, WinHome),
 4139    exists_directory(Home),
 4140    !.
 4141:- else. 4142java_home(Home) :-
 4143    member(Home, [ '/usr/lib/java',
 4144                   '/usr/local/lib/java'
 4145                 ]),
 4146    exists_directory(Home),
 4147    !.
 4148:- endif. 4149
 4150:- dynamic
 4151    jvm_ready/0. 4152:- volatile
 4153    jvm_ready/0. 4154
 4155setup_jvm :-
 4156    jvm_ready,
 4157    !.
 4158setup_jvm :-
 4159    add_jpl_to_classpath,
 4160    add_java_to_ldpath,
 4161    libjpl(JPL),
 4162    catch(load_foreign_library(JPL), E, report_java_setup_problem(E)),
 4163    add_jpl_to_ldpath(JPL),
 4164    assert(jvm_ready).
 4165
 4166report_java_setup_problem(E) :-
 4167    print_message(error, E),
 4168    check_java_environment.
 4169
 4170         /*******************************
 4171         *          MESSAGES            *
 4172         *******************************/
 4173
 4174:- multifile
 4175    prolog:message//1. 4176
 4177prolog:message(extend_ld_path(Dirs)) -->
 4178    [ 'Extended DLL search path with'-[] ],
 4179    dir_per_line(Dirs).
 4180prolog:message(jpl(run(Command))) -->
 4181    [ 'Could not find libjpl.dylib dependencies.'-[],
 4182      'Please run `?- ~p.` to correct this'-[Command]
 4183    ].
 4184
 4185dir_per_line([]) --> [].
 4186dir_per_line([H|T]) -->
 4187    [ nl, '  ~q'-[H] ],
 4188    dir_per_line(T).
 4189
 4190         /****************************************************************************
 4191         * PARSING/GENERATING ENTITY NAME / FINDCLASS DESCRIPTOR / METHOD DESCRIPTOR *
 4192         ****************************************************************************/
 4193
 4194% ===
 4195% PRINCIPLE
 4196%
 4197% We process list of character codes in the DCG (as opposed to lists of
 4198% characters)
 4199%
 4200% In SWI Prolog the character codes are the Unicode code values - the DCGs
 4201% looking at individual characters of a Java identifier expect this.
 4202%
 4203% To generate list of character codes from literals, the backquote notation
 4204% can be used:
 4205%
 4206% ?- X=`alpha`.
 4207% X = [97, 108, 112, 104, 97].
 4208%
 4209% However, Jab Wielmaker says:
 4210%
 4211% "Please use "string" for terminals in DCGs. The SWI-Prolog DCG compiler
 4212%  handles these correctly and this retains compatibility."
 4213%
 4214% So we do that.
 4215% ===
 4216
 4217% jpl_entityname//1
 4218%
 4219% Relate a Java-side "entity name" (a String as returned by Class.getName())
 4220% (in the DCG accumulator as a list of Unicode code values) to JPL's
 4221% Prolog-side "type term".
 4222%
 4223% For example:
 4224%
 4225% ~~~
 4226%       Java-side "entity name"  <----->   JPL Prolog-side "type term"
 4227%         "java.util.Date"                 class([java,util],['Date'])
 4228% ~~~
 4229%
 4230% @see https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Class.html#getName()
 4231%
 4232% Example for getName() calls generating entity names
 4233%
 4234% ~~~
 4235%
 4236% class TJ {
 4237%   public static final void main(String[] argv) {
 4238%
 4239%      System.out.println(void.class.getName());        // void
 4240%      System.out.println(Void.TYPE.getName());         // void
 4241%      System.out.println(Void.class.getName());        // java.lang.Void
 4242%
 4243%      System.out.println(char.class.getName());        // char
 4244%      System.out.println(Character.TYPE.getName());    // char
 4245%      System.out.println(Character.class.getName());   // java.lang.Character
 4246%      System.out.println(Character.valueOf('x').getClass().getName());  // java.lang.Character
 4247%
 4248%      System.out.println(int[].class.getName());                               // [I
 4249%      System.out.println((new int[4]).getClass().getName());                   // [I
 4250%      int[] a = {1,2,3}; System.out.println(a.getClass().getName());           // [I
 4251%
 4252%      System.out.println(int[][].class.getName());                             // [[I
 4253%      System.out.println((new int[4][4]).getClass().getName());                // [[I
 4254%      int[][] aa = {{1},{2},{3}}; System.out.println(aa.getClass().getName()); // [[I
 4255%
 4256%      System.out.println(Integer[][].class.getName());                             // [[Ljava.lang.Integer;
 4257%      System.out.println((new Integer[4][4]).getClass().getName());                // [[Ljava.lang.Integer;
 4258%      Integer[][] bb = {{1},{2},{3}}; System.out.println(bb.getClass().getName()); // [[Ljava.lang.Integer;
 4259%
 4260%   }
 4261% }
 4262% ~~~
 4263%
 4264% Note that We can list the possible "jpl type terms" directly in the head of
 4265% jpl_entityname//1 (except for the primitives). This helps in clause selection
 4266% and documentation. Note that the fact that the last two clauses T are not tagged as
 4267% "primitive()" makes this representation nonuniform; should be fixed at some time.
 4268% ---
 4269
 4270jpl_entityname(class(Ps,Cs)) --> jpl_classname(class(Ps,Cs),dotty),!.
 4271jpl_entityname(array(T))     --> jpl_array_type_descriptor(array(T),dotty),!.
 4272jpl_entityname(void)         --> "void",!.
 4273jpl_entityname(P)            --> jpl_primitive_entityname(P).
 4274
 4275% ---
 4276% The "findclass descriptor" is used for the JNI function FindClass and is
 4277% either an array type descriptor with a "slashy" package name or directly
 4278% a classname, also with a "slasgy" package name
 4279% ---
 4280
 4281jpl_findclass_descriptor(array(T))     --> jpl_array_type_descriptor(array(T),slashy),!.
 4282jpl_findclass_descriptor(class(Ps,Cs)) --> jpl_classname(class(Ps,Cs),slashy).
 4283
 4284% ---
 4285% The "method descriptor" is used to find a method ID based on the method
 4286% signature. It contains method arguments and type of method return value
 4287% ---
 4288
 4289jpl_method_descriptor(method(Ts,T)) --> "(", jpl_method_descriptor_args(Ts), ")", jpl_method_descriptor_retval(T).
 4290
 4291jpl_method_descriptor_args([T|Ts]) --> jpl_field_descriptor(T,slashy), !, jpl_method_descriptor_args(Ts).
 4292jpl_method_descriptor_args([]) --> [].
 4293
 4294jpl_method_descriptor_retval(void) --> "V".
 4295jpl_method_descriptor_retval(T) --> jpl_field_descriptor(T,slashy).
 4296
 4297% ---
 4298% The "binary classname" (i.e. the classname as it appears in binaries) as
 4299% specified in The "Java Language Specification".
 4300% See "Binary Compatibility" - "The Form of a Binary"
 4301% https://docs.oracle.com/javase/specs/jls/se14/html/jls-13.html#jls-13.1
 4302% which points to the "fully qualified name" and "canonical name"
 4303% https://docs.oracle.com/javase/specs/jls/se14/html/jls-6.html#jls-6.7
 4304%
 4305% For JNI, we can switch to "slashy" mode instead of the "dotty" mode, which
 4306% technically makes this NOT the "binary classname", but we keep the predicate name.
 4307% ---
 4308
 4309jpl_classname(class(Ps,Cs),Mode) --> jpl_package_parts(Ps,Mode), jpl_class_parts(Cs).
 4310
 4311% ---
 4312% The qualified name of the package (which may be empty if it is the
 4313% unnamed package). This is a series of Java identifiers separated by dots, but
 4314% in order to reduce codesize, we switch to the "slash" separator depending
 4315% on a second argument, the mode, which is either "dotty" or "slashy".
 4316% "The fully qualified name of a named package that is not a subpackage of a
 4317% named package is its simple name." ... "A simple name is a single identifier."
 4318% https://docs.oracle.com/javase/specs/jls/se14/html/jls-6.html#jls-6.7
 4319% Note that the last '.' is not considered a separator towards the subsequent
 4320% class parts but as a terminator of the package parts sequence (it's a view
 4321% less demanding of backtracking)
 4322% ---
 4323
 4324jpl_package_parts([A|As],dotty)  --> jpl_java_id(A), ".", !, jpl_package_parts(As,dotty).
 4325jpl_package_parts([A|As],slashy) --> jpl_java_id(A), "/", !, jpl_package_parts(As,slashy).
 4326jpl_package_parts([],_)          --> [].
 4327
 4328% ---
 4329% The class parts of a class name (everything beyond the last dot
 4330% of the package prefix, if it exists). This comes from "13.1 - The form of
 4331% a binary", where it is laid out a bit confusingly.
 4332% https://docs.oracle.com/javase/specs/jls/se14/html/jls-13.html#jls-13.1
 4333%
 4334% PROBLEM 2020-08:
 4335%
 4336% Here is an ambiguity that I haven't been able to resolve: '$' is a perfectly
 4337% legitimate character both at the start and in the middle of a classname,
 4338% in fact you can create classes with '$' inside the classname and they compile
 4339% marvelously (try it!). However it is also used as separator for inner class
 4340% names ... but not really! In fact, it is just a concatentation character for
 4341% a _generated class name_ (that makes sense - an inner class is a syntactic
 4342% construct of Java the Language, but of no concern to the JVM, not even for
 4343% access checking because the compiler is supposed to have bleached out any
 4344% problemtic code).
 4345% Parsing such a generated class name can go south in several different ways:
 4346% '$' at the begging, '$' at the end, multiple runs of '$$$' .. one should not
 4347% attempt to do it!
 4348% But the original JPL code does, so we keep this practice for now.
 4349% ---
 4350
 4351jpl_class_parts(Cs) --> { nonvar(Cs), ! },                 % guard
 4352                        { atomic_list_concat(Cs,'$',A) },  % fuse known Cs with '$'
 4353                        jpl_java_type_id(A).               % verify it & insert it into list
 4354
 4355jpl_class_parts(Cs) --> { var(Cs), ! },                % guard
 4356                        jpl_java_type_id(A),           % grab an id including its '$'
 4357                        { messy_dollar_split(A,Cs) }.  % split it along '$'
 4358
 4359
 4360% ---
 4361% "field descriptors" appear in method signatures or inside array type
 4362% descriptors (which are itself field descriptors)
 4363% ---
 4364
 4365jpl_field_descriptor(class(Ps,Cs),Mode)  --> jpl_reference_type_descriptor(class(Ps,Cs),Mode),!.
 4366jpl_field_descriptor(array(T),Mode)      --> jpl_array_type_descriptor(array(T),Mode),!.
 4367jpl_field_descriptor(T,_)                --> jpl_primitive_type_descriptor(T). % sadly untagged with primitive(_) in the head
 4368
 4369jpl_reference_type_descriptor(class(Ps,Cs),Mode) --> "L", jpl_classname(class(Ps,Cs),Mode), ";".
 4370
 4371jpl_array_type_descriptor(array(T),Mode) --> "[", jpl_field_descriptor(T,Mode).
 4372
 4373% ---
 4374% Breaking a bare classname at the '$'
 4375% ---
 4376% Heuristic: Only a '$' flanked to the left by a valid character
 4377% that is a non-dollar and to the right by a valid character that
 4378% may or may not be a dollar gives rise to split.
 4379%
 4380% The INVERSE of messy_dollar_split/2 is atomic_list_concat/3
 4381
 4382messy_dollar_split(A,Out) :-
 4383   assertion(A \== ''),
 4384   atom_chars(A,Chars),
 4385   append([''|Chars],[''],GAChars), % GA is a "guarded A char list" flanked by empties and contains at least 3 chars
 4386   triple_process(GAChars,[],[],RunsOut),
 4387   postprocess_messy_dollar_split_runs(RunsOut,Out).
 4388
 4389postprocess_messy_dollar_split_runs(Runs,Out) :-
 4390   reverse(Runs,R1),
 4391   maplist([Rin,Rout]>>reverse(Rin,Rout),R1,O1),
 4392   maplist([Chars,Atom]>>atom_chars(Atom,Chars),O1,Out).
 4393
 4394% Split only between P and N, dropping C, when:
 4395% 1) C is a $ and P is not a dollar and not a start of line
 4396% 2) N is not the end of line
 4397
 4398triple_process([P,'$',N|Rest],Run,Runs,Out) :-
 4399   N \== '', P \== '$' , P \== '',!,
 4400   triple_process(['',N|Rest],[],[Run|Runs],Out).
 4401
 4402triple_process(['','$',N|Rest],Run,Runs,Out) :-
 4403   !,
 4404   triple_process(['',N|Rest],['$'|Run],Runs,Out).
 4405
 4406triple_process([_,C,N|Rest],Run,Runs,Out) :-
 4407   C \== '$',!,
 4408   triple_process([C,N|Rest],[C|Run],Runs,Out).
 4409
 4410triple_process([_,C,''],Run,Runs,[[C|Run]|Runs]) :- !.
 4411
 4412triple_process([_,''],Run,Runs,[Run|Runs]).
 4413
 4414% ===
 4415% Low-level DCG rules
 4416% ===
 4417
 4418% ---
 4419% A Java type identifier is a Java identifier different from "var" and "yield"
 4420% ---
 4421
 4422jpl_java_type_id(I)  --> jpl_java_id(I), { \+memberchk(I,[var,yield]) }.
 4423
 4424% ---
 4425% The Java identifier is described at
 4426% https://docs.oracle.com/javase/specs/jls/se14/html/jls-3.html#jls-Identifier
 4427% ---
 4428
 4429jpl_java_id(I) --> jpl_java_id_raw(I),
 4430                   { \+jpl_java_keyword(I),
 4431                     \+jpl_java_boolean_literal(I),
 4432                     \+jpl_java_null_literal(I) }.
 4433
 4434% ---
 4435% For direct handling of an identifier, we suffer symmetry breakdown.
 4436% ---
 4437
 4438jpl_java_id_raw(A) --> { atom(A),! },  % guard
 4439                       { atom_codes(A,[C|Cs]) }, % explode A
 4440                       { jpl_java_id_start_char(C) },
 4441                       [C],
 4442                       jpl_java_id_part_chars(Cs).
 4443
 4444% building X from the character code list
 4445
 4446jpl_java_id_raw(A) --> { var(A),! },  % guard
 4447                       [C],
 4448                       { jpl_java_id_start_char(C) },
 4449                       jpl_java_id_part_chars(Cs),
 4450                       { atom_codes(A,[C|Cs]) }. % fuse A
 4451
 4452jpl_java_id_part_chars([C|Cs]) --> [C], { jpl_java_id_part_char(C) } ,!, jpl_java_id_part_chars(Cs).
 4453jpl_java_id_part_chars([])     --> [].
 4454
 4455% ---
 4456% jpl_primitive_in_array//1
 4457% Described informally in Javadoc for Class.getName()
 4458% https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Class.html#getName()
 4459% The left-hand side should (the JPL type) really be tagged with primitive(boolean) etc.
 4460% ---
 4461
 4462jpl_primitive_type_descriptor(boolean) --> "Z",!.
 4463jpl_primitive_type_descriptor(byte)    --> "B",!.
 4464jpl_primitive_type_descriptor(char)    --> "C",!.
 4465jpl_primitive_type_descriptor(double)  --> "D",!.
 4466jpl_primitive_type_descriptor(float)   --> "F",!.
 4467jpl_primitive_type_descriptor(int)     --> "I",!.
 4468jpl_primitive_type_descriptor(long)    --> "J",!.
 4469jpl_primitive_type_descriptor(short)   --> "S".
 4470
 4471% ---
 4472% jpl_primitive_entityname//1
 4473% These are just the primitive names.
 4474% The left-hand side should (the JPL type) really be tagged with primitive(boolean) etc.
 4475% ---
 4476
 4477jpl_primitive_entityname(boolean) --> "boolean" ,!.
 4478jpl_primitive_entityname(byte)    --> "byte"    ,!.
 4479jpl_primitive_entityname(char)    --> "char"    ,!.
 4480jpl_primitive_entityname(double)  --> "double"  ,!.
 4481jpl_primitive_entityname(float)   --> "float"   ,!.
 4482jpl_primitive_entityname(int)     --> "int"     ,!.
 4483jpl_primitive_entityname(long)    --> "long"    ,!.
 4484jpl_primitive_entityname(short)   --> "short".
 4485
 4486% ---
 4487% Certain java keywords that may not occur as java identifier
 4488% ---
 4489
 4490jpl_java_boolean_literal(true).
 4491jpl_java_boolean_literal(false).
 4492
 4493jpl_java_null_literal(null).
 4494
 4495jpl_java_keyword('_').
 4496jpl_java_keyword(abstract).
 4497jpl_java_keyword(assert).
 4498jpl_java_keyword(boolean).
 4499jpl_java_keyword(break).
 4500jpl_java_keyword(byte).
 4501jpl_java_keyword(case).
 4502jpl_java_keyword(catch).
 4503jpl_java_keyword(char).
 4504jpl_java_keyword(class).
 4505jpl_java_keyword(const).
 4506jpl_java_keyword(continue).
 4507jpl_java_keyword(default).
 4508jpl_java_keyword(do).
 4509jpl_java_keyword(double).
 4510jpl_java_keyword(else).
 4511jpl_java_keyword(enum).
 4512jpl_java_keyword(extends).
 4513jpl_java_keyword(final).
 4514jpl_java_keyword(finally).
 4515jpl_java_keyword(float).
 4516jpl_java_keyword(for).
 4517jpl_java_keyword(goto).
 4518jpl_java_keyword(if).
 4519jpl_java_keyword(implements).
 4520jpl_java_keyword(import).
 4521jpl_java_keyword(instanceof).
 4522jpl_java_keyword(int).
 4523jpl_java_keyword(interface).
 4524jpl_java_keyword(long).
 4525jpl_java_keyword(native).
 4526jpl_java_keyword(new).
 4527jpl_java_keyword(package).
 4528jpl_java_keyword(private).
 4529jpl_java_keyword(protected).
 4530jpl_java_keyword(public).
 4531jpl_java_keyword(return).
 4532jpl_java_keyword(short).
 4533jpl_java_keyword(static).
 4534jpl_java_keyword(strictfp).
 4535jpl_java_keyword(super).
 4536jpl_java_keyword(switch).
 4537jpl_java_keyword(synchronized).
 4538jpl_java_keyword(this).
 4539jpl_java_keyword(throw).
 4540jpl_java_keyword(throws).
 4541jpl_java_keyword(transient).
 4542jpl_java_keyword(try).
 4543jpl_java_keyword(void).
 4544jpl_java_keyword(volatile).
 4545jpl_java_keyword(while).
 4546
 4547% ===
 4548% Classify codepoints (i.e. integers) as "Java identifier start/part characters"
 4549%
 4550% A "Java identifier" starts with a "Java identifier start character" and
 4551% continues with a "Java identifier part character".
 4552%
 4553% A "Java identifier start character" is a character for which
 4554% Character.isJavaIdentifierStart(c) returns true, where "c" can be a
 4555% Java char or an integer Unicode code value (basically, that's the definition).
 4556%
 4557% Similarly, a "Java identifier part character" is a character for which
 4558% point Character.isJavaIdentifierPart(c) returns true
 4559%
 4560% See:
 4561%
 4562% https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Character.html#isJavaIdentifierStart(int)
 4563% https://docs.oracle.com/en/java/javase/14/docs/api/java.base/java/lang/Character.html#isJavaIdentifierPart(int)
 4564%
 4565% A simple Java program was used to generate the runs of unicode character
 4566% points listed below. They are searched lineraly. Generally, a
 4567% code point/value encountered by jpl would be below even 255 and so be
 4568% found quickly
 4569%
 4570% PROBLEM:
 4571%
 4572% 1) If the Prolog implementation does not represent characters internally
 4573%    with Unicode code values, i.e. if atom_codes/2 takes/returns other values
 4574%    than Unicode code values (may be the case for Prologs other than SWI Prolog)
 4575%    an implementation-dependent mapping from/to Unicode will have to be performed
 4576%    first!
 4577%
 4578% 2) Is this slow or not? It depends on what the compiler does.
 4579% ===
 4580
 4581jpl_java_id_start_char(C) :-
 4582   assertion(integer(C)),
 4583   java_id_start_char_ranges(Ranges), % retrieve ranges
 4584   char_inside_range(C,Ranges).               % check
 4585
 4586jpl_java_id_part_char(C) :-
 4587   assertion(integer(C)),
 4588   java_id_part_char_ranges(Ranges),  % retrieve ranges
 4589   char_inside_range(C,Ranges).               % check
 4590
 4591char_inside_range(C,[[_Low,High]|Ranges]) :-
 4592   High < C,!,char_inside_range(C,Ranges).
 4593
 4594char_inside_range(C,[[Low,High]|_]) :-
 4595   Low =< C, C =< High.
 4596
 4597% ---
 4598% The ranges below are generated with a Java program, then printed
 4599% See "CharRangePrinter.java"
 4600% Note that 36 is "$" which IS allowed as start and part character!
 4601% In fact, there are class names that start with '$' (which is why the
 4602% current version of JPL cannot connect to LibreOffice)
 4603% ---
 4604
 4605java_id_start_char_ranges(
 4606   [[36,36],[65,90],[95,95],[97,122],[162,165],[170,170],[181,181],[186,186],
 4607   [192,214],[216,246],[248,705],[710,721],[736,740],[748,748],[750,750],
 4608   [880,884],[886,887],[890,893],[895,895],[902,902],[904,906],[908,908],
 4609   [910,929],[931,1013],[1015,1153],[1162,1327],[1329,1366],[1369,1369],
 4610   [1376,1416],[1423,1423],[1488,1514],[1519,1522],[1547,1547],[1568,1610],
 4611   [1646,1647],[1649,1747],[1749,1749],[1765,1766],[1774,1775],[1786,1788],
 4612   [1791,1791],[1808,1808],[1810,1839],[1869,1957],[1969,1969],[1994,2026],
 4613   [2036,2037],[2042,2042],[2046,2069],[2074,2074],[2084,2084],[2088,2088],
 4614   [2112,2136],[2144,2154],[2208,2228],[2230,2237],[2308,2361],[2365,2365],
 4615   [2384,2384],[2392,2401],[2417,2432],[2437,2444],[2447,2448],[2451,2472],
 4616   [2474,2480],[2482,2482],[2486,2489],[2493,2493],[2510,2510],[2524,2525],
 4617   [2527,2529],[2544,2547],[2555,2556],[2565,2570],[2575,2576],[2579,2600],
 4618   [2602,2608],[2610,2611],[2613,2614],[2616,2617],[2649,2652],[2654,2654],
 4619   [2674,2676],[2693,2701],[2703,2705],[2707,2728],[2730,2736],[2738,2739],
 4620   [2741,2745],[2749,2749],[2768,2768],[2784,2785],[2801,2801],[2809,2809],
 4621   [2821,2828],[2831,2832],[2835,2856],[2858,2864],[2866,2867],[2869,2873],
 4622   [2877,2877],[2908,2909],[2911,2913],[2929,2929],[2947,2947],[2949,2954],
 4623   [2958,2960],[2962,2965],[2969,2970],[2972,2972],[2974,2975],[2979,2980],
 4624   [2984,2986],[2990,3001],[3024,3024],[3065,3065],[3077,3084],[3086,3088],
 4625   [3090,3112],[3114,3129],[3133,3133],[3160,3162],[3168,3169],[3200,3200],
 4626   [3205,3212],[3214,3216],[3218,3240],[3242,3251],[3253,3257],[3261,3261],
 4627   [3294,3294],[3296,3297],[3313,3314],[3333,3340],[3342,3344],[3346,3386],
 4628   [3389,3389],[3406,3406],[3412,3414],[3423,3425],[3450,3455],[3461,3478],
 4629   [3482,3505],[3507,3515],[3517,3517],[3520,3526],[3585,3632],[3634,3635],
 4630   [3647,3654],[3713,3714],[3716,3716],[3718,3722],[3724,3747],[3749,3749],
 4631   [3751,3760],[3762,3763],[3773,3773],[3776,3780],[3782,3782],[3804,3807],
 4632   [3840,3840],[3904,3911],[3913,3948],[3976,3980],[4096,4138],[4159,4159],
 4633   [4176,4181],[4186,4189],[4193,4193],[4197,4198],[4206,4208],[4213,4225],
 4634   [4238,4238],[4256,4293],[4295,4295],[4301,4301],[4304,4346],[4348,4680],
 4635   [4682,4685],[4688,4694],[4696,4696],[4698,4701],[4704,4744],[4746,4749],
 4636   [4752,4784],[4786,4789],[4792,4798],[4800,4800],[4802,4805],[4808,4822],
 4637   [4824,4880],[4882,4885],[4888,4954],[4992,5007],[5024,5109],[5112,5117],
 4638   [5121,5740],[5743,5759],[5761,5786],[5792,5866],[5870,5880],[5888,5900],
 4639   [5902,5905],[5920,5937],[5952,5969],[5984,5996],[5998,6000],[6016,6067],
 4640   [6103,6103],[6107,6108],[6176,6264],[6272,6276],[6279,6312],[6314,6314],
 4641   [6320,6389],[6400,6430],[6480,6509],[6512,6516],[6528,6571],[6576,6601],
 4642   [6656,6678],[6688,6740],[6823,6823],[6917,6963],[6981,6987],[7043,7072],
 4643   [7086,7087],[7098,7141],[7168,7203],[7245,7247],[7258,7293],[7296,7304],
 4644   [7312,7354],[7357,7359],[7401,7404],[7406,7411],[7413,7414],[7418,7418],
 4645   [7424,7615],[7680,7957],[7960,7965],[7968,8005],[8008,8013],[8016,8023],
 4646   [8025,8025],[8027,8027],[8029,8029],[8031,8061],[8064,8116],[8118,8124],
 4647   [8126,8126],[8130,8132],[8134,8140],[8144,8147],[8150,8155],[8160,8172],
 4648   [8178,8180],[8182,8188],[8255,8256],[8276,8276],[8305,8305],[8319,8319],
 4649   [8336,8348],[8352,8383],[8450,8450],[8455,8455],[8458,8467],[8469,8469],
 4650   [8473,8477],[8484,8484],[8486,8486],[8488,8488],[8490,8493],[8495,8505],
 4651   [8508,8511],[8517,8521],[8526,8526],[8544,8584],[11264,11310],[11312,11358],
 4652   [11360,11492],[11499,11502],[11506,11507],[11520,11557],[11559,11559],
 4653   [11565,11565],[11568,11623],[11631,11631],[11648,11670],[11680,11686],
 4654   [11688,11694],[11696,11702],[11704,11710],[11712,11718],[11720,11726],
 4655   [11728,11734],[11736,11742],[11823,11823],[12293,12295],[12321,12329],
 4656   [12337,12341],[12344,12348],[12353,12438],[12445,12447],[12449,12538],
 4657   [12540,12543],[12549,12591],[12593,12686],[12704,12730],[12784,12799],
 4658   [13312,19893],[19968,40943],[40960,42124],[42192,42237],[42240,42508],
 4659   [42512,42527],[42538,42539],[42560,42606],[42623,42653],[42656,42735],
 4660   [42775,42783],[42786,42888],[42891,42943],[42946,42950],[42999,43009],
 4661   [43011,43013],[43015,43018],[43020,43042],[43064,43064],[43072,43123],
 4662   [43138,43187],[43250,43255],[43259,43259],[43261,43262],[43274,43301],
 4663   [43312,43334],[43360,43388],[43396,43442],[43471,43471],[43488,43492],
 4664   [43494,43503],[43514,43518],[43520,43560],[43584,43586],[43588,43595],
 4665   [43616,43638],[43642,43642],[43646,43695],[43697,43697],[43701,43702],
 4666   [43705,43709],[43712,43712],[43714,43714],[43739,43741],[43744,43754],
 4667   [43762,43764],[43777,43782],[43785,43790],[43793,43798],[43808,43814],
 4668   [43816,43822],[43824,43866],[43868,43879],[43888,44002],[44032,55203],
 4669   [55216,55238],[55243,55291],[63744,64109],[64112,64217],[64256,64262],
 4670   [64275,64279],[64285,64285],[64287,64296],[64298,64310],[64312,64316],
 4671   [64318,64318],[64320,64321],[64323,64324],[64326,64433],[64467,64829],
 4672   [64848,64911],[64914,64967],[65008,65020],[65075,65076],[65101,65103],
 4673   [65129,65129],[65136,65140],[65142,65276],[65284,65284],[65313,65338],
 4674   [65343,65343],[65345,65370],[65382,65470],[65474,65479],[65482,65487],
 4675   [65490,65495],[65498,65500],[65504,65505],[65509,65510]]).
 4676
 4677java_id_part_char_ranges(
 4678   [[0,8],[14,27],[36,36],[48,57],[65,90],[95,95],[97,122],[127,159],[162,165],
 4679   [170,170],[173,173],[181,181],[186,186],[192,214],[216,246],[248,705],
 4680   [710,721],[736,740],[748,748],[750,750],[768,884],[886,887],[890,893],
 4681   [895,895],[902,902],[904,906],[908,908],[910,929],[931,1013],[1015,1153],
 4682   [1155,1159],[1162,1327],[1329,1366],[1369,1369],[1376,1416],[1423,1423],
 4683   [1425,1469],[1471,1471],[1473,1474],[1476,1477],[1479,1479],[1488,1514],
 4684   [1519,1522],[1536,1541],[1547,1547],[1552,1562],[1564,1564],[1568,1641],
 4685   [1646,1747],[1749,1757],[1759,1768],[1770,1788],[1791,1791],[1807,1866],
 4686   [1869,1969],[1984,2037],[2042,2042],[2045,2093],[2112,2139],[2144,2154],
 4687   [2208,2228],[2230,2237],[2259,2403],[2406,2415],[2417,2435],[2437,2444],
 4688   [2447,2448],[2451,2472],[2474,2480],[2482,2482],[2486,2489],[2492,2500],
 4689   [2503,2504],[2507,2510],[2519,2519],[2524,2525],[2527,2531],[2534,2547],
 4690   [2555,2556],[2558,2558],[2561,2563],[2565,2570],[2575,2576],[2579,2600],
 4691   [2602,2608],[2610,2611],[2613,2614],[2616,2617],[2620,2620],[2622,2626],
 4692   [2631,2632],[2635,2637],[2641,2641],[2649,2652],[2654,2654],[2662,2677],
 4693   [2689,2691],[2693,2701],[2703,2705],[2707,2728],[2730,2736],[2738,2739],
 4694   [2741,2745],[2748,2757],[2759,2761],[2763,2765],[2768,2768],[2784,2787],
 4695   [2790,2799],[2801,2801],[2809,2815],[2817,2819],[2821,2828],[2831,2832],
 4696   [2835,2856],[2858,2864],[2866,2867],[2869,2873],[2876,2884],[2887,2888],
 4697   [2891,2893],[2902,2903],[2908,2909],[2911,2915],[2918,2927],[2929,2929],
 4698   [2946,2947],[2949,2954],[2958,2960],[2962,2965],[2969,2970],[2972,2972],
 4699   [2974,2975],[2979,2980],[2984,2986],[2990,3001],[3006,3010],[3014,3016],
 4700   [3018,3021],[3024,3024],[3031,3031],[3046,3055],[3065,3065],[3072,3084],
 4701   [3086,3088],[3090,3112],[3114,3129],[3133,3140],[3142,3144],[3146,3149],
 4702   [3157,3158],[3160,3162],[3168,3171],[3174,3183],[3200,3203],[3205,3212],
 4703   [3214,3216],[3218,3240],[3242,3251],[3253,3257],[3260,3268],[3270,3272],
 4704   [3274,3277],[3285,3286],[3294,3294],[3296,3299],[3302,3311],[3313,3314],
 4705   [3328,3331],[3333,3340],[3342,3344],[3346,3396],[3398,3400],[3402,3406],
 4706   [3412,3415],[3423,3427],[3430,3439],[3450,3455],[3458,3459],[3461,3478],
 4707   [3482,3505],[3507,3515],[3517,3517],[3520,3526],[3530,3530],[3535,3540],
 4708   [3542,3542],[3544,3551],[3558,3567],[3570,3571],[3585,3642],[3647,3662],
 4709   [3664,3673],[3713,3714],[3716,3716],[3718,3722],[3724,3747],[3749,3749],
 4710   [3751,3773],[3776,3780],[3782,3782],[3784,3789],[3792,3801],[3804,3807],
 4711   [3840,3840],[3864,3865],[3872,3881],[3893,3893],[3895,3895],[3897,3897],
 4712   [3902,3911],[3913,3948],[3953,3972],[3974,3991],[3993,4028],[4038,4038],
 4713   [4096,4169],[4176,4253],[4256,4293],[4295,4295],[4301,4301],[4304,4346],
 4714   [4348,4680],[4682,4685],[4688,4694],[4696,4696],[4698,4701],[4704,4744],
 4715   [4746,4749],[4752,4784],[4786,4789],[4792,4798],[4800,4800],[4802,4805],
 4716   [4808,4822],[4824,4880],[4882,4885],[4888,4954],[4957,4959],[4992,5007],
 4717   [5024,5109],[5112,5117],[5121,5740],[5743,5759],[5761,5786],[5792,5866],
 4718   [5870,5880],[5888,5900],[5902,5908],[5920,5940],[5952,5971],[5984,5996],
 4719   [5998,6000],[6002,6003],[6016,6099],[6103,6103],[6107,6109],[6112,6121],
 4720   [6155,6158],[6160,6169],[6176,6264],[6272,6314],[6320,6389],[6400,6430],
 4721   [6432,6443],[6448,6459],[6470,6509],[6512,6516],[6528,6571],[6576,6601],
 4722   [6608,6617],[6656,6683],[6688,6750],[6752,6780],[6783,6793],[6800,6809],
 4723   [6823,6823],[6832,6845],[6912,6987],[6992,7001],[7019,7027],[7040,7155],
 4724   [7168,7223],[7232,7241],[7245,7293],[7296,7304],[7312,7354],[7357,7359],
 4725   [7376,7378],[7380,7418],[7424,7673],[7675,7957],[7960,7965],[7968,8005],
 4726   [8008,8013],[8016,8023],[8025,8025],[8027,8027],[8029,8029],[8031,8061],
 4727   [8064,8116],[8118,8124],[8126,8126],[8130,8132],[8134,8140],[8144,8147],
 4728   [8150,8155],[8160,8172],[8178,8180],[8182,8188],[8203,8207],[8234,8238],
 4729   [8255,8256],[8276,8276],[8288,8292],[8294,8303],[8305,8305],[8319,8319],
 4730   [8336,8348],[8352,8383],[8400,8412],[8417,8417],[8421,8432],[8450,8450],
 4731   [8455,8455],[8458,8467],[8469,8469],[8473,8477],[8484,8484],[8486,8486],
 4732   [8488,8488],[8490,8493],[8495,8505],[8508,8511],[8517,8521],[8526,8526],
 4733   [8544,8584],[11264,11310],[11312,11358],[11360,11492],[11499,11507],
 4734   [11520,11557],[11559,11559],[11565,11565],[11568,11623],[11631,11631],
 4735   [11647,11670],[11680,11686],[11688,11694],[11696,11702],[11704,11710],
 4736   [11712,11718],[11720,11726],[11728,11734],[11736,11742],[11744,11775],
 4737   [11823,11823],[12293,12295],[12321,12335],[12337,12341],[12344,12348],
 4738   [12353,12438],[12441,12442],[12445,12447],[12449,12538],[12540,12543],
 4739   [12549,12591],[12593,12686],[12704,12730],[12784,12799],[13312,19893],
 4740   [19968,40943],[40960,42124],[42192,42237],[42240,42508],[42512,42539],
 4741   [42560,42607],[42612,42621],[42623,42737],[42775,42783],[42786,42888],
 4742   [42891,42943],[42946,42950],[42999,43047],[43064,43064],[43072,43123],
 4743   [43136,43205],[43216,43225],[43232,43255],[43259,43259],[43261,43309],
 4744   [43312,43347],[43360,43388],[43392,43456],[43471,43481],[43488,43518],
 4745   [43520,43574],[43584,43597],[43600,43609],[43616,43638],[43642,43714],
 4746   [43739,43741],[43744,43759],[43762,43766],[43777,43782],[43785,43790],
 4747   [43793,43798],[43808,43814],[43816,43822],[43824,43866],[43868,43879],
 4748   [43888,44010],[44012,44013],[44016,44025],[44032,55203],[55216,55238],
 4749   [55243,55291],[63744,64109],[64112,64217],[64256,64262],[64275,64279],
 4750   [64285,64296],[64298,64310],[64312,64316],[64318,64318],[64320,64321],
 4751   [64323,64324],[64326,64433],[64467,64829],[64848,64911],[64914,64967],
 4752   [65008,65020],[65024,65039],[65056,65071],[65075,65076],[65101,65103],
 4753   [65129,65129],[65136,65140],[65142,65276],[65279,65279],[65284,65284],
 4754   [65296,65305],[65313,65338],[65343,65343],[65345,65370],[65382,65470],
 4755   [65474,65479],[65482,65487],[65490,65495],[65498,65500],[65504,65505],
 4756   [65509,65510],[65529,65531]]).
 4757
 4758
 4759         /*******************************
 4760         *      EXCEPTION HANDLING      *
 4761         *******************************/
 4762
 4763% ===
 4764% throwme(+LookupPred,+LookupTerm)
 4765%
 4766% Predicate called to construct an exception term and throw it. Information
 4767% about how to construct the actual exception is found by performing a lookup
 4768% based on the key formed by the pair (LookupPred,LookupTerm).
 4769%
 4770% LookupPred :
 4771%    What predicate is throwing; this is an atom (a keyword) generally shaped
 4772%    after the actual predicate name of the throwing predicate. It is not a
 4773%    predicate indicator.
 4774%
 4775% LookupTerm :
 4776%    A term, possibly compound, that describes the problem somehow. It is both
 4777%    programmer-interpretable (but still abstract) as well as a way of passing
 4778%    values that can be inserted into the "Formal" part.
 4779%
 4780% Example: throwme(setter_atomic,nonzero(A))
 4781% ===
 4782
 4783throwme(LookupPred,LookupTerm) :-
 4784   findall([Location,Formal,Msg],exc_desc(LookupPred,LookupTerm,Location,Formal,Msg),Bag),
 4785   length(Bag,BagLength),
 4786   throwme_help(BagLength,Bag,LookupPred,LookupTerm).
 4787
 4788% Helper invoked if exactly 1 applicable "exception descriptor" could be found.
 4789% Throw the corresponding exception!
 4790% This is the first clause in line. If there is no match on arg1, the catchall
 4791% fallback is used instead.
 4792% The constructed error term is "quasi ISO-standard" because its structure is
 4793% "error(Formal,Context)" -- but there is not guarantee that the "Formal" term
 4794% is any of the ISO-listed allowed "Formal" term (in fact, it generally is not).
 4795% The "Context" (about which the ISO standard says nothing, leaving it to be
 4796% "implementation-defined") is structured according to SWI-Prolog conventions:
 4797% "context(Location,Msg)" where "Location", if left fresh, can be filled with
 4798% a stack trace on the toplevel or by a catching catch_with_backtrace/3. It
 4799% is, however, often filled with the predicate indicator of the throwing
 4800% predicate. The "Msg" should be a stringy thing to printed out, i.e. a
 4801% human-readable explainer that is either an atom or a string.
 4802% - Is there a requirement that "Msg" be forced to an atom?
 4803% ---
 4804
 4805throwme_help(1,[[Location,Formal,Msg]],_,_) :-
 4806   throw(error(Formal,context(Location,Msg))).
 4807
 4808% ---
 4809% Helper invoked if not exactly 1 applicable "exception descriptor" could be found.
 4810% That means the set of exception descriptors is incomplete/ambiguous or the lookup
 4811% query is wrong. Throws a quasi-ISO-standard exception following the format
 4812% error(_,_) but with the formal term the non-ISO atom 'programming_error'.
 4813% - Note that "Msg" is an atom, not a string (is that ok? it should probably be
 4814%   a String, at least in SWI-Prolog)
 4815% - Note that the second argument for error(_,_) follows SWI-Prolog conventions
 4816%   and with its first position fresh, may be filled with a backtrace.
 4817% ---
 4818
 4819throwme_help(Count,_,LookupPred,LookupTerm) :-
 4820   Count \== 1,
 4821   with_output_to(
 4822      atom(Msg),
 4823      format("Instead of 1, found ~d exception descriptors for LookupPred = ~q, LookupTerm = ~q",
 4824         [Count,LookupPred,LookupTerm])),
 4825   throw(error(programming_error,context(_,Msg))).
 4826
 4827% ===
 4828% exc_desc(+LookupPred,+LookupTerm,?Location,?Formal,?Msg)
 4829% ===
 4830% Descriptors for exceptions.
 4831%
 4832% The first two arguments are used for lookup. See throwme/2 for an explainer.
 4833%
 4834% The three last arguments are output values which are use to construct
 4835% the exception term that is suppoed to be thrown by the caller.
 4836%
 4837% If "Location" is left a freshvar, it can be instantiated to a backtrack if
 4838% the exception reaches the Prolog Toplevel or is caught by
 4839% catch_with_backtrace/3.
 4840%
 4841% Otherwise, "Location" should be a predicate indicator or something similar.
 4842%
 4843% Example:
 4844%
 4845% exc_desc(jpl_call_static,no_such_method(M),
 4846%          jpl_call/4,
 4847%          existence_error(method,M),
 4848%          'some text')
 4849%
 4850% exc_desc(jpl_call_static,no_such_method(M),
 4851%          _,
 4852%          existence_error(method,M),
 4853%          'some text')
 4854%
 4855% The "Msg" is a user-readable message. For now, it is not dynamically
 4856% constructed (i.e. using format/3 calls) inside of exc_desc/5, nor is
 4857% internationalization supported for that matter. In some cases, the "Msg"
 4858% has been created by caller and is passed in inside "LookupTerm", from where
 4859% it is unification-picked-out-of-there into arg 5.
 4860%
 4861% The "Formal" is exactly the "formal term" that will used in the "exception
 4862% term", and it is built by unification doing pick/put against "LookupTerm".
 4863% It may or may not be ISO-Standard.
 4864%
 4865% Note that the fact that we adhere to ISO standard atoms instead of defining
 4866% our own for JPL has the advantage that exception-printing handlers on the
 4867% toplevel still work but the generated text is confusing: for example the
 4868% exception-generating handler receives a "type_error" (which is meant to
 4869% indicate a type problem inside a Prolog program, but here is also used to
 4870% indicate a type problem of a very different nature, e.g. the caller wants
 4871% to instantiate a Java interface) and the argument passed in the formal is
 4872% the name of the Java class as an atom. Then the printing handler will say
 4873% this: "there is a problem because this is an atom: 'foo.bar.Interface'" and
 4874% only by reading the cleartext message will the actual problem be revealed:
 4875% "you tried to instantiate an interface".
 4876% ---
 4877
 4878safe_type_to_classname(Type,CN) :-
 4879   catch(
 4880      (jpl_type_to_classname(Type,CN)
 4881       -> true
 4882       ;  with_output_to(atom(CN),format("~q",[Type]))),
 4883      _DontCareCatcher,
 4884      CN='???').
 4885
 4886exc_desc(jpl_new,x_is_var,
 4887         jpl_new/3,
 4888         instantiation_error,
 4889         '1st arg must be bound to a classname, descriptor or object type').
 4890
 4891exc_desc(jpl_new,x_not_classname(X),
 4892         jpl_new/3,
 4893         domain_error(classname,X),
 4894         'if 1st arg is an atom, it must be a classname or descriptor').
 4895
 4896exc_desc(jpl_new,x_not_instantiable(X),
 4897         jpl_new/3,
 4898         type_error(instantiable,X),
 4899         '1st arg must be a classname, descriptor or object type').
 4900
 4901exc_desc(jpl_new,not_a_jpl_term(X),
 4902         jpl_new/3,
 4903         type_error(term,X),
 4904         'result is not a org.jpl7.Term instance as required').
 4905
 4906% ---
 4907
 4908exc_desc(jpl_new_class,params_is_var,
 4909         jpl_new/3,
 4910         instantiation_error,
 4911         '2nd arg must be a proper list of valid parameters for a constructor').
 4912
 4913exc_desc(jpl_new_class,params_is_not_list(Params),
 4914         jpl_new/3,
 4915         type_error(list,Params),
 4916         '2nd arg must be a proper list of valid parameters for a constructor').
 4917
 4918exc_desc(jpl_new_class,class_is_interface(Type),
 4919         jpl_new/3,
 4920         type_error(concrete_class,CN),
 4921         'cannot create instance of an interface') :- safe_type_to_classname(Type,CN).
 4922
 4923exc_desc(jpl_new_class,class_without_constructor(Type,Arity),
 4924         jpl_new/3,
 4925         existence_error(constructor,CN/Arity),
 4926         'no constructor found with the corresponding quantity of parameters') :- safe_type_to_classname(Type,CN).
 4927
 4928exc_desc(jpl_new_class,acyclic(X,Msg),
 4929         jpl_new/3,
 4930         type_error(acyclic,X),
 4931         Msg).
 4932
 4933exc_desc(jpl_new_class,bad_jpl_datum(Params),
 4934         jpl_new/3,
 4935         domain_error(list(jpl_datum),Params),
 4936         'one or more of the actual parameters is not a valid representation of any Java value or object').
 4937
 4938exc_desc(jpl_new_class,single_constructor_mismatch(Co),
 4939         jpl_new/3,
 4940         existence_error(constructor,Co),
 4941         'the actual parameters are not assignable to the formal parameter types of the only constructor which takes this qty of parameters').
 4942
 4943exc_desc(jpl_new_class,any_constructor_mismatch(Params),
 4944         jpl_new/3,
 4945         type_error(constructor_args,Params),
 4946         'the actual parameters are not assignable to the formal parameter types of any of the constructors which take this qty of parameters').
 4947
 4948exc_desc(jpl_new_class,constructor_multimatch(Params),
 4949         jpl_new/3,
 4950         type_error(constructor_params,Params),
 4951         'more than one most-specific matching constructor (shouldn''t happen)').
 4952
 4953exc_desc(jpl_new_class,class_is_abstract(Type),
 4954         jpl_new/3,
 4955         type_error(concrete_class,CN),
 4956         'cannot create instance of an abstract class') :- safe_type_to_classname(Type,CN).
 4957
 4958% ---
 4959
 4960exc_desc(jpl_new_array,params_is_var,
 4961         jpl_new/3,
 4962         instantiation_error,
 4963         'when constructing a new array, 2nd arg must either be a non-negative integer (denoting the required array length) or a proper list of valid element values').
 4964
 4965exc_desc(jpl_new_array,params_is_negative(Params),
 4966         jpl_new/3,
 4967         domain_error(array_length,Params),
 4968         'when constructing a new array, if the 2nd arg is an integer (denoting the required array length) then it must be non-negative').
 4969
 4970% ---
 4971
 4972exc_desc(jpl_new_primitive,primitive_type_requested(T),
 4973         jpl_new/3,
 4974         domain_error(object_type,T),
 4975         'cannot construct an instance of a primitive type').
 4976
 4977% the call to this is commented out in jpl.pl
 4978exc_desc(jpl_new_primitive,params_is_var,
 4979         jpl_new/3,
 4980         instantiation_error,
 4981         'when constructing a new instance of a primitive type, 2nd arg must be bound (to a representation of a suitable value)').
 4982
 4983% the call to this is commented out in jpl.pl
 4984exc_desc(jpl_new_primitive,params_is_bad(Params),
 4985         jpl_new/3,
 4986         domain_error(constructor_args,Params),Msg) :-
 4987   atomic_list_concat([
 4988         'when constructing a new instance of a primitive type, 2nd arg must either be an ',
 4989         'empty list (indicating that the default value of that type is required) or a ',
 4990         'list containing exactly one representation of a suitable value'],Msg).
 4991
 4992% ---
 4993
 4994exc_desc(jpl_new_catchall,catchall(T),
 4995         jpl_new/3,
 4996         domain_error(jpl_type,T),
 4997         '1st arg must denote a known or plausible type').
 4998
 4999% ---
 5000
 5001exc_desc(jpl_call,arg1_is_var,
 5002         jpl_call/4,
 5003         instantiation_error,
 5004         '1st arg must be bound to an object, classname, descriptor or type').
 5005
 5006exc_desc(jpl_call,no_such_class(X),
 5007         jpl_call/4,
 5008         existence_error(class,X),
 5009         'the named class cannot be found').
 5010
 5011exc_desc(jpl_call,arg1_is_bad(X),
 5012         jpl_call/4,
 5013         type_error(class_name_or_descriptor,X),
 5014         '1st arg must be an object, classname, descriptor or type').
 5015
 5016exc_desc(jpl_call,arg1_is_array(X),
 5017         jpl_call/4,
 5018         type_error(object_or_class,X),
 5019         'cannot call a static method of an array type, as none exists').
 5020
 5021exc_desc(jpl_call,arg1_is_bad_2(X),
 5022         jpl_call/4,
 5023         domain_error(object_or_class,X),
 5024         '1st arg must be an object, classname, descriptor or type').
 5025
 5026exc_desc(jpl_call,mspec_is_var,
 5027         jpl_call/4,
 5028         instantiation_error,
 5029         '2nd arg must be an atom naming a public method of the class or object').
 5030
 5031exc_desc(jpl_call,mspec_is_bad(Mspec),
 5032         jpl_call/4,
 5033         type_error(method_name,Mspec),
 5034         '2nd arg must be an atom naming a public method of the class or object').
 5035
 5036exc_desc(jpl_call,acyclic(Te,Msg),
 5037         jpl_call/4,
 5038         type_error(acyclic,Te),
 5039         Msg).
 5040
 5041exc_desc(jpl_call,nonconvertible_params(Params),
 5042         jpl_call/4,
 5043         type_error(method_params,Params),
 5044         'not all actual parameters are convertible to Java values or references').
 5045
 5046exc_desc(jpl_call,arg3_is_var,
 5047         jpl_call/4,
 5048         instantiation_error,
 5049         '3rd arg must be a proper list of actual parameters for the named method').
 5050
 5051exc_desc(jpl_call,arg3_is_bad(Params),
 5052         jpl_call/4,
 5053         type_error(method_params,Params),
 5054         '3rd arg must be a proper list of actual parameters for the named method').
 5055
 5056exc_desc(jpl_call,not_a_jpl_term(X),
 5057         jpl_call/4,
 5058         type_error(jni_jref,X),
 5059         'result is not a org.jpl7.Term instance as required').
 5060
 5061% ---
 5062
 5063exc_desc(jpl_call_instance,no_such_method(M),
 5064	 jpl_call/4,
 5065	 existence_error(method,M),
 5066         'the class or object has no public methods with the given name and quantity of parameters').
 5067
 5068exc_desc(jpl_call_instance,param_not_assignable(P),
 5069	 jpl_call/4,
 5070	 type_error(method_params,P),
 5071         'the actual parameters are not assignable to the formal parameters of any of the named methods').
 5072
 5073exc_desc(jpl_call_instance,multiple_most_specific(M),
 5074	 jpl_call/4,
 5075	 existence_error(most_specific_method,M),
 5076         'more than one most-specific method is found for the actual parameters (this should not happen)').
 5077
 5078% ---
 5079
 5080exc_desc(jpl_call_static,no_such_method(M),
 5081         jpl_call/4,
 5082	 existence_error(method,M),
 5083         'the class has no public static methods with the given name and quantity of parameters').
 5084
 5085exc_desc(jpl_call_static,param_not_assignable(P),
 5086	 jpl_call/4,
 5087	 type_error(method_params,P),
 5088         'the actual parameters are not assignable to the formal parameters of any of the named methods').
 5089
 5090exc_desc(jpl_call_static,multiple_most_specific(M),
 5091	 jpl_call/4,
 5092	 existence_error(most_specific_method,M),
 5093         'more than one most-specific method is found for the actual parameters (this should not happen)').
 5094
 5095% ---
 5096
 5097exc_desc(jpl_get,arg1_is_var,
 5098	 jpl_get/3,
 5099         instantiation_error,
 5100         '1st arg must be bound to an object, classname, descriptor or type').
 5101
 5102exc_desc(jpl_get,named_class_not_found(Type),
 5103	 jpl_get/3,
 5104         existence_error(class,CN),
 5105         'the named class cannot be found') :- safe_type_to_classname(Type,CN).
 5106
 5107exc_desc(jpl_get,arg1_is_bad(X),
 5108	 jpl_get/3,
 5109         type_error(class_name_or_descriptor,X),
 5110         '1st arg must be an object, classname, descriptor or type').
 5111
 5112exc_desc(jpl_get,arg1_is_bad_2(X),
 5113	 jpl_get/3,
 5114         domain_error(object_or_class,X),
 5115         '1st arg must be an object, classname, descriptor or type').
 5116
 5117exc_desc(jpl_get,not_a_jpl_term(X),
 5118         jpl_get/3,
 5119         type_error(jni_ref,X),
 5120         'result is not a org.jpl7.Term instance as required').
 5121
 5122% ---
 5123
 5124exc_desc(jpl_get_static,arg2_is_var,
 5125	 jpl_get/3,
 5126	 instantiation_error,
 5127         '2nd arg must be bound to an atom naming a public field of the class').
 5128
 5129exc_desc(jpl_get_static,arg2_is_bad(F),
 5130	 jpl_get/3,
 5131	 type_error(field_name,F),
 5132         '2nd arg must be an atom naming a public field of the class').
 5133
 5134exc_desc(jpl_get_static,no_such_field(F),
 5135	 jpl_get/3,
 5136	 existence_error(field,F),
 5137         'the class or object has no public static field with the given name').
 5138
 5139exc_desc(jpl_get_static,multiple_fields(F),
 5140	 jpl_get/3,
 5141	 existence_error(unique_field,F),
 5142         'more than one field is found with the given name').
 5143
 5144% ---
 5145
 5146exc_desc(jpl_get_instance,arg2_is_var,
 5147	 jpl_get/3,
 5148	 instantiation_error,
 5149         '2nd arg must be bound to an atom naming a public field of the class or object').
 5150
 5151exc_desc(jpl_get_instance,arg2_is_bad(X),
 5152	 jpl_get/3,
 5153	 type_error(field_name,X),
 5154         '2nd arg must be an atom naming a public field of the class or object').
 5155
 5156exc_desc(jpl_get_instance,no_such_field(Fname),
 5157	 jpl_get/3,
 5158	 existence_error(field,Fname),
 5159         'the class or object has no public field with the given name').
 5160
 5161exc_desc(jpl_get_instance,multiple_fields(Fname),
 5162	 jpl_get/3,
 5163	 existence_error(unique_field,Fname),
 5164         'more than one field is found with the given name').
 5165
 5166% ---
 5167
 5168exc_desc(jpl_get_instance_array,arg2_is_var,
 5169	 jpl_get/3,
 5170	 instantiation_error,
 5171         'when 1st arg is an array, 2nd arg must be bound to an index, an index range, or ''length''').
 5172
 5173exc_desc(jpl_get_instance_array,arg2_is_bad(X),
 5174	 jpl_get/3,
 5175	 domain_error(array_index,X),
 5176         'when 1st arg is an array, integral 2nd arg must be non-negative').
 5177
 5178exc_desc(jpl_get_instance_array,arg2_is_too_large(X),
 5179	 jpl_get/3,
 5180	 domain_error(array_index,X),
 5181         'when 1st arg is an array, integral 2nd arg must not exceed upper bound of array').
 5182
 5183exc_desc(jpl_get_instance_array,bad_range_low(R),
 5184	 jpl_get/3,
 5185	 domain_error(array_index_range,R),
 5186         'lower bound of array index range must not exceed upper bound of array').
 5187
 5188exc_desc(jpl_get_instance_array,bad_range_high(R),
 5189	 jpl_get/3,
 5190	 domain_error(array_index_range,R),
 5191         'upper bound of array index range must not exceed upper bound of array').
 5192
 5193exc_desc(jpl_get_instance_array,bad_range_pair_values(R),
 5194	 jpl_get/3,
 5195	 domain_error(array_index_range,R),
 5196         'array index range must be a non-decreasing pair of non-negative integers').
 5197
 5198exc_desc(jpl_get_instance_array,bad_range_pair_types(R),
 5199	 jpl_get/3,
 5200	 type_error(array_index_range,R),
 5201         'array index range must be a non-decreasing pair of non-negative integers').
 5202
 5203exc_desc(jpl_get_instance_array,no_such_field(F),
 5204	 jpl_get/3,
 5205	 domain_error(array_field_name,F),
 5206         'the array has no public field with the given name').
 5207
 5208exc_desc(jpl_get_instance_array,wrong_spec(F),
 5209	 jpl_get/3,
 5210	 type_error(array_lookup_spec,F),
 5211         'when 1st arg is an array, 2nd arg must be an index, an index range, or ''length''').
 5212
 5213% ---
 5214
 5215exc_desc(jpl_set,arg1_is_var,
 5216	 jpl_set/3,
 5217	 instantiation_error,
 5218         '1st arg must be an object, classname, descriptor or type').
 5219
 5220exc_desc(jpl_set,classname_does_not_resolve(X),
 5221	 jpl_set/3,
 5222	 existence_error(class,X),
 5223         'the named class cannot be found').
 5224
 5225exc_desc(jpl_set,named_class_not_found(Type),
 5226         jpl_set/3,
 5227	 existence_error(class,CN),
 5228         'the named class cannot be found') :- safe_type_to_classname(Type,CN).
 5229
 5230exc_desc(jpl_set,acyclic(X,Msg),
 5231         jpl_set/3,
 5232         type_error(acyclic,X),
 5233         Msg).
 5234
 5235exc_desc(jpl_set,arg1_is_bad(X),
 5236	 jpl_set/3,
 5237	 domain_error(object_or_class,X),
 5238         '1st arg must be an object, classname, descriptor or type').
 5239
 5240% ---
 5241
 5242exc_desc(jpl_set_instance_class,arg2_is_var,
 5243	 jpl_set/3,
 5244	 instantiation_error,
 5245	 '2nd arg must be bound to the name of a public, non-final field').
 5246
 5247exc_desc(jpl_set_instance_class,arg2_is_bad(Fname),
 5248	 jpl_set/3,
 5249	 type_error(field_name,Fname),
 5250	 '2nd arg must be the name of a public, non-final field').
 5251
 5252exc_desc(jpl_set_instance_class,no_such_field(Fname),
 5253	 jpl_set/3,
 5254	 existence_error(field,Fname),
 5255	 'no public fields of the object have this name').
 5256
 5257exc_desc(jpl_set_instance_class,field_is_final(Fname),
 5258	 jpl_set/3,
 5259	 permission_error(modify,final_field,Fname),
 5260	 'cannot assign a value to a final field (actually you could but I''ve decided not to let you)').
 5261
 5262exc_desc(jpl_set_instance_class,incompatible_value(Type,V),
 5263	 jpl_set/3,
 5264	 type_error(CN,V),
 5265	 'the value is not assignable to the named field of the class') :- safe_type_to_classname(Type,CN).
 5266
 5267exc_desc(jpl_set_instance_class,arg3_is_bad(V),
 5268	 jpl_set/3,
 5269	 type_error(field_value,V),
 5270	 '3rd arg does not represent any Java value or object').
 5271
 5272exc_desc(jpl_set_instance_class,multiple_fields(Fname),
 5273	 jpl_set/3,
 5274	 existence_error(field,Fname),
 5275	 'more than one public field of the object has this name (this should not happen)').
 5276
 5277% ---
 5278
 5279exc_desc(jpl_set_instance_array,arg3_is_var,
 5280	 jpl_set/3,
 5281	 instantiation_error,
 5282	 'when 1st arg is an array, 3rd arg must be bound to a suitable element value or list of values').
 5283
 5284exc_desc(jpl_set_instance_array,arg2_is_var,
 5285	 jpl_set/3,
 5286	 instantiation_error,
 5287	 'when 1st arg is an array, 2nd arg must be bound to an index or index range').
 5288
 5289exc_desc(jpl_set_instance_array,arg2_is_bad(FSpec),
 5290	 jpl_set/3,
 5291	 domain_error(array_index,FSpec),
 5292	 'when 1st arg is an array, an integral 2nd arg must be a non-negative index').
 5293
 5294exc_desc(jpl_set_instance_array,no_values(Fspec,Vs),
 5295	 jpl_set/3,
 5296	 domain_error(array_element(Fspec),Vs),
 5297	 'no values for array element assignment: needs one').
 5298
 5299exc_desc(jpl_set_instance_array,more_than_one_value(Fspec,Vs),
 5300	 jpl_set/3,
 5301	 domain_error(array_element(Fspec),Vs),
 5302	 'too many values for array element assignment: needs one').
 5303
 5304exc_desc(jpl_set_instance_array,too_few_values(N-M,Vs),
 5305	 jpl_set/3,
 5306	 domain_error(array_elements(N-M),Vs),
 5307	 'too few values for array range assignment').
 5308
 5309exc_desc(jpl_set_instance_array,too_many_values(N-M,Vs),
 5310	 jpl_set/3,
 5311	 domain_error(array_elements(N-M),Vs),
 5312	 'too many values for array range assignment').
 5313
 5314exc_desc(jpl_set_instance_array,bad_range_pair_values(N-M),
 5315	 jpl_set/3,
 5316	 domain_error(array_index_range,N-M),
 5317	 'array index range must be a non-decreasing pair of non-negative integers').
 5318
 5319exc_desc(jpl_set_instance_array,bad_range_pair_types(N-M),
 5320	 jpl_set/3,
 5321	 type_error(array_index_range,N-M),
 5322	 'array index range must be a non-decreasing pair of non-negative integers').
 5323
 5324exc_desc(jpl_set_instance_array,cannot_assign_to_final_field,
 5325	 jpl_set/3,
 5326	 permission_error(modify,final_field,length),
 5327	 'cannot assign a value to a final field').
 5328
 5329exc_desc(jpl_set_instance_array,no_such_field(Fspec),
 5330	 jpl_set/3,
 5331	 existence_error(field,Fspec),
 5332	 'array has no field with that name').
 5333
 5334exc_desc(jpl_set_instance_array,arg2_is_bad_2(Fspec),
 5335	 jpl_set/3,
 5336	 domain_error(array_index,Fspec),
 5337	 'when 1st arg is an array object, 2nd arg must be a non-negative index or index range').
 5338
 5339% ---
 5340
 5341exc_desc(jpl_set_static,arg2_is_unbound,
 5342         jpl_set/3,
 5343         instantiation_error,
 5344         'when 1st arg denotes a class, 2nd arg must be bound to the name of a public, static, non-final field').
 5345
 5346exc_desc(jpl_set_static,arg2_is_bad(Fname),
 5347         jpl_set/3,
 5348         type_error(field_name,Fname),
 5349         'when 1st arg denotes a class, 2nd arg must be the name of a public, static, non-final field').
 5350
 5351exc_desc(jpl_set_static,no_such_public_static_field(field,Fname),
 5352         jpl_set/3,
 5353         existence_error(field,Fname),
 5354	 'class has no public static fields of this name').
 5355
 5356exc_desc(jpl_set_static,cannot_assign_final_field(Fname),
 5357         jpl_set/3,
 5358         permission_error(modify,final_field,Fname),
 5359	 'cannot assign a value to a final field').
 5360
 5361exc_desc(jpl_set_static,value_not_assignable(Type,V),
 5362         jpl_set/3,
 5363         type_error(CN,V),
 5364	 'the value is not assignable to the named field of the class') :- safe_type_to_classname(Type,CN).
 5365
 5366exc_desc(jpl_set_static,arg3_is_bad(field_value,V),
 5367         jpl_set/3,
 5368         type_error(field_value,V),
 5369	 '3rd arg does not represent any Java value or object').
 5370
 5371exc_desc(jpl_set_static,multiple_matches(field,Fname),
 5372         jpl_set/3,
 5373         existence_error(field,Fname),
 5374	 'more than one public static field of the class has this name (this should not happen)(?)').
 5375
 5376% ---
 5377
 5378exc_desc(jpl_set_array,not_all_values_assignable(T,Ds),
 5379         jpl_set/3,
 5380         type_error(array(T),Ds),
 5381	 'not all values are assignable to the array element type').
 5382
 5383exc_desc(jpl_set_array,not_all_values_convertible(T,Ds),
 5384         jpl_set/3,
 5385         type_error(array(T),Ds),
 5386	 'not all values are convertible to Java values or references').
 5387
 5388exc_desc(jpl_set_array,element_type_unknown(array_element_type,T),
 5389         jpl_set/3,
 5390         type_error(array_element_type,T),
 5391	 'array element type is unknown: neither a class, nor an array type, nor a primitive type').
 5392
 5393% ---
 5394
 5395exc_desc(jpl_datum_to_type,is_cyclic(Term),
 5396         jpl_call/4, % I don't know why, but the tests expect jpl_call/4 here
 5397         type_error(acyclic,Term),
 5398         'must be acyclic').
 5399
 5400% ---
 5401
 5402exc_desc(jpl_type_to_class,arg1_is_var,
 5403         jpl_type_to_class/2,
 5404         instantiation_error,
 5405	 '1st arg must be bound to a JPL type').
 5406
 5407% ---
 5408
 5409exc_desc(check_lib,lib_not_found(Name,Msg),
 5410         check_lib/2,
 5411         existence_error(library,Name),
 5412         Msg).
 5413
 5414
 5415         /*******************************
 5416         *      Initialize JVM          *
 5417         *******************************/
 5418
 5419:- initialization(setup_jvm, now).        % must be ready before export