2:- module(jpl,
    3	  [ jpl_get_default_jvm_opts/1,
    4	    jpl_set_default_jvm_opts/1,
    5	    jpl_get_actual_jvm_opts/1,
    6	    jpl_pl_lib_version/1,
    7	    jpl_c_lib_version/1,
    8	    jpl_new/3,
    9	    jpl_call/4,
   10	    jpl_get/3,
   11	    jpl_set/3,
   12	    jpl_servlet_byref/3,
   13	    jpl_servlet_byval/3,
   14	    jpl_class_to_classname/2,
   15	    jpl_class_to_type/2,
   16	    jpl_classname_to_class/2,
   17	    jpl_classname_to_type/2,
   18	    jpl_datum_to_type/2,
   19	    jpl_false/1,
   20	    jpl_is_class/1,
   21	    jpl_is_false/1,
   22	    jpl_is_null/1,
   23	    jpl_is_object/1,
   24	    jpl_is_object_type/1,
   25	    jpl_is_ref/1,
   26	    jpl_is_true/1,
   27	    jpl_is_type/1,
   28	    jpl_is_void/1,
   29	    jpl_null/1,
   30	    jpl_object_to_class/2,
   31	    jpl_object_to_type/2,
   32	    jpl_primitive_type/1,
   33	    jpl_ref_to_type/2,
   34	    jpl_true/1,
   35	    jpl_type_to_class/2,
   36	    jpl_type_to_classname/2,
   37	    jpl_void/1,
   38	    jpl_array_to_length/2,
   39	    jpl_array_to_list/2,
   40	    jpl_datums_to_array/2,
   41	    jpl_enumeration_element/2,
   42	    jpl_enumeration_to_list/2,
   43	    jpl_hashtable_pair/2,
   44	    jpl_iterator_element/2,
   45	    jpl_list_to_array/2,
   46	    jpl_terms_to_array/2,
   47	    jpl_map_element/2,
   48	    jpl_set_element/2
   49	  ]).   50
   51
   52/*  $Id$
   53
   54	Part of JPL -- SWI-Prolog/Java interface
   55
   56	Author:        Paul Singleton, Fred Dushin and Jan Wielemaker
   57	E-mail:        paul@jbgb.com
   58	WWW:           http://www.swi-prolog.org
   59	Copyright (C): 1985-2004, Paul Singleton
   60
   61	This program is free software; you can redistribute it and/or
   62	modify it under the terms of the GNU General Public License
   63	as published by the Free Software Foundation; either version 2
   64	of the License, or (at your option) any later version.
   65
   66	This program is distributed in the hope that it will be useful,
   67	but WITHOUT ANY WARRANTY; without even the implied warranty of
   68	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   69	GNU General Public License for more details.
   70
   71	You should have received a copy of the GNU Lesser General Public
   72	License along with this library; if not, write to the Free Software
   73	Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   74
   75	As a special exception, if you link this library with other files,
   76	compiled with a Free Software compiler, to produce an executable, this
   77	library does not by itself cause the resulting executable to be covered
   78	by the GNU General Public License. This exception does not however
   79	invalidate any other reasons why the executable file might be covered by
   80	the GNU General Public License.
   81	
   82	
   83	IKVM Version 666
   84*/
   85
   86:- use_module(library(lists)).   87
   88% suppress debugging this library
   89:- set_prolog_flag(generate_debug_info, true).   90
   91%------------------------------------------------------------------------------
   92
   93jpl_get_default_jvm_opts( Opts) :-
   94	jni_get_default_jvm_opts( Opts).
   95
   96%------------------------------------------------------------------------------
   97
   98jpl_set_default_jvm_opts( Opts) :-
   99	is_list( Opts),
  100	length( Opts, N),
  101	jni_set_default_jvm_opts( N, Opts).
  102
  103%------------------------------------------------------------------------------
  104
  105jpl_get_actual_jvm_opts( Opts) :-
  106	jni_get_actual_jvm_opts( Opts).
  107
  108%------------------------------------------------------------------------------
  109
  110jpl_assert( Fact) :-
  111	(   jpl_assert_policy( Fact, yes)
  112	->  assert( Fact)
  113	;   true
  114	).
  115
  116%------------------------------------------------------------------------------
  117
  118jpl_assert_policy( jpl_field_spec_cache(_,_,_,_,_,_), yes).
  119jpl_assert_policy( jpl_method_spec_cache(_,_,_,_,_,_,_,_), yes).
  120jpl_assert_policy( jpl_class_tag_type_cache(_,_), yes).
  121jpl_assert_policy( jpl_classname_type_cache(_,_), yes).
  122jpl_assert_policy( jpl_iref_type_cache(_,_), no).   % must correspond to JPL_CACHE_TYPE_OF_REF in jpl.c
  123
  124jpl_assert_policy( jpl_field_spec_is_cached(_), YN) :-
  125	jpl_assert_policy( jpl_field_spec_cache(_,_,_,_,_,_), YN).
  126jpl_assert_policy( jpl_method_spec_is_cached(_), YN) :-
  127	jpl_assert_policy( jpl_method_spec_cache(_,_,_,_,_,_,_,_), YN).
  128
  129%------------------------------------------------------------------------------
  130
  131% jpl_tidy_iref_type_cache( +Iref) :-
  132%   delete the cached type info, if any, under Iref;
  133%   called from jpl.c's jni_free_iref() via jni_tidy_iref_type_cache()
  134
  135jpl_tidy_iref_type_cache( Iref) :-
  136  % write( '[decaching types for iref='), write( Iref), write( ']'), nl,
  137	retractall( jpl_iref_type_cache(Iref,_)),
  138	true.
  139
  140%------------------------------------------------------------------------------
  141
  142% jpl_call(+X, +MethodSpec, +Params, -Result) :-
  143%   X should be:
  144%     an object reference
  145%       (for static or instance methods)
  146%     a classname, descriptor or type
  147%       (for static methods of the denoted class)
  148%
  149%   MethodSpec should be:
  150%     a method name (as an atom)
  151%       (may involve dynamic overload resolution based on inferred types of params)
  152%
  153%   Params should be:
  154%     a proper list (perhaps empty) of suitable actual parameters for the named method
  155%
  156%   finally, an attempt will be made to unify Result with the returned result
  157
  158jpl_call(X, Mspec, Params, R) :-
  159	(   jpl_object_to_type(X, Type)         % the usual case (goal fails safely if X is var or rubbish)
  160	->  Obj = X,
  161	    Kind = instance
  162	;   var(X)
  163	->  throw(error(instantiation_error,
  164			context(jpl_call/4,
  165				'1st arg must be bound to an object, classname, descriptor or type')))
  166	;   atom(X)
  167	->  (   jpl_classname_to_type( X, Type)     % does this attempt to load the class?
  168	->  (   jpl_type_to_class( Type, ClassObj)
  169	    ->  Kind = static
  170	    ;   throw(error(existence_error(class,X),
  171			context(jpl_call/4,
  172				'the named class cannot be found')))
  173	    )
  174	;   throw(error(type_error(class_name_or_descriptor,X),
  175		    context(jpl_call/4, '1st arg must be an object, classname, descriptor or type')))
  176	)
  177	;   X = class(_,_)
  178	->  Type = X,
  179	    jpl_type_to_class( Type, ClassObj),
  180	    Kind = static
  181	;   X = array(_)
  182	->  throw(error(type_error(object_or_class,X),
  183		    context(jpl_call/4, 'cannot call a static method of an array type, as none exists')))
  184	;   throw(error(domain_error(object_or_class,X),
  185		    context(jpl_call/4,
  186			    '1st arg must be an object, classname, descriptor or type')))
  187	),
  188	(   atom(Mspec)                 % the usual case, i.e. a method name
  189	->  true
  190	;   var(Mspec)
  191	->  throw(error(instantiation_error,
  192		    context(jpl_call/4, '2nd arg must be an atom naming a public method of the class or object')))
  193	;   throw(error(type_error(method_name,Mspec),
  194		    context(jpl_call/4, '2nd arg must be an atom naming a public method of the class or object')))
  195	),
  196	(   is_list(Params)
  197	->  (   catch(
  198		jpl_datums_to_types(Params, Taps),
  199		error(type_error(acyclic,Te),context(jpl_datum_to_type/2,Msg)),
  200		throw(error(type_error(acyclic,Te),context(jpl_call/4,Msg)))
  201	    )
  202	->  true
  203	;   throw(error(type_error(method_params,Params),
  204		    context(jpl_call/4, 'not all actual parameters are convertible to Java values or references')))
  205	),
  206	length( Params, A)
  207	;   var(Params)
  208	->  throw(error(instantiation_error,
  209		    context(jpl_call/4, '3rd arg must be a proper list of actual parameters for the named method')))
  210	;   throw(error(type_error(method_params,Params),
  211		    context(jpl_call/4, '3rd arg must be a proper list of actual parameters for the named method')))
  212	),
  213	(   Kind == instance
  214	->  jpl_call_instance(Type, Obj, Mspec, Params, Taps, A, Rx)
  215	;   jpl_call_static(Type, ClassObj, Mspec, Params, Taps, A, Rx)
  216	),
  217	(   nonvar(R),
  218	    R = {Term}  % yucky way of requesting Term->term conversion
  219	->  (   jni_jref_to_term( Rx, TermX)    % fails if Rx isn't a JRef to a jpl.Term
  220	->  Term = TermX
  221	;   throw(error(type_error,
  222			context(jpl_call/4, 'result is not a jpl.Term instance as required')))
  223	)
  224	;   R = Rx
  225	).
  226
  227%------------------------------------------------------------------------------
 jpl_call_instance(+ObjectType, +Object, +MethodName, Params, ActualParamTypes, Arity, -Result)
call 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
  237jpl_call_instance(Type, Obj, Mname, Params, Taps, A, Rx) :-
  238	findall(                    % get remaining details of all accessible methods of Obj's class (as denoted by Type)
  239	z5(I,Mods,MID,Tr,Tfps),
  240	jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
  241	Z5s
  242	),
  243	(   Z5s = []
  244	->  throw(error(existence_error(method,Mname/A),
  245		    context(jpl_call/4,
  246			    'the class or object has no public methods with the given name and quantity of parameters')))
  247	;   findall(
  248	    z5(I,Mods,MID,Tr,Tfps),             % those to which Params is assignable
  249	    (   member(z5(I,Mods,MID,Tr,Tfps), Z5s),
  250		jpl_types_fit_types(Taps, Tfps) % assignability test: actual param types "fit" formal param types
  251	    ),
  252	    Z5sA                                % Params-assignable methods
  253	),
  254	(   Z5sA == []
  255	->  throw(error(type_error(method_params,Params),
  256			context(jpl_call/4,
  257				'the actual parameters are not assignable to the formal parameters of any of the named methods')))
  258
  259	;   Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
  260	->  true                                % exactly one applicable method
  261	;   jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
  262	->  true                                % exactly one most-specific applicable method
  263	;   throw(error(existence_error(most_specific_method,Mname/Params),
  264			context(jpl_call/4,
  265				'more than one most-specific method is found for the actual parameters (this should not happen)')))
  266	)
  267	),
  268	(   member(static, Mods)                                        % if the chosen method is static
  269	->  jpl_object_to_class(Obj, ClassObj),                         % get a java.lang.Class instance which personifies Obj's class
  270	jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx) % call static method w.r.t. associated Class object
  271	;   jpl_call_instance_method(Tr, Obj, MID, Tfps, Params, Rx)    % else call (non-static) method w.r.t. object itself
  272	).
  273
  274%------------------------------------------------------------------------------
 jpl_call_static(+ClassType, +ClassObject, +MethodName, Params, ActualParamTypes, Arity, -Result)
call 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
  285jpl_call_static(Type, ClassObj, Mname, Params, Taps, A, Rx) :-
  286	findall(                    % get all accessible static methods of the class denoted by Type and ClassObj
  287	z5(I,Mods,MID,Tr,Tfps),
  288	(   jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
  289	    member(static, Mods)
  290	),
  291	Z5s
  292	),
  293	(   Z5s = []
  294	->  throw(error(existence_error(method,Mname/A),
  295		    context(jpl_call/4,
  296			    'the class has no public static methods with the given name and quantity of parameters')))
  297	;   findall(
  298	    z5(I,Mods,MID,Tr,Tfps),
  299	    (   member(z5(I,Mods,MID,Tr,Tfps), Z5s),
  300		jpl_types_fit_types(Taps, Tfps) % assignability test: actual param types "fit" formal param types
  301	    ),
  302	    Z5sA                                % Params-assignable methods
  303	),
  304	(   Z5sA == []
  305	->  throw(error(type_error(method_params,Params),
  306			context(jpl_call/4,
  307				'the actual parameters are not assignable to the formal parameters of any of the named methods')))
  308	;   Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
  309	->  true                % exactly one applicable method
  310	;   jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
  311	->  true                % exactly one most-specific applicable method
  312	;   throw(error(existence_error(most_specific_method,Mname/Params),
  313			context(jpl_call/4,
  314				'more than one most-specific method is found for the actual parameters (this should not happen)')))
  315	)
  316	),
  317	jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx).
  318
  319%------------------------------------------------------------------------------
  320
  321% jpl_call_instance_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result) :-
  322
  323jpl_call_instance_method(void, Class, MID, Tfps, Ps, R) :-
  324	jCallVoidMethod(Class, MID, Tfps, Ps),
  325	jpl_void(R).
  326
  327jpl_call_instance_method(boolean, Class, MID, Tfps, Ps, R) :-
  328	jCallBooleanMethod(Class, MID, Tfps, Ps, R).
  329
  330jpl_call_instance_method(byte, Class, MID, Tfps, Ps, R) :-
  331	jCallByteMethod(Class, MID, Tfps, Ps, R).
  332
  333jpl_call_instance_method(char, Class, MID, Tfps, Ps, R) :-
  334	jCallCharMethod(Class, MID, Tfps, Ps, R).
  335
  336jpl_call_instance_method(short, Class, MID, Tfps, Ps, R) :-
  337	jCallShortMethod(Class, MID, Tfps, Ps, R).
  338
  339jpl_call_instance_method(int, Class, MID, Tfps, Ps, R) :-
  340	jCallIntMethod(Class, MID, Tfps, Ps, R).
  341
  342jpl_call_instance_method(long, Class, MID, Tfps, Ps, R) :-
  343	jCallLongMethod(Class, MID, Tfps, Ps, R).
  344
  345jpl_call_instance_method(float, Class, MID, Tfps, Ps, R) :-
  346	jCallFloatMethod(Class, MID, Tfps, Ps, R).
  347
  348jpl_call_instance_method(double, Class, MID, Tfps, Ps, R) :-
  349	jCallDoubleMethod(Class, MID, Tfps, Ps, R).
  350
  351jpl_call_instance_method(array(_), Class, MID, Tfps, Ps, R) :-
  352	jCallObjectMethod(Class, MID, Tfps, Ps, R).
  353
  354jpl_call_instance_method(class(_,_), Class, MID, Tfps, Ps, R) :-
  355	jCallObjectMethod(Class, MID, Tfps, Ps, R).
  356
  357%------------------------------------------------------------------------------
  358
  359% jpl_call_static_method(+Type, +ClassObject, +MethodID, +FormalParamTypes, +Params, -Result) :-
  360
  361jpl_call_static_method(void, Class, MID, Tfps, Ps, R) :-
  362	jCallStaticVoidMethod(Class, MID, Tfps, Ps),
  363	jpl_void(R).
  364
  365jpl_call_static_method(boolean, Class, MID, Tfps, Ps, R) :-
  366	jCallStaticBooleanMethod(Class, MID, Tfps, Ps, R).
  367
  368jpl_call_static_method(byte, Class, MID, Tfps, Ps, R) :-
  369	jCallStaticByteMethod(Class, MID, Tfps, Ps, R).
  370
  371jpl_call_static_method(char, Class, MID, Tfps, Ps, R) :-
  372	jCallStaticCharMethod(Class, MID, Tfps, Ps, R).
  373
  374jpl_call_static_method(short, Class, MID, Tfps, Ps, R) :-
  375	jCallStaticShortMethod(Class, MID, Tfps, Ps, R).
  376
  377jpl_call_static_method(int, Class, MID, Tfps, Ps, R) :-
  378	jCallStaticIntMethod(Class, MID, Tfps, Ps, R).
  379
  380jpl_call_static_method(long, Class, MID, Tfps, Ps, R) :-
  381	jCallStaticLongMethod(Class, MID, Tfps, Ps, R).
  382
  383jpl_call_static_method(float, Class, MID, Tfps, Ps, R) :-
  384	jCallStaticFloatMethod(Class, MID, Tfps, Ps, R).
  385
  386jpl_call_static_method(double, Class, MID, Tfps, Ps, R) :-
  387	jCallStaticDoubleMethod(Class, MID, Tfps, Ps, R).
  388
  389jpl_call_static_method(array(_), Class, MID, Tfps, Ps, R) :-
  390	jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
  391
  392jpl_call_static_method(class(_,_), Class, MID, Tfps, Ps, R) :-
  393	jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
  394
  395%------------------------------------------------------------------------------
  396
  397%type   jpl_fergus_find_candidate(list(T), T, T, list(T))
  398
  399jpl_fergus_find_candidate([], Candidate, Candidate, []).
  400
  401jpl_fergus_find_candidate([X|Xs], Candidate0, Candidate, Rest) :-
  402	(   jpl_fergus_greater(X, Candidate0)
  403	->  Candidate1 = X,
  404	Rest = [Candidate0|Rest1]
  405	;   Candidate1 = Candidate0,
  406	Rest = [X|Rest1]
  407	),
  408	jpl_fergus_find_candidate(Xs, Candidate1, Candidate, Rest1).
  409
  410%------------------------------------------------------------------------------
  411
  412jpl_fergus_greater(z5(_,_,_,_,Tps1), z5(_,_,_,_,Tps2)) :-
  413	jpl_types_fit_types(Tps1, Tps2).
  414jpl_fergus_greater(z3(_,_,Tps1), z3(_,_,Tps2)) :-
  415	jpl_types_fit_types(Tps1, Tps2).
  416
  417%------------------------------------------------------------------------------
  418
  419%type   jpl_fergus_is_the_greatest(list(T), T)
 jpl_fergus_is_the_greatest(Xs, GreatestX)
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
  429jpl_fergus_is_the_greatest([X|Xs], Greatest) :-
  430	jpl_fergus_find_candidate(Xs, X, Greatest, Rest),
  431	forall(
  432	member(R, Rest),
  433	jpl_fergus_greater(Greatest, R)
  434	).
  435
  436%------------------------------------------------------------------------------
 jpl_get(+X, +Fspec, -V)
X can be:

Fspec can be:

finally, an attempt will be made to unify V with the retrieved value

  459jpl_get(X, Fspec, V) :-
  460	(   jpl_object_to_type(X, Type)
  461	->  Obj = X,
  462	    jpl_get_instance( Type, Type, Obj, Fspec, Vx)   % pass Type twice for FAI
  463	;   var(X)
  464	->  throw(error(instantiation_error,
  465		    context(jpl_get/3,
  466			    '1st arg must be bound to an object, classname, descriptor or type')))
  467	;   jpl_is_type(X)          % e.g. class([java,lang],['String']), array(int)
  468	->  Type = X,
  469	    (   jpl_type_to_class(Type, ClassObj)
  470	    ->  jpl_get_static( Type, ClassObj, Fspec, Vx)
  471	    ;   jpl_type_to_classname( Type, Classname),
  472		throw(error(existence_error(class,Classname),
  473			    context(jpl_get/3,
  474				    'the named class cannot be found')))
  475	    )
  476	;   atom(X)
  477	->  (   jpl_classname_to_type( X, Type)     % does this attempt to load the class?
  478	    ->  (   jpl_type_to_class( Type, ClassObj)
  479		->  jpl_get_static( Type, ClassObj, Fspec, Vx)
  480		;   throw(error(existence_error(class,X),
  481				context(jpl_get/3,
  482					'the named class cannot be found')))
  483		)
  484	    ;   throw(error(type_error(class_name_or_descriptor,X),
  485			    context(jpl_get/3, '1st arg must be an object, classname, descriptor or type')))
  486	    )
  487
  488	;   throw(error(domain_error(object_or_class,X),
  489		    context(jpl_get/3,
  490			    '1st arg must be bound to an object, classname, descriptor or type')))
  491	),
  492	(   nonvar(V),
  493	    V = {Term}  % yucky way of requesting Term->term conversion
  494	->  (   jni_jref_to_term( Vx, TermX)    % fails if Rx is not a JRef to a jpl.Term
  495	    ->  Term = TermX
  496	    ;   throw(error(type_error,
  497			    context(jpl_call/4, 'result is not a jpl.Term instance as required')))
  498	    )
  499	;   V = Vx
  500	).
  501
  502%------------------------------------------------------------------------------
 jpl_get_static(+Type, +ClassObject, +FieldName, -Value)
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
  511jpl_get_static(Type, ClassObj, Fname, Vx) :-
  512	(   atom(Fname)             % assume it's a field name
  513	->  true
  514	;   var(Fname)
  515	->  throw(error(instantiation_error,
  516		    context(jpl_get/3, '2nd arg must be bound to an atom naming a public field of the class')))
  517	;   throw(error(type_error(field_name,Fname),
  518		    context(jpl_get/3, '2nd arg must be an atom naming a public field of the class')))
  519	),
  520  % get static fields of the denoted class
  521	findall(
  522	z4(I,Mods,FID,Tf),
  523	(   jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
  524	    member(static, Mods)
  525	),
  526	Z4s
  527	),
  528	(   Z4s = []
  529	->  throw(error(existence_error(field,Fname),
  530		    context(jpl_get/3,
  531			    'the class or object has no public static field with the given name')))
  532	;   Z4s = [z4(I,_Mods,FID,Tf)]
  533	->  jpl_get_static_field(Tf, ClassObj, FID, Vx)
  534	;   throw(error(existence_error(unique_field,Fname),
  535		    context(jpl_get/3,
  536			    'more than one field is found with the given name')))
  537	).
  538
  539%------------------------------------------------------------------------------
  540
  541% jpl_get_instance(+Type, +Type, +Object, +FieldSpecifier, -Value) :-
  542
  543jpl_get_instance(class(_,_), Type, Obj, Fname, Vx) :-
  544	(   atom(Fname)                 % the usual case
  545	->  true
  546	;   var(Fname)
  547	->  throw(error(instantiation_error,
  548		    context(jpl_get/3, '2nd arg must be bound to an atom naming a public field of the class or object')))
  549	;   throw(error(type_error(field_name,Fname),
  550		    context(jpl_get/3, '2nd arg must be an atom naming a public field of the class or object')))
  551	),
  552	findall(z4(I,Mods,FID,Tf),
  553		jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
  554		Z4s),
  555	(   Z4s = []
  556	->  throw(error(existence_error(field,Fname),
  557			context(jpl_get/3,
  558				'the class or object has no public field with the given name')))
  559	;   Z4s = [z4(I,Mods,FID,Tf)]
  560	->  (   member(static, Mods)
  561	    ->  jpl_object_to_class(Obj, ClassObj),
  562		jpl_get_static_field(Tf, ClassObj, FID, Vx)
  563	    ;   jpl_get_instance_field(Tf, Obj, FID, Vx)
  564	    )
  565	;   throw(error(existence_error(unique_field,Fname),
  566		    context(jpl_get/3,
  567			    'more than one field is found with the given name')))
  568	).
  569
  570jpl_get_instance(array(ElementType), _, Array, Fspec, Vx) :-
  571	(   var(Fspec)
  572	->  throw(error(instantiation_error,
  573			context(jpl_get/3,
  574				'when 1st arg is an array, 2nd arg must be bound to an index, an index range, or ''length''')))
  575	;   integer(Fspec)
  576	->  (   Fspec < 0       % lo bound check
  577	    ->  throw(error(domain_error(array_index,Fspec),
  578			    context(jpl_get/3,
  579				    'when 1st arg is an array, integral 2nd arg must be non-negative')))
  580	    ;   jGetArrayLength(Array, Len),
  581		Fspec >= Len    % hi bound check
  582	    ->  throw(error(domain_error(array_index,Fspec),
  583			    context(jpl_get/3,
  584				    'when 1st arg is an array, integral 2nd arg must not exceed upper bound of array')))
  585	    ;   jpl_get_array_element(ElementType, Array, Fspec, Vx)
  586	    )
  587	;   Fspec = N-M     % NB should we support e.g. 3-2 -> [] ?
  588	->  (   integer(N),
  589	        integer(M)
  590	    ->  (   N >= 0,
  591		    M >= N
  592		->  jGetArrayLength(Array, Len),
  593		    (   N >= Len
  594		    ->  throw(error(domain_error(array_index_range,N-M),
  595				    context(jpl_get/3,
  596					    'lower bound of array index range must not exceed upper bound of array')))
  597		    ;   M >= Len
  598		    ->  throw(error(domain_error(array_index_range,N-M),
  599				    context(jpl_get/3,
  600					    'upper bound of array index range must not exceed upper bound of array')))
  601		    ;   jpl_get_array_elements(ElementType, Array, N, M, Vx)
  602		    )
  603		;   throw(error(domain_error(array_index_range,N-M),
  604				context(jpl_get/3,
  605					'array index range must be a non-decreasing pair of non-negative integers')))
  606		)
  607	    ;   throw(error(type_error(array_index_range,N-M),
  608			    context(jpl_get/3,
  609				    'array index range must be a non-decreasing pair of non-negative integers')))
  610	    )
  611	;   atom(Fspec)
  612	->  (   Fspec == length             % special-case for this solitary array "method"
  613	    ->  jGetArrayLength(Array, Vx)
  614	    ;   throw(error(domain_error(array_field_name,Fspec),
  615			    context(jpl_get/3,
  616				    'the array has no public field with the given name')))
  617	    )
  618	;   throw(error(type_error(array_lookup_spec,Fspec),
  619			context(jpl_get/3,
  620				'when 1st arg is an array, 2nd arg must be an index, an index range, or ''length''')))
  621	).
  622
  623%------------------------------------------------------------------------------
 jpl_get_array_element(+ElementType, +Array, +Index, -Vc)
Array is (a reference to) an 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 ...
  634jpl_get_array_element(Type, Array, Index, Vc) :-
  635	(   (   Type = class(_,_)
  636	    ;   Type = array(_)
  637	    )
  638	->  jGetObjectArrayElement(Array, Index, Vr)
  639	;   jpl_primitive_type(Type)
  640	->  jni_type_to_xput_code(Type, Xc),
  641	    jni_alloc_buffer(Xc, 1, Bp),		% one-element buf for a Type
  642	    jpl_get_primitive_array_region(Type, Array, Index, 1, Bp),
  643	    jni_fetch_buffer_value(Bp, 0, Vr, Xc),	% zero-th element
  644	    jni_free_buffer(Bp)
  645	),
  646	Vr = Vc.    % redundant since Vc is always (?) unbound at call
  647
  648%------------------------------------------------------------------------------
 jpl_get_array_elements(+ElementType, +Array, +N, +M, -Vs)
serves only jpl_get_instance Vs will always be unbound on entry
  654jpl_get_array_elements(ElementType, Array, N, M, Vs) :-
  655	(   (   ElementType = class(_,_)
  656	    ;   ElementType = array(_)
  657	    )
  658	->  jpl_get_object_array_elements(Array, N, M, Vs)
  659	;   jpl_get_primitive_array_elements(ElementType, Array, N, M, Vs)
  660	).
  661
  662%------------------------------------------------------------------------------
  663
  664jpl_get_instance_field(boolean, Obj, FieldID, V) :-
  665	jGetBooleanField(Obj, FieldID, V).
  666jpl_get_instance_field(byte, Obj, FieldID, V) :-
  667	jGetByteField(Obj, FieldID, V).
  668jpl_get_instance_field(char, Obj, FieldID, V) :-
  669	jGetCharField(Obj, FieldID, V).
  670jpl_get_instance_field(short, Obj, FieldID, V) :-
  671	jGetShortField(Obj, FieldID, V).
  672jpl_get_instance_field(int, Obj, FieldID, V) :-
  673	jGetIntField(Obj, FieldID, V).
  674jpl_get_instance_field(long, Obj, FieldID, V) :-
  675	jGetLongField(Obj, FieldID, V).
  676jpl_get_instance_field(float, Obj, FieldID, V) :-
  677	jGetFloatField(Obj, FieldID, V).
  678jpl_get_instance_field(double, Obj, FieldID, V) :-
  679	jGetDoubleField(Obj, FieldID, V).
  680jpl_get_instance_field(class(_,_), Obj, FieldID, V) :-
  681	jGetObjectField(Obj, FieldID, V).
  682jpl_get_instance_field(array(_), Obj, FieldID, V) :-
  683	jGetObjectField(Obj, FieldID, V).
  684
  685%------------------------------------------------------------------------------
 jpl_get_object_array_elements(+Array, +LoIndex, +HiIndex, -Vcs)
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
  696jpl_get_object_array_elements(Array, Lo, Hi, Vcs) :-
  697	(   Lo =< Hi
  698	->  Vcs = [Vc|Vcs2],
  699	    jGetObjectArrayElement(Array, Lo, Vc),
  700	    Next is Lo+1,
  701	    jpl_get_object_array_elements(Array, Next, Hi, Vcs2)
  702	;   Vcs = []
  703	).
  704
  705%------------------------------------------------------------------------------
 jpl_get_primitive_array_elements(+ElementType, +Array, +LoIndex, +HiIndex, -Vcs)
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
  714jpl_get_primitive_array_elements(ElementType, Array, Lo, Hi, Vcs) :-
  715	Size is Hi-Lo+1,
  716	(   Size == 0
  717	->  Vcs = []
  718	;   jni_type_to_xput_code(ElementType, Xc),
  719	    jni_alloc_buffer(Xc, Size, Bp),
  720	    jpl_get_primitive_array_region(ElementType, Array, Lo, Size, Bp),
  721	    jpl_primitive_buffer_to_array(ElementType, Xc, Bp, 0, Size, Vcs),
  722	    jni_free_buffer(Bp)
  723	).
  724
  725%------------------------------------------------------------------------------
  726
  727jpl_get_primitive_array_region(boolean, Array, Lo, S, I) :-
  728	jGetBooleanArrayRegion(Array, Lo, S, jbuf(I,boolean)).
  729jpl_get_primitive_array_region(byte, Array, Lo, S, I) :-
  730	jGetByteArrayRegion(Array, Lo, S, jbuf(I,byte)).
  731jpl_get_primitive_array_region(char, Array, Lo, S, I) :-
  732	jGetCharArrayRegion(Array, Lo, S, jbuf(I,char)).
  733jpl_get_primitive_array_region(short, Array, Lo, S, I) :-
  734	jGetShortArrayRegion(Array, Lo, S, jbuf(I,short)).
  735jpl_get_primitive_array_region(int, Array, Lo, S, I) :-
  736	jGetIntArrayRegion(Array, Lo, S, jbuf(I,int)).
  737jpl_get_primitive_array_region(long, Array, Lo, S, I) :-
  738	jGetLongArrayRegion(Array, Lo, S, jbuf(I,long)).
  739jpl_get_primitive_array_region(float, Array, Lo, S, I) :-
  740	jGetFloatArrayRegion(Array, Lo, S, jbuf(I,float)).
  741jpl_get_primitive_array_region(double, Array, Lo, S, I) :-
  742	jGetDoubleArrayRegion(Array, Lo, S, jbuf(I,double)).
  743
  744%------------------------------------------------------------------------------
  745
  746jpl_get_static_field(boolean, Array, FieldID, V) :-
  747	jGetStaticBooleanField(Array, FieldID, V).
  748jpl_get_static_field(byte, Array, FieldID, V) :-
  749	jGetStaticByteField(Array, FieldID, V).
  750jpl_get_static_field(char, Array, FieldID, V) :-
  751	jGetStaticCharField(Array, FieldID, V).
  752jpl_get_static_field(short, Array, FieldID, V) :-
  753	jGetStaticShortField(Array, FieldID, V).
  754jpl_get_static_field(int, Array, FieldID, V) :-
  755	jGetStaticIntField(Array, FieldID, V).
  756jpl_get_static_field(long, Array, FieldID, V) :-
  757	jGetStaticLongField(Array, FieldID, V).
  758jpl_get_static_field(float, Array, FieldID, V) :-
  759	jGetStaticFloatField(Array, FieldID, V).
  760jpl_get_static_field(double, Array, FieldID, V) :-
  761	jGetStaticDoubleField(Array, FieldID, V).
  762jpl_get_static_field(class(_,_), Array, FieldID, V) :-
  763	jGetStaticObjectField(Array, FieldID, V).
  764jpl_get_static_field(array(_), Array, FieldID, V) :-
  765	jGetStaticObjectField(Array, FieldID, V).
  766
  767%------------------------------------------------------------------------------
 jpl_new(+X, +Params, -V)
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 {Term} then we attempt to convert a new jpl.Term instance to a corresponding term; this is of little obvious use here, but is consistent with jpl_call/4 and jpl_get/3

  799jpl_new(X, Params, V) :-
  800	(   var(X)
  801	->  throw(error(instantiation_error,
  802		    context(jpl_new/3,
  803			    '1st arg must be bound to a classname, descriptor or object type')))
  804	;   jpl_is_type(X)                  % NB only class(_,_) or array(_)
  805	->  Type = X
  806	;   atom(X)                 % e.g. 'java.lang.String', '[L', 'boolean'
  807	->  (   jpl_classname_to_type(X, Type)
  808	    ->  true
  809	    ;   throw(error(domain_error(classname,X),
  810			    context(jpl_new/3,
  811				    'if 1st arg is an atom, it must be a classname or descriptor')))
  812	    )
  813	;   throw(error(type_error(instantiable,X),
  814			context(jpl_new/3,
  815				'1st arg must be a classname, descriptor or object type')))
  816	),
  817	jpl_new_1(Type, Params, Vx),
  818	(   nonvar(V),
  819	    V = {Term}  % yucky way of requesting Term->term conversion
  820	->  (   jni_jref_to_term( Vx, TermX)    % fails if Rx is not a JRef to a jpl.Term
  821	    ->  Term = TermX
  822	    ;   throw(error(type_error,
  823			    context(jpl_call/4, 'result is not a jpl.Term instance as required')))
  824	    )
  825	;   V = Vx
  826	).
  827
  828%------------------------------------------------------------------------------
  829
  830% jpl_new_1(+Tx, +Params, -Vx) :-
  831%   (serves only jpl_new/3)
  832%
  833%   Tx can be:
  834%     a class(_,_) or array(_) type;
  835%
  836%   Params must be:
  837%     a proper list of constructor parameters
  838%
  839%   at exit, Vx is bound to a JPL reference to a new, initialised instance of Tx
  840
  841jpl_new_1(class(Ps,Cs), Params, Vx) :-
  842	!,                                      % green (see below)
  843	Tx = class(Ps,Cs),
  844	(   var(Params)
  845	->  throw(error(instantiation_error,
  846		    context(jpl_new/3,
  847			    '2nd arg must be a proper list of valid parameters for a constructor')))
  848	;   \+ is_list(Params)
  849	->  throw(error(type_error(list,Params),
  850		    context(jpl_new/3,
  851			    '2nd arg must be a proper list of valid parameters for a constructor')))
  852	;   true
  853	),
  854	length(Params, A),          % the "arity" of the required constructor
  855	jpl_type_to_class(Tx, Cx),  % throws Java exception if class is not found
  856	N = '<init>',               % JNI's constructor naming convention for GetMethodID()
  857	Tr = void,                  % all constructors have this return "type"
  858	findall(
  859	z3(I,MID,Tfps),
  860	jpl_method_spec(Tx, I, N, A, _Mods, MID, Tr, Tfps), % cached
  861	Z3s
  862	),
  863	(   Z3s == []               % no constructors which require the given qty of parameters?
  864	->  jpl_type_to_classname( Tx, Cn),
  865	(   jpl_call( Cx, isInterface, [], @(true))
  866	->  throw(error(type_error(concrete_class,Cn),
  867			context(jpl_new/3,
  868				'cannot create instance of an interface')))
  869	;   throw(error(existence_error(constructor,Cn/A),
  870			context(jpl_new/3,
  871				'no constructor found with the corresponding quantity of parameters')))
  872	)
  873	;   (   catch(
  874		jpl_datums_to_types(Params, Taps),  % infer actual parameter types
  875		error(type_error(acyclic,Te),context(jpl_datum_to_type/2,Msg)),
  876		throw(error(type_error(acyclic,Te),context(jpl_new/3,Msg)))
  877	    )
  878	->  true
  879	;   throw(error(domain_error(list(jpl_datum),Params),
  880			context(jpl_new/3,
  881				'one or more of the actual parameters is not a valid representation of any Java value or object')))
  882	),
  883	findall(
  884	    z3(I,MID,Tfps),                 % select constructors to which actual parameters are assignable
  885	    (   member(z3(I,MID,Tfps), Z3s),
  886		jpl_types_fit_types(Taps, Tfps) % assignability test: actual parameter types "fit" formal parameter types?
  887	    ),
  888	    Z3sA
  889	),
  890	(   Z3sA == []                      % no type-assignable constructors?
  891	->  (   Z3s = [_]
  892	    ->  throw(error(existence_error(constructor,Tx/A),
  893			context(jpl_new/3,
  894				'the actual parameters are not assignable to the formal parameter types of the only constructor which takes this qty of parameters')))
  895	    ;   throw(error(type_error(constructor_args,Params),
  896			context(jpl_new/3,
  897				'the actual parameters are not assignable to the formal parameter types of any of the constructors which take this qty of parameters')))
  898	    )
  899	;   Z3sA = [z3(I,MID,Tfps)]
  900	->  true
  901	;   jpl_z3s_to_most_specific_z3(Z3sA, z3(I,MID,Tfps))
  902	->  true
  903	;   throw(error(type_error(constructor_params,Params),
  904			context(jpl_new/3,
  905				'more than one most-specific matching constructor (shouldn''t happen)')))
  906	)
  907	),
  908	catch(
  909	jNewObject(Cx, MID, Tfps, Params, Vx),
  910	error(java_exception(@(_)), 'java.lang.InstantiationException'),
  911	(   jpl_type_to_classname( Tx, Cn),
  912	    throw(error(type_error(concrete_class,Cn),
  913			context(jpl_new/3,
  914				'cannot create instance of an abstract class')))
  915	)
  916	),
  917	jpl_cache_type_of_ref(Tx, Vx).          % since we know it
  918
  919jpl_new_1(array(T), Params, Vx) :-
  920	!,
  921	(   var(Params)
  922	->  throw(error(instantiation_error,
  923		    context(jpl_new/3,
  924			    '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')))
  925	;   integer(Params)         % integer I -> array[0..I-1] of default values
  926	->  (   Params >= 0
  927	->  Len is Params
  928	;   throw(error(domain_error(array_length,Params),
  929		    context(jpl_new/3,
  930			    'when constructing a new array, if the 2nd arg is an integer (denoting the required array length) then it must be non-negative')))
  931	)
  932	;   is_list(Params)     % [V1,..VN] -> array[0..N-1] of respective values
  933	->  length(Params, Len)
  934	),
  935	jpl_new_array(T, Len, Vx), % NB may throw out-of-memory exception
  936	(   nth0(I, Params, Param),     % nmember fails silently when Params is integer
  937	jpl_set(Vx, I, Param),
  938	fail
  939	;   true
  940	),
  941	jpl_cache_type_of_ref(array(T), Vx).   % since we know it
  942
  943jpl_new_1(T, _Params, _Vx) :-       % doomed attempt to create new primitive type instance (formerly a dubious completist feature :-)
  944	jpl_primitive_type(T),
  945	!,
  946	throw(error(domain_error(object_type,T),
  947	    context(jpl_new/3,
  948		    'cannot construct an instance of a primitive type'))).
  949  % (   var(Params)
  950  % ->  throw(error(instantiation_error,
  951  %                 context(jpl_new/3,
  952  %                         'when constructing a new instance of a primitive type, 2nd arg must be bound (to a representation of a suitable value)')))
  953  % ;   Params == []
  954  % ->  jpl_primitive_type_default_value(T, Vx)
  955  % ;   Params = [Param]
  956  % ->  jpl_primitive_type_term_to_value(T, Param, Vx)
  957  % ;   throw(error(domain_error(constructor_args,Params),
  958  %                 context(jpl_new/3,
  959  %                         'when constructing a new instance of a primitive type, 2nd arg must either be an empty list (indicating that the default value of that type is required) or a list containing exactly one representation of a suitable value)')))
  960  % ).
  961
  962jpl_new_1( T, _, _) :-
  963	throw(error(domain_error(jpl_type,T),
  964		    context(jpl_new/3,
  965			    '1st arg must denote a known or plausible type'))).
  966
  967%------------------------------------------------------------------------------
  968
  969% jpl_new_array(+ElementType, +Length, -NewArray) :-
  970
  971jpl_new_array(boolean, Len, A) :-
  972	jNewBooleanArray(Len, A).
  973
  974jpl_new_array(byte, Len, A) :-
  975	jNewByteArray(Len, A).
  976
  977jpl_new_array(char, Len, A) :-
  978	jNewCharArray(Len, A).
  979
  980jpl_new_array(short, Len, A) :-
  981	jNewShortArray(Len, A).
  982
  983jpl_new_array(int, Len, A) :-
  984	jNewIntArray(Len, A).
  985
  986jpl_new_array(long, Len, A) :-
  987	jNewLongArray(Len, A).
  988
  989jpl_new_array(float, Len, A) :-
  990	jNewFloatArray(Len, A).
  991
  992jpl_new_array(double, Len, A) :-
  993	jNewDoubleArray(Len, A).
  994
  995jpl_new_array(array(T), Len, A) :-
  996	jpl_type_to_class(array(T), C),
  997	jNewObjectArray(Len, C, @(null), A).        % initialise each element to null
  998
  999jpl_new_array(class(Ps,Cs), Len, A) :-
 1000	jpl_type_to_class(class(Ps,Cs), C),
 1001	jNewObjectArray(Len, C, @(null), A).
 1002
 1003%------------------------------------------------------------------------------
 1004
 1005% jpl_set(+X, +Fspec, +V) :-
 1006%   basically, sets the Fspec-th field of class or object X to value V
 1007%   iff it is assignable
 1008%
 1009%   X can be:
 1010%     a class instance
 1011%       (for static or non-static fields)
 1012%     an array
 1013%       (for indexed element or subrange assignment)
 1014%     a classname, or a class/2 or array/1 type
 1015%       (for static fields)
 1016%   but not:
 1017%     a String (no fields to retrieve)
 1018%
 1019%   Fspec can be:
 1020%     an atomic field name
 1021%       (overloading through shadowing has yet to be handled properly)
 1022%     an array index I
 1023%       (X must be an array object: V is assigned to X[I])
 1024%     a pair I-J of integers
 1025%       (X must be an array object, V must be a list of values: successive members of V are assigned to X[I..J])
 1026%
 1027%   V must be a suitable value or object
 1028
 1029jpl_set(X, Fspec, V) :-
 1030	(   jpl_object_to_type(X, Type)         % the usual case (test is safe if X is var or rubbish)
 1031	->  Obj = X,
 1032	catch(
 1033	    jpl_set_instance(Type, Type, Obj, Fspec, V),    % first 'Type' is for FAI
 1034	    error(type_error(acyclic,Te),context(jpl_datum_to_type/2,Msg)),
 1035	    throw(error(type_error(acyclic,Te),context(jpl_set/3,Msg)))
 1036	)
 1037	;   var(X)
 1038	->  throw(error(instantiation_error,
 1039		    context(jpl_set/3,
 1040			    '1st arg must be an object, classname, descriptor or type')))
 1041	;   (   atom(X)
 1042	->  (   jpl_classname_to_type(X, Type)          % it's a classname or descriptor...
 1043	    ->  true
 1044	    ;   throw(error(existence_error(class,X),
 1045			context(jpl_set/3,
 1046				'the named class cannot be found')))
 1047	    )
 1048	;   (   X = class(_,_)                          % it's a class type...
 1049	    ;   X = array(_)                            % ...or an array type
 1050	    )
 1051	->  Type = X
 1052	),
 1053	(   jpl_type_to_class( Type, ClassObj)      % ...whose Class object is available
 1054	->  true
 1055	;   jpl_type_to_classname( Type, Classname),
 1056	    throw(error(existence_error(class,Classname),
 1057		    context(jpl_set/3,
 1058			    'the class cannot be found')))
 1059	)
 1060	->  catch(
 1061	    jpl_set_static(Type, ClassObj, Fspec, V),
 1062	    error(type_error(acyclic,Te),context(jpl_datum_to_type/2,Msg)),
 1063	    throw(error(type_error(acyclic,Te),context(jpl_set/3,Msg)))
 1064	)
 1065	;   throw(error(domain_error(object_or_class,X),
 1066		    context(jpl_set/3,
 1067			    '1st arg must be an object, classname, descriptor or type')))
 1068	).
 1069
 1070%------------------------------------------------------------------------------
 1071
 1072% jpl_set_instance(+Type, +Type, +ObjectReference, +FieldName, +Value) :-
 1073%   ObjectReference is a JPL reference to a Java object
 1074%   of the class denoted by Type (which is passed twice for first agument indexing);
 1075%   FieldName should name a public, non-final (static or non-static) field of this object,
 1076%   but could be anything, and is validated here;
 1077%   Value should be assignable to the named field, but could be anything, and is validated here
 1078
 1079jpl_set_instance(class(_,_), Type, Obj, Fname, V) :-    % a non-array object
 1080	(   atom(Fname)                 % the usual case
 1081	->  true
 1082	;   var(Fname)
 1083	->  throw(error(instantiation_error,
 1084		    context(jpl_set/3,
 1085			    '2nd arg must be bound to the name of a public, non-final field')))
 1086	;   throw(error(type_error(field_name,Fname),
 1087		    context(jpl_set/3,
 1088			    '2nd arg must be the name of a public, non-final field')))
 1089	),
 1090	findall(
 1091	z4(I,Mods,FID,Tf),
 1092	jpl_field_spec(Type, I, Fname, Mods, FID, Tf),  % public fields of class denoted by Type
 1093	Z4s
 1094	),
 1095	(   Z4s = []
 1096	->  throw(error(existence_error(field,Fname),
 1097		    context(jpl_set/3,
 1098			    'no public fields of the object have this name')))
 1099	;   Z4s = [z4(I,Mods,FID,Tf)]
 1100	->  (   member(final, Mods)
 1101	->  throw(error(permission_error(modify,final_field,Fname),
 1102		    context(jpl_set/3,
 1103			    'cannot assign a value to a final field (actually you could but I''ve decided not to let you)')))
 1104	;   jpl_datum_to_type( V, Tv)
 1105	->  (   jpl_type_fits_type( Tv, Tf)
 1106	    ->  (   member(static, Mods)
 1107		->  jpl_object_to_class(Obj, ClassObj),
 1108		    jpl_set_static_field(Tf, ClassObj, FID, V)
 1109		;   jpl_set_instance_field(Tf, Obj, FID, V)         % oughta be jpl_set_instance_field?
 1110		)
 1111	    ;   jpl_type_to_nicename( Tf, NNf),
 1112		throw(error(type_error(NNf,V),
 1113		    context(jpl_set/3,
 1114			    'the value is not assignable to the named field of the class')))
 1115	    )
 1116	;   throw(error(type_error(field_value,V),
 1117		    context(jpl_set/3,
 1118			    '3rd arg does not represent any Java value or object')))
 1119	)
 1120	;   throw(error(existence_error(field,Fname),   % 'existence'? or some other sort of error maybe?
 1121		    context(jpl_set/3,
 1122			    'more than one public field of the object has this name (this should not happen)')))
 1123	).
 1124
 1125
 1126jpl_set_instance(array(Type), _, Obj, Fspec, V) :-
 1127	(   is_list(V)                  % a list of array element values
 1128	->  Vs = V
 1129	;   var(V)
 1130	->  throw(error(instantiation_error,
 1131		    context(jpl_set/3, 'when 1st arg is an array, 3rd arg must be bound to a suitable element value or list of values')))
 1132	;   Vs = [V]                    % a single array element value
 1133	),
 1134	length(Vs, Iv),
 1135	(   var(Fspec)
 1136	->  throw(error(instantiation_error,
 1137		    context(jpl_set/3,
 1138			    'when 1st arg is an array, 2nd arg must be bound to an index or index range')))
 1139	;   integer(Fspec)          % single-element assignment
 1140	->  (   Fspec < 0
 1141	->  throw(error(domain_error(array_index,Fspec),
 1142		    context(jpl_set/3,
 1143			    'when 1st arg is an array, an integral 2nd arg must be a non-negative index')))
 1144	;   Iv is 1
 1145	->  N is Fspec
 1146	;   Iv is 0
 1147	->  throw(error(domain_error(array_element(Fspec),Vs),
 1148			context(jpl_set/3,
 1149				'no values for array element assignment: needs one')))
 1150	;   throw(error(domain_error(array_element(Fspec),Vs),
 1151			context(jpl_set/3,
 1152				'too many values for array element assignment: needs one')))
 1153	)
 1154	;   Fspec = N-M             % element-sequence assignment
 1155	->  (   integer(N),
 1156	    integer(M)
 1157	->  (   N >= 0,
 1158		Size is (M-N)+1,
 1159		Size >= 0
 1160	    ->  (   Size == Iv
 1161		->  true
 1162		;   Size < Iv
 1163		->  throw(error(domain_error(array_elements(N-M),Vs),
 1164				context(jpl_set/3,
 1165					'too few values for array range assignment')))
 1166		;   throw(error(domain_error(array_elements(N-M),Vs),
 1167				context(jpl_set/3,
 1168					'too many values for array range assignment')))
 1169		)
 1170	    ;   throw(error(domain_error(array_index_range,N-M),
 1171		    context(jpl_set/3,
 1172			    'array index range must be a non-decreasing pair of non-negative integers')))
 1173	    )
 1174	;   throw(error(type_error(array_index_range,N-M),
 1175		    context(jpl_set/3,
 1176			    'array index range must be a non-decreasing pair of non-negative integers')))
 1177	)
 1178	;   atom(Fspec)
 1179	->  (   Fspec == length
 1180	->  throw(error(permission_error(modify,final_field,length),
 1181			    context(jpl_set/3,
 1182				    'cannot assign a value to a final field')))
 1183	;   throw(error(existence_error(field,Fspec),
 1184			    context(jpl_set/3,
 1185				    'array has no field with that name')))
 1186	)
 1187	;   throw(error(domain_error(array_index,Fspec),
 1188		    context(jpl_set/3,
 1189			    'when 1st arg is an array object, 2nd arg must be a non-negative index or index range')))
 1190	),
 1191	jpl_set_array(Type, Obj, N, Iv, Vs).
 1192
 1193%------------------------------------------------------------------------------
 1194
 1195% jpl_set_static(+Type, +ClassObj, +FieldName, +Value) :-
 1196%   we can rely on:
 1197%       Type being a class/2 type representing some accessible class
 1198%       ClassObj being an instance of java.lang.Class which represents the same class as Type
 1199%   but FieldName could be anything, so we validate it here,
 1200%   look for a suitable (static) field of the target class,
 1201%   then call jpl_set_static_field/4 to attempt to assign Value (which could be anything) to it
 1202%
 1203%   NB this does not yet handle shadowed fields correctly...
 1204
 1205jpl_set_static(Type, ClassObj, Fname, V) :-
 1206	(   atom(Fname)                     % the usual case
 1207	->  true
 1208	;   var(Fname)
 1209	->  throw(error(instantiation_error,
 1210		    context(jpl_set/3,
 1211			    'when 1st arg denotes a class, 2nd arg must be bound to the name of a public, static, non-final field')))
 1212	;   throw(error(type_error(field_name,Fname),
 1213		    context(jpl_set/3,
 1214			    'when 1st arg denotes a class, 2nd arg must be the name of a public, static, non-final field')))
 1215	),
 1216	findall(  % get all static fields of the denoted class
 1217	z4(I,Mods,FID,Tf),
 1218	(   jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
 1219	    member(static, Mods)
 1220	),
 1221	Z4s
 1222	),
 1223	(   Z4s = []
 1224	->  throw(error(existence_error(field,Fname),
 1225		    context(jpl_set/3,
 1226			    'class has no public static fields of this name')))
 1227	;   Z4s = [z4(I,Mods,FID,Tf)]       % exactly one synonymous field?
 1228	->  (   member(final, Mods)
 1229	->  throw(error(permission_error(modify,final_field,Fname),
 1230		    context(jpl_set/3,
 1231			    'cannot assign a value to a final field')))
 1232	;   jpl_datum_to_type(V, Tv)
 1233	->  (   jpl_type_fits_type(Tv, Tf)
 1234	    ->  jpl_set_static_field(Tf, ClassObj, FID, V)
 1235	    ;   jpl_type_to_nicename(Tf, NNf),
 1236		throw(error(type_error(NNf,V),
 1237		    context(jpl_set/3,
 1238			    'the value is not assignable to the named field of the class')))
 1239	    )
 1240	;   throw(error(type_error(field_value,V),
 1241		    context(jpl_set/3,
 1242			    '3rd arg does not represent any Java value or object')))
 1243	)
 1244	;   throw(error(existence_error(field,Fname),
 1245		    context(jpl_set/3,
 1246			    'more than one public static field of the class has this name (this should not happen)(?)')))
 1247	).
 1248
 1249%------------------------------------------------------------------------------
 jpl_set_array(+ElementType, +Array, +Offset, +DatumQty, +Datums)
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,_))
 1258jpl_set_array(T, A, N, I, Ds) :-
 1259	(   jpl_datums_to_types(Ds, Tds)        % most specialised types of given values
 1260	->  (   jpl_types_fit_type(Tds, T)      % all assignable to element type?
 1261	    ->  true
 1262	    ;   throw(error(type_error(array(T),Ds),
 1263			    context(jpl_set/3,
 1264				    'not all values are assignable to the array element type')))
 1265	    )
 1266	;   throw(error(type_error(array(T),Ds),
 1267		    context(jpl_set/3,
 1268			    'not all values are convertible to Java values or references')))
 1269	),
 1270	(   (   T = class(_,_)
 1271	    ;   T = array(_)                    % array elements are objects
 1272	    )
 1273	->  (   nth0(J, Ds, D),                 % for each datum
 1274	        Nd is N+J,                      % compute array index
 1275		(   D = {Tq}                    % quoted term?
 1276		->  jni_term_to_jref(Tq, D2)    % convert to a JPL reference to a corresponding jpl.Term object
 1277		;   D = D2
 1278		),
 1279		jSetObjectArrayElement(A, Nd, D2),
 1280		fail                            % iterate
 1281	    ;   true
 1282	    )
 1283	;   jpl_primitive_type(T)               % array elements are primitive values
 1284	->  jni_type_to_xput_code(T, Xc),
 1285	    jni_alloc_buffer(Xc, I, Bp),        % I-element buf of required primitive type
 1286	    jpl_set_array_1(Ds, T, 0, Bp),
 1287	    jpl_set_elements(T, A, N, I, Bp),
 1288	    jni_free_buffer(Bp)
 1289	;   throw(error(system_error(array_element_type,T),
 1290		    context(jpl_set/3,
 1291			    'array element type is unknown (this should not happen)')))
 1292	).
 1293
 1294%------------------------------------------------------------------------------
 jpl_set_array_1(+Values, +Type, +BufferIndex, +BufferPointer)
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...
 1303jpl_set_array_1([], _, _, _).
 1304jpl_set_array_1([V|Vs], Tprim, Ib, Bp) :-
 1305	jni_type_to_xput_code(Tprim, Xc),
 1306	jni_stash_buffer_value(Bp, Ib, V, Xc),
 1307	Ibnext is Ib+1,
 1308	jpl_set_array_1(Vs, Tprim, Ibnext, Bp).
 1309
 1310%------------------------------------------------------------------------------
 1311
 1312jpl_set_elements(boolean, Obj, N, I, Bp) :-
 1313	jSetBooleanArrayRegion(Obj, N, I, jbuf(Bp,boolean)).
 1314jpl_set_elements(char, Obj, N, I, Bp) :-
 1315	jSetCharArrayRegion(Obj, N, I, jbuf(Bp,char)).
 1316jpl_set_elements(byte, Obj, N, I, Bp) :-
 1317	jSetByteArrayRegion(Obj, N, I, jbuf(Bp,byte)).
 1318jpl_set_elements(short, Obj, N, I, Bp) :-
 1319	jSetShortArrayRegion(Obj, N, I, jbuf(Bp,short)).
 1320jpl_set_elements(int, Obj, N, I, Bp) :-
 1321	jSetIntArrayRegion(Obj, N, I, jbuf(Bp,int)).
 1322jpl_set_elements(long, Obj, N, I, Bp) :-
 1323	jSetLongArrayRegion(Obj, N, I, jbuf(Bp,long)).
 1324jpl_set_elements(float, Obj, N, I, Bp) :-
 1325	jSetFloatArrayRegion(Obj, N, I, jbuf(Bp,float)).
 1326jpl_set_elements(double, Obj, N, I, Bp) :-
 1327	jSetDoubleArrayRegion(Obj, N, I, jbuf(Bp,double)).
 1328
 1329%------------------------------------------------------------------------------
 jpl_set_instance_field(+Type, +Obj, +FieldID, +V)
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)
 1336jpl_set_instance_field(boolean, Obj, FieldID, V) :-
 1337	jSetBooleanField(Obj, FieldID, V).
 1338jpl_set_instance_field(byte, Obj, FieldID, V) :-
 1339	jSetByteField(Obj, FieldID, V).
 1340jpl_set_instance_field(char, Obj, FieldID, V) :-
 1341	jSetCharField(Obj, FieldID, V).
 1342jpl_set_instance_field(short, Obj, FieldID, V) :-
 1343	jSetShortField(Obj, FieldID, V).
 1344jpl_set_instance_field(int, Obj, FieldID, V) :-
 1345	jSetIntField(Obj, FieldID, V).
 1346jpl_set_instance_field(long, Obj, FieldID, V) :-
 1347	jSetLongField(Obj, FieldID, V).
 1348jpl_set_instance_field(float, Obj, FieldID, V) :-
 1349	jSetFloatField(Obj, FieldID, V).
 1350jpl_set_instance_field(double, Obj, FieldID, V) :-
 1351	jSetDoubleField(Obj, FieldID, V).
 1352jpl_set_instance_field(class(_,_), Obj, FieldID, V) :-  % also handles byval term assignments
 1353	(   V = {T}                     % quoted term?
 1354	->  jni_term_to_jref(T, V2)     % convert to a JPL reference to a corresponding jpl.Term object
 1355	;   V = V2
 1356	),
 1357	jSetObjectField(Obj, FieldID, V2).
 1358jpl_set_instance_field(array(_), Obj, FieldID, V) :-
 1359	jSetObjectField(Obj, FieldID, V).
 1360
 1361%------------------------------------------------------------------------------
 1362
 1363% jpl_set_static_field(+Type, +ClassObj, +FieldID, +V) :-
 1364%   we can rely on Type, ClassObj and FieldID being valid,
 1365%   and on V being assignable (if V is a quoted term then it is converted here)
 1366
 1367jpl_set_static_field(boolean, Obj, FieldID, V) :-
 1368	jSetStaticBooleanField(Obj, FieldID, V).
 1369
 1370jpl_set_static_field(byte, Obj, FieldID, V) :-
 1371	jSetStaticByteField(Obj, FieldID, V).
 1372
 1373jpl_set_static_field(char, Obj, FieldID, V) :-
 1374	jSetStaticCharField(Obj, FieldID, V).
 1375
 1376jpl_set_static_field(short, Obj, FieldID, V) :-
 1377	jSetStaticShortField(Obj, FieldID, V).
 1378
 1379jpl_set_static_field(int, Obj, FieldID, V) :-
 1380	jSetStaticIntField(Obj, FieldID, V).
 1381
 1382jpl_set_static_field(long, Obj, FieldID, V) :-
 1383	jSetStaticLongField(Obj, FieldID, V).
 1384
 1385jpl_set_static_field(float, Obj, FieldID, V) :-
 1386	jSetStaticFloatField(Obj, FieldID, V).
 1387
 1388jpl_set_static_field(double, Obj, FieldID, V) :-
 1389	jSetStaticDoubleField(Obj, FieldID, V).
 1390
 1391jpl_set_static_field(class(_,_), Obj, FieldID, V) :-    % also handles byval term assignments
 1392	(   V = {T}                         % quoted term?
 1393	->  jni_term_to_jref(T, V2)         % convert to a JPL reference to a corresponding jpl.Term object
 1394	;   V = V2
 1395	),
 1396	jSetStaticObjectField(Obj, FieldID, V2).
 1397
 1398jpl_set_static_field(array(_), Obj, FieldID, V) :-
 1399	jSetStaticObjectField(Obj, FieldID, V).
 1400
 1401%------------------------------------------------------------------------------
 1402
 1403% jpl_z3s_to_most_specific_z3(+Zs, -Z) :-
 1404%   Zs is a list of arity-matching, type-suitable z3(I,MID,Tfps)
 1405%   Z is the single most specific element of Zs,
 1406%   i.e. that than which no other z3/3 has a more specialised signature;
 1407%   fails if there is more than one such
 1408
 1409jpl_z3s_to_most_specific_z3(Zs, Z) :-
 1410	jpl_fergus_is_the_greatest(Zs, Z).
 1411
 1412%------------------------------------------------------------------------------
 1413
 1414% jpl_z5s_to_most_specific_z5(+Zs, -Z) :-
 1415%   Zs is a list of arity-matching, type-suitable z5(I,Mods,MID,Tr,Tfps)
 1416%   Z is the single most specific element of Zs,
 1417%   i.e. that than which no other z5/5 has a more specialised signature
 1418%   (this fails if there is more than one such)
 1419
 1420jpl_z5s_to_most_specific_z5(Zs, Z) :-
 1421	jpl_fergus_is_the_greatest(Zs, Z).
 1422
 1423%------------------------------------------------------------------------------
 1424
 1425% jpl_pl_lib_version(-VersionString) :-
 1426% jpl_pl_lib_version(-Major, -Minor, -Patch, -Status) :-
 1427
 1428jpl_pl_lib_version(VersionString) :-
 1429	jpl_pl_lib_version(Major, Minor, Patch, Status),
 1430	concat_atom([Major,'.',Minor,'.',Patch,'-',Status], VersionString).
 1431
 1432
 1433jpl_pl_lib_version(3, 1, 4, alpha).
 1434
 1435%------------------------------------------------------------------------------
 1436
 1437% jpl_type_alfa(0'$) -->        % presumably not allowed
 1438%   "$".                        % given the "inner class" syntax?
 1439
 1440jpl_type_alfa(0'_) -->
 1441	"_",
 1442	!.
 1443
 1444jpl_type_alfa(C) -->
 1445	[C], { C>=0'a, C=<0'z },
 1446	!.
 1447
 1448jpl_type_alfa(C) -->
 1449	[C], { C>=0'A, C=<0'Z }.
 1450
 1451%------------------------------------------------------------------------------
 1452
 1453jpl_type_alfa_num(C) -->
 1454	jpl_type_alfa(C),
 1455	!.
 1456
 1457jpl_type_alfa_num(C) -->
 1458	[C], { C>=0'0, C=<0'9 }.
 1459
 1460%------------------------------------------------------------------------------
 1461
 1462jpl_type_array_classname(array(T)) -->
 1463	"[", jpl_type_classname_2(T).
 1464
 1465%------------------------------------------------------------------------------
 1466
 1467jpl_type_array_descriptor(array(T)) -->
 1468	"[", jpl_type_descriptor_1(T).
 1469
 1470%------------------------------------------------------------------------------
 1471
 1472jpl_type_bare_class_descriptor(class(Ps,Cs)) -->
 1473	jpl_type_slashed_package_parts(Ps), jpl_type_class_parts(Cs).
 1474
 1475%------------------------------------------------------------------------------
 1476
 1477jpl_type_bare_classname(class(Ps,Cs)) -->
 1478	jpl_type_dotted_package_parts(Ps), jpl_type_class_parts(Cs).
 1479
 1480%------------------------------------------------------------------------------
 1481
 1482jpl_type_class_descriptor(class(Ps,Cs)) -->
 1483	"L", jpl_type_bare_class_descriptor(class(Ps,Cs)), ";".
 1484
 1485%------------------------------------------------------------------------------
 1486
 1487jpl_type_class_part(N) -->
 1488	jpl_type_id(N).
 1489
 1490%------------------------------------------------------------------------------
 1491
 1492jpl_type_class_parts([C|Cs]) -->
 1493	jpl_type_class_part(C), jpl_type_inner_class_parts(Cs).
 1494
 1495%------------------------------------------------------------------------------
 1496
 1497jpl_type_classname_1(T) -->
 1498	jpl_type_bare_classname(T),
 1499	!.
 1500
 1501jpl_type_classname_1(T) -->
 1502	jpl_type_array_classname(T),
 1503	!.
 1504
 1505jpl_type_classname_1(T) -->
 1506	jpl_type_primitive(T).
 1507
 1508%------------------------------------------------------------------------------
 1509
 1510jpl_type_classname_2(T) -->
 1511	jpl_type_delimited_classname(T).
 1512
 1513jpl_type_classname_2(T) -->
 1514	jpl_type_array_classname(T).
 1515
 1516jpl_type_classname_2(T) -->
 1517	jpl_type_primitive(T).
 1518
 1519%------------------------------------------------------------------------------
 1520
 1521jpl_type_delimited_classname(Class) -->
 1522	"L", jpl_type_bare_classname(Class), ";".
 1523
 1524%------------------------------------------------------------------------------
 1525
 1526jpl_type_descriptor_1(T) -->
 1527	jpl_type_primitive(T),
 1528	!.
 1529
 1530jpl_type_descriptor_1(T) -->
 1531	jpl_type_class_descriptor(T),
 1532	!.
 1533
 1534jpl_type_descriptor_1(T) -->
 1535	jpl_type_array_descriptor(T),
 1536	!.
 1537
 1538jpl_type_descriptor_1(T) -->
 1539	jpl_type_method_descriptor(T).
 1540
 1541%------------------------------------------------------------------------------
 1542
 1543jpl_type_dotted_package_parts([P|Ps]) -->
 1544	jpl_type_package_part(P), ".", !, jpl_type_dotted_package_parts(Ps).
 1545
 1546jpl_type_dotted_package_parts([]) -->
 1547	[].
 1548
 1549%------------------------------------------------------------------------------
 1550
 1551jpl_type_findclassname(T) -->
 1552	jpl_type_bare_class_descriptor(T).
 1553
 1554jpl_type_findclassname(T) -->
 1555	jpl_type_array_descriptor(T).
 1556
 1557%------------------------------------------------------------------------------
 1558
 1559jpl_type_id(A) -->
 1560	{ nonvar(A) -> atom_codes(A,[C|Cs]) ; true },
 1561	jpl_type_alfa(C), jpl_type_id_rest(Cs),
 1562	{ atom_codes(A, [C|Cs]) }.
 1563
 1564%------------------------------------------------------------------------------
 1565
 1566jpl_type_id_rest([C|Cs]) -->
 1567	jpl_type_alfa_num(C), !, jpl_type_id_rest(Cs).
 1568
 1569jpl_type_id_rest([]) -->
 1570	[].
 1571
 1572%------------------------------------------------------------------------------
 1573
 1574jpl_type_id_v2(A) -->                   % inner class name parts (empirically)
 1575	{ nonvar(A) -> atom_codes(A,Cs) ; true },
 1576	jpl_type_id_rest(Cs),
 1577	{ atom_codes(A, Cs) }.
 1578
 1579%------------------------------------------------------------------------------
 1580
 1581jpl_type_inner_class_part(N) -->
 1582	jpl_type_id_v2(N).
 1583
 1584%------------------------------------------------------------------------------
 1585
 1586jpl_type_inner_class_parts([C|Cs]) -->
 1587	"$", jpl_type_inner_class_part(C), !, jpl_type_inner_class_parts(Cs).
 1588
 1589jpl_type_inner_class_parts([]) -->
 1590	[].
 1591
 1592%------------------------------------------------------------------------------
 1593
 1594jpl_type_method_descriptor(method(Ts,T)) -->
 1595	"(", jpl_type_method_descriptor_args(Ts), ")", jpl_type_method_descriptor_return(T).
 1596
 1597%------------------------------------------------------------------------------
 1598
 1599jpl_type_method_descriptor_args([T|Ts]) -->
 1600	jpl_type_descriptor_1(T), !, jpl_type_method_descriptor_args(Ts).
 1601
 1602jpl_type_method_descriptor_args([]) -->
 1603	[].
 1604
 1605%------------------------------------------------------------------------------
 1606
 1607jpl_type_method_descriptor_return(T) -->
 1608	jpl_type_void(T).
 1609
 1610jpl_type_method_descriptor_return(T) -->
 1611	jpl_type_descriptor_1(T).
 1612
 1613%------------------------------------------------------------------------------
 1614
 1615jpl_type_package_part(N) -->
 1616	jpl_type_id(N).
 1617
 1618%------------------------------------------------------------------------------
 1619
 1620jpl_type_primitive(boolean) -->
 1621	"Z",
 1622	!.
 1623
 1624jpl_type_primitive(byte) -->
 1625	"B",
 1626	!.
 1627
 1628jpl_type_primitive(char) -->
 1629	"C",
 1630	!.
 1631
 1632jpl_type_primitive(short) -->
 1633	"S",
 1634	!.
 1635
 1636jpl_type_primitive(int) -->
 1637	"I",
 1638	!.
 1639
 1640jpl_type_primitive(long) -->
 1641	"J",
 1642	!.
 1643
 1644jpl_type_primitive(float) -->
 1645	"F",
 1646	!.
 1647
 1648jpl_type_primitive(double) -->
 1649	"D".
 1650
 1651%------------------------------------------------------------------------------
 1652
 1653jpl_type_slashed_package_parts([P|Ps]) -->
 1654	jpl_type_package_part(P), "/", !, jpl_type_slashed_package_parts(Ps).
 1655
 1656jpl_type_slashed_package_parts([]) -->
 1657	[].
 1658
 1659%------------------------------------------------------------------------------
 1660
 1661jpl_type_void(void) -->
 1662	"V".
 1663
 1664%------------------------------------------------------------------------------
 1665
 1666%type   jCallBooleanMethod(object, method_id, types, datums, boolean)
 1667
 1668% jCallBooleanMethod(+Obj, +MethodID, +Types, +Params, -Rbool) :-
 1669
 1670jCallBooleanMethod(Obj, MethodID, Types, Params, Rbool) :-
 1671	jni_params_put(Params, Types, ParamBuf),
 1672	jni_func(39, Obj, MethodID, ParamBuf, Rbool).
 1673
 1674%------------------------------------------------------------------------------
 1675
 1676%type   jCallByteMethod(object, method_id, types, datums, byte)
 1677
 1678% jCallByteMethod(+Obj, +MethodID, +Types, +Params, -Rbyte) :-
 1679
 1680jCallByteMethod(Obj, MethodID, Types, Params, Rbyte) :-
 1681	jni_params_put(Params, Types, ParamBuf),
 1682	jni_func(42, Obj, MethodID, ParamBuf, Rbyte).
 1683
 1684%------------------------------------------------------------------------------
 1685
 1686%type   jCallCharMethod(object, method_id, types, datums, char)
 1687
 1688% jCallCharMethod(+Obj, +MethodID, +Types, +Params, -Rchar) :-
 1689
 1690jCallCharMethod(Obj, MethodID, Types, Params, Rchar) :-
 1691	jni_params_put(Params, Types, ParamBuf),
 1692	jni_func(45, Obj, MethodID, ParamBuf, Rchar).
 1693
 1694%------------------------------------------------------------------------------
 1695
 1696%type   jCallDoubleMethod(object, method_id, types, datums, double)
 1697
 1698% jCallDoubleMethod(+Obj, +MethodID, +Types, +Params, -Rdouble) :-
 1699
 1700jCallDoubleMethod(Obj, MethodID, Types, Params, Rdouble) :-
 1701	jni_params_put(Params, Types, ParamBuf),
 1702	jni_func(60, Obj, MethodID, ParamBuf, Rdouble).
 1703
 1704%------------------------------------------------------------------------------
 1705
 1706%type   jCallFloatMethod(object, method_id, types, datums, float)
 1707
 1708% jCallFloatMethod(+Obj, +MethodID, +Types, +Params, -Rfloat) :-
 1709
 1710jCallFloatMethod(Obj, MethodID, Types, Params, Rfloat) :-
 1711	jni_params_put(Params, Types, ParamBuf),
 1712	jni_func(57, Obj, MethodID, ParamBuf, Rfloat).
 1713
 1714%------------------------------------------------------------------------------
 1715
 1716%type   jCallIntMethod(object, method_id, types, datums, int)
 1717
 1718% jCallIntMethod(+Obj, +MethodID, +Types, +Params, -Rint) :-
 1719
 1720jCallIntMethod(Obj, MethodID, Types, Params, Rint) :-
 1721	jni_params_put(Params, Types, ParamBuf),
 1722	jni_func(51, Obj, MethodID, ParamBuf, Rint).
 1723
 1724%------------------------------------------------------------------------------
 1725
 1726%type   jCallLongMethod(object, method_id, types, datums, long)
 1727
 1728% jCallLongMethod(+Obj, +MethodID, +Types, +Params, -Rlong) :-
 1729
 1730jCallLongMethod(Obj, MethodID, Types, Params, Rlong) :-
 1731	jni_params_put(Params, Types, ParamBuf),
 1732	jni_func(54, Obj, MethodID, ParamBuf, Rlong).
 1733
 1734%------------------------------------------------------------------------------
 1735
 1736%type   jCallObjectMethod(object, method_id, types, datums, object)
 1737
 1738% jCallObjectMethod(+Obj, +MethodID, +Types, +Params, -Robj) :-
 1739
 1740jCallObjectMethod(Obj, MethodID, Types, Params, Robj) :-
 1741	jni_params_put(Params, Types, ParamBuf),
 1742	jni_func(36, Obj, MethodID, ParamBuf, Robj).
 1743
 1744%------------------------------------------------------------------------------
 1745
 1746%type   jCallShortMethod(object, method_id, types, datums, short)
 1747
 1748% jCallShortMethod(+Obj, +MethodID, +Types, +Params, -Rshort) :-
 1749
 1750jCallShortMethod(Obj, MethodID, Types, Params, Rshort) :-
 1751	jni_params_put(Params, Types, ParamBuf),
 1752	jni_func(48, Obj, MethodID, ParamBuf, Rshort).
 1753
 1754%------------------------------------------------------------------------------
 1755
 1756%type   jCallStaticBooleanMethod(class, types, datums, boolean)
 1757
 1758% jCallStaticBooleanMethod(+Class, +MethodID, +Types, +Params, -Rbool) :-
 1759
 1760jCallStaticBooleanMethod(Class, MethodID, Types, Params, Rbool) :-
 1761	jni_params_put(Params, Types, ParamBuf),
 1762	jni_func(119, Class, MethodID, ParamBuf, Rbool).
 1763
 1764%------------------------------------------------------------------------------
 1765
 1766%type   jCallStaticByteMethod(class, method_id, types, datums, byte)
 1767
 1768% jCallStaticByteMethod(+Class, +MethodID, +Types, +Params, -Rbyte) :-
 1769
 1770jCallStaticByteMethod(Class, MethodID, Types, Params, Rbyte) :-
 1771	jni_params_put(Params, Types, ParamBuf),
 1772	jni_func(122, Class, MethodID, ParamBuf, Rbyte).
 1773
 1774%------------------------------------------------------------------------------
 1775
 1776%type   jCallStaticCharMethod(class, method_id, types, datums, char)
 1777
 1778% jCallStaticCharMethod(+Class, +MethodID, +Types, +Params, -Rchar) :-
 1779
 1780jCallStaticCharMethod(Class, MethodID, Types, Params, Rchar) :-
 1781	jni_params_put(Params, Types, ParamBuf),
 1782	jni_func(125, Class, MethodID, ParamBuf, Rchar).
 1783
 1784%------------------------------------------------------------------------------
 1785
 1786%type   jCallStaticDoubleMethod(class, method_id, types, datums, double)
 1787
 1788% jCallStaticDoubleMethod(+Class, +MethodID, +Types, +Params, -Rdouble) :-
 1789
 1790jCallStaticDoubleMethod(Class, MethodID, Types, Params, Rdouble) :-
 1791	jni_params_put(Params, Types, ParamBuf),
 1792	jni_func(140, Class, MethodID, ParamBuf, Rdouble).
 1793
 1794%------------------------------------------------------------------------------
 1795
 1796%type   jCallStaticFloatMethod(class, method_id, types, datums, float)
 1797
 1798% jCallStaticFloatMethod(+Class, +MethodID, +Types, +Params, -Rfloat) :-
 1799
 1800jCallStaticFloatMethod(Class, MethodID, Types, Params, Rfloat) :-
 1801	jni_params_put(Params, Types, ParamBuf),
 1802	jni_func(137, Class, MethodID, ParamBuf, Rfloat).
 1803
 1804%------------------------------------------------------------------------------
 1805
 1806%type   jCallStaticIntMethod(class, method_id, types, datums, int)
 1807
 1808% jCallStaticIntMethod(+Class, +MethodID, +Types, +Params, -Rint) :-
 1809
 1810jCallStaticIntMethod(Class, MethodID, Types, Params, Rint) :-
 1811	jni_params_put(Params, Types, ParamBuf),
 1812	jni_func(131, Class, MethodID, ParamBuf, Rint).
 1813
 1814%------------------------------------------------------------------------------
 1815
 1816%type   jCallStaticLongMethod(class, method_id, types, datums, long)
 1817
 1818% jCallStaticLongMethod(+Class, +MethodID, +Types, +Params, -Rlong) :-
 1819
 1820jCallStaticLongMethod(Class, MethodID, Types, Params, Rlong) :-
 1821	jni_params_put(Params, Types, ParamBuf),
 1822	jni_func(134, Class, MethodID, ParamBuf, Rlong).
 1823
 1824%------------------------------------------------------------------------------
 1825
 1826%type   jCallStaticObjectMethod(class, method_id, types, datums, object)
 1827
 1828% jCallStaticObjectMethod(+Class, +MethodID, +Types, +Params, -Robj) :-
 1829
 1830jCallStaticObjectMethod(Class, MethodID, Types, Params, Robj) :-
 1831	jni_params_put(Params, Types, ParamBuf),
 1832	jni_func(116, Class, MethodID, ParamBuf, Robj).
 1833
 1834%------------------------------------------------------------------------------
 1835
 1836%type   jCallStaticShortMethod(class, method_id, types, datums, short)
 1837
 1838% jCallStaticShortMethod(+Class, +MethodID, +Types, +Params, -Rshort) :-
 1839
 1840jCallStaticShortMethod(Class, MethodID, Types, Params, Rshort) :-
 1841	jni_params_put(Params, Types, ParamBuf),
 1842	jni_func(128, Class, MethodID, ParamBuf, Rshort).
 1843
 1844%------------------------------------------------------------------------------
 1845
 1846%type   jCallStaticVoidMethod(class, method_id, types, datums)
 1847
 1848% jCallStaticVoidMethod(+Class, +MethodID, +Types, +Params) :-
 1849
 1850jCallStaticVoidMethod(Class, MethodID, Types, Params) :-
 1851	jni_params_put(Params, Types, ParamBuf),
 1852	jni_void(143, Class, MethodID, ParamBuf).
 1853
 1854%------------------------------------------------------------------------------
 1855
 1856%type   jCallVoidMethod(object, method_id, types, datums)
 1857
 1858% jCallVoidMethod(+Obj, +MethodID, +Types, +Params) :-
 1859
 1860jCallVoidMethod(Obj, MethodID, Types, Params) :-
 1861	jni_params_put(Params, Types, ParamBuf),
 1862	jni_void(63, Obj, MethodID, ParamBuf).
 1863
 1864%------------------------------------------------------------------------------
 1865
 1866%type   jFindClass(findclassname, class)
 1867
 1868% jFindClass(+ClassName, -Class) :-
 1869
 1870jFindClass(ClassName, Class) :- current_predicate(user:cliFindClass/2),user:cliFindClass(ClassName, Class),!.
 1871jFindClass(ClassName, Class) :-
 1872	jni_func(6, ClassName, Class).
 1873
 1874%------------------------------------------------------------------------------
 1875
 1876%type   jGetArrayLength(array, int)
 1877
 1878% jGetArrayLength(+Array, -Size) :-
 1879
 1880jGetArrayLength(Array, Size) :-
 1881	jni_func(171, Array, Size).
 1882
 1883%------------------------------------------------------------------------------
 1884
 1885%type   jGetBooleanArrayRegion(boolean_array, int, int, boolean_buf)
 1886
 1887% jGetBooleanArrayRegion(+Array, +Start, +Len, +Buf) :-
 1888
 1889jGetBooleanArrayRegion(Array, Start, Len, Buf) :-
 1890	jni_void(199, Array, Start, Len, Buf).
 1891
 1892%------------------------------------------------------------------------------
 1893
 1894%type   jGetBooleanField(object, field_id, boolean)
 1895
 1896% jGetBooleanField(+Obj, +FieldID, -Rbool) :-
 1897
 1898jGetBooleanField(Obj, FieldID, Rbool) :-
 1899	jni_func(96, Obj, FieldID, Rbool).
 1900
 1901%------------------------------------------------------------------------------
 1902
 1903%type   jGetByteArrayRegion(byte_array, int, int, byte_buf)
 1904
 1905% jGetByteArrayRegion(+Array, +Start, +Len, +Buf) :-
 1906
 1907jGetByteArrayRegion(Array, Start, Len, Buf) :-
 1908	jni_void(200, Array, Start, Len, Buf).
 1909
 1910%------------------------------------------------------------------------------
 1911
 1912%type   jGetByteField(object, field_id, byte)
 1913
 1914% jGetByteField(+Obj, +FieldID, -Rbyte) :-
 1915
 1916jGetByteField(Obj, FieldID, Rbyte) :-
 1917	jni_func(97, Obj, FieldID, Rbyte).
 1918
 1919%------------------------------------------------------------------------------
 1920
 1921%type   jGetCharArrayRegion(char_array, int, int, char_buf)
 1922
 1923% jGetCharArrayRegion(+Array, +Start, +Len, +Buf) :-
 1924
 1925jGetCharArrayRegion(Array, Start, Len, Buf) :-
 1926	jni_void(201, Array, Start, Len, Buf).
 1927
 1928%------------------------------------------------------------------------------
 1929
 1930%type   jGetCharField(object, field_id, char)
 1931
 1932% jGetCharField(+Obj, +FieldID, -Rchar) :-
 1933
 1934jGetCharField(Obj, FieldID, Rchar) :-
 1935	jni_func(98, Obj, FieldID, Rchar).
 1936
 1937%------------------------------------------------------------------------------
 1938
 1939%type   jGetDoubleArrayRegion(double_array, int, int, double_buf)
 1940
 1941% jGetDoubleArrayRegion(+Array, +Start, +Len, +Buf) :-
 1942
 1943jGetDoubleArrayRegion(Array, Start, Len, Buf) :-
 1944	jni_void(206, Array, Start, Len, Buf).
 1945
 1946%------------------------------------------------------------------------------
 1947
 1948%type   jGetDoubleField(object, field_id, double)
 1949
 1950% jGetDoubleField(+Obj, +FieldID, -Rdouble) :-
 1951
 1952jGetDoubleField(Obj, FieldID, Rdouble) :-
 1953	jni_func(103, Obj, FieldID, Rdouble).
 1954
 1955%------------------------------------------------------------------------------
 1956
 1957%type   jGetFieldID(class, descriptor, field_id)
 1958
 1959% jGetFieldID(+Class, +Name, +Typedescriptor, -FieldID) :-
 1960
 1961jGetFieldID(Class, Name, Type, FieldID) :-
 1962	jpl_type_to_descriptor(Type, TD),
 1963	jni_func(94, Class, Name, TD, FieldID).
 1964
 1965%------------------------------------------------------------------------------
 1966
 1967%type   jGetFloatArrayRegion(float_array, int, int, float_buf)
 1968
 1969% jGetFloatArrayRegion(+Array, +Start, +Len, +Buf) :-
 1970
 1971jGetFloatArrayRegion(Array, Start, Len, Buf) :-
 1972	jni_void(205, Array, Start, Len, Buf).
 1973
 1974%------------------------------------------------------------------------------
 1975
 1976%type   jGetFloatField(object, field_id, float)
 1977
 1978% jGetFloatField(+Obj, +FieldID, -Rfloat) :-
 1979
 1980jGetFloatField(Obj, FieldID, Rfloat) :-
 1981	jni_func(102, Obj, FieldID, Rfloat).
 1982
 1983%------------------------------------------------------------------------------
 1984
 1985%type   jGetIntArrayRegion(int_array, int, int, int_buf)
 1986
 1987% jGetIntArrayRegion(+Array, +Start, +Len, +Buf) :-
 1988
 1989jGetIntArrayRegion(Array, Start, Len, Buf) :-
 1990	jni_void(203, Array, Start, Len, Buf).
 1991
 1992%------------------------------------------------------------------------------
 1993
 1994%type   jGetIntField(object, field_id, int)
 1995
 1996% jGetIntField(+Obj, +FieldID, -Rint) :-
 1997
 1998jGetIntField(Obj, FieldID, Rint) :-
 1999	jni_func(100, Obj, FieldID, Rint).
 2000
 2001%------------------------------------------------------------------------------
 2002
 2003%type   jGetLongArrayRegion(long_array, int, int, long_buf)
 2004
 2005% jGetLongArrayRegion(+Array, +Start, +Len, +Buf) :-
 2006
 2007jGetLongArrayRegion(Array, Start, Len, Buf) :-
 2008	jni_void(204, Array, Start, Len, Buf).
 2009
 2010%------------------------------------------------------------------------------
 2011
 2012%type   jGetLongField(object, field_id, long)
 2013
 2014% jGetLongField(+Obj, +FieldID, -Rlong) :-
 2015
 2016jGetLongField(Obj, FieldID, Rlong) :-
 2017	jni_func(101, Obj, FieldID, Rlong).
 2018
 2019%------------------------------------------------------------------------------
 2020
 2021%type   jGetMethodID(class, name, descriptor, method_id)
 2022
 2023% jGetMethodID(+Class, +Name, +TypeDescriptor, -MethodID) :-
 2024
 2025jGetMethodID(Class, Name, Type, MethodID) :-
 2026	jpl_type_to_descriptor(Type, TD),
 2027	jni_func(33, Class, Name, TD, MethodID).
 2028
 2029%------------------------------------------------------------------------------
 2030
 2031%type   jGetObjectArrayElement(object_array, int, object)
 2032
 2033% jGetObjectArrayElement(+Array, +Index, -Obj) :-
 2034
 2035jGetObjectArrayElement(Array, Index, Obj) :-
 2036	jni_func(173, Array, Index, Obj).
 2037
 2038%------------------------------------------------------------------------------
 2039
 2040%type   jGetObjectClass(object, class)
 2041
 2042% jGetObjectClass(+Object, -Class) :-
 2043
 2044jGetObjectClass(Object, Class) :-
 2045	jni_func(31, Object, Class).
 2046
 2047%------------------------------------------------------------------------------
 2048
 2049%type   jGetObjectField(object, field_id, object)
 2050
 2051% jGetObjectField(+Obj, +FieldID, -RObj) :-
 2052
 2053jGetObjectField(Obj, FieldID, Robj) :-
 2054	jni_func(95, Obj, FieldID, Robj).
 2055
 2056%------------------------------------------------------------------------------
 2057
 2058%type   jGetShortArrayRegion(short_array, int, int, short_buf)
 2059
 2060% jGetShortArrayRegion(+Array, +Start, +Len, +Buf) :-
 2061
 2062jGetShortArrayRegion(Array, Start, Len, Buf) :-
 2063	jni_void(202, Array, Start, Len, Buf).
 2064
 2065%------------------------------------------------------------------------------
 2066
 2067%type   jGetShortField(object, field_id, short)
 2068
 2069% jGetShortField(+Obj, +FieldID, -Rshort) :-
 2070
 2071jGetShortField(Obj, FieldID, Rshort) :-
 2072	jni_func(99, Obj, FieldID, Rshort).
 2073
 2074%------------------------------------------------------------------------------
 2075
 2076%type   jGetStaticBooleanField(class, field_id, boolean)
 2077
 2078% jGetStaticBooleanField(+Class, +FieldID, -Rbool) :-
 2079
 2080jGetStaticBooleanField(Class, FieldID, Rbool) :-
 2081	jni_func(146, Class, FieldID, Rbool).
 2082
 2083%------------------------------------------------------------------------------
 2084
 2085%type   jGetStaticByteField(class, field_id, byte)
 2086
 2087% jGetStaticByteField(+Class, +FieldID, -Rbyte) :-
 2088
 2089jGetStaticByteField(Class, FieldID, Rbyte) :-
 2090	jni_func(147, Class, FieldID, Rbyte).
 2091
 2092%------------------------------------------------------------------------------
 2093
 2094%type   jGetStaticCharField(class, field_id, char)
 2095
 2096% jGetStaticCharField(+Class, +FieldID, -Rchar) :-
 2097
 2098jGetStaticCharField(Class, FieldID, Rchar) :-
 2099	jni_func(148, Class, FieldID, Rchar).
 2100
 2101%------------------------------------------------------------------------------
 2102
 2103%type   jGetStaticDoubleField(class, field_id, double)
 2104
 2105% jGetStaticDoubleField(+Class, +FieldID, -Rdouble) :-
 2106
 2107jGetStaticDoubleField(Class, FieldID, Rdouble) :-
 2108	jni_func(153, Class, FieldID, Rdouble).
 2109
 2110%------------------------------------------------------------------------------
 2111
 2112%type   jGetStaticFieldID(class, name, field_id)
 2113
 2114% jGetStaticFieldID(+Class, +Name, +TypeDescriptor, -FieldID) :-
 2115
 2116jGetStaticFieldID(Class, Name, Type, FieldID) :-
 2117	jpl_type_to_descriptor(Type, TD),               % cache this?
 2118	jni_func(144, Class, Name, TD, FieldID).
 2119
 2120%------------------------------------------------------------------------------
 2121
 2122%type   jGetStaticFloatField(class, field_id, float)
 2123
 2124% jGetStaticFloatField(+Class, +FieldID, -Rfloat) :-
 2125
 2126jGetStaticFloatField(Class, FieldID, Rfloat) :-
 2127	jni_func(152, Class, FieldID, Rfloat).
 2128
 2129%------------------------------------------------------------------------------
 2130
 2131%type   jGetStaticIntField(class, field_id, int)
 2132
 2133% jGetStaticIntField(+Class, +FieldID, -Rint) :-
 2134
 2135jGetStaticIntField(Class, FieldID, Rint) :-
 2136	jni_func(150, Class, FieldID, Rint).
 2137
 2138%------------------------------------------------------------------------------
 2139
 2140%type   jGetStaticLongField(class, field_id, long)
 2141
 2142% jGetStaticLongField(+Class, +FieldID, -Rlong) :-
 2143
 2144jGetStaticLongField(Class, FieldID, Rlong) :-
 2145	jni_func(151, Class, FieldID, Rlong).
 2146
 2147%------------------------------------------------------------------------------
 2148
 2149%type   jGetStaticMethodID(class, name, method_id)
 2150
 2151% jGetStaticMethodID(+Class, +Name, +TypeDescriptor, -MethodID) :-
 2152
 2153jGetStaticMethodID(Class, Name, Type, MethodID) :-
 2154	jpl_type_to_descriptor(Type, TD),
 2155	jni_func(113, Class, Name, TD, MethodID).
 2156
 2157%------------------------------------------------------------------------------
 2158
 2159%type   jGetStaticObjectField(class, field_id, object)
 2160
 2161% jGetStaticObjectField(+Class, +FieldID, -RObj) :-
 2162
 2163jGetStaticObjectField(Class, FieldID, Robj) :-
 2164	jni_func(145, Class, FieldID, Robj).
 2165
 2166%------------------------------------------------------------------------------
 2167
 2168%type   jGetStaticShortField(class, field_id, short)
 2169
 2170% jGetStaticShortField(+Class, +FieldID, -Rshort) :-
 2171
 2172jGetStaticShortField(Class, FieldID, Rshort) :-
 2173	jni_func(149, Class, FieldID, Rshort).
 2174
 2175%------------------------------------------------------------------------------
 2176
 2177%type   jGetSuperclass(object, object)
 2178
 2179% jGetSuperclass(+Class1, -Class2) :-
 2180
 2181jGetSuperclass(Class1, Class2) :-
 2182	jni_func(10, Class1, Class2).
 2183
 2184%------------------------------------------------------------------------------
 2185
 2186%type   jIsAssignableFrom(object, object)
 2187
 2188% jIsAssignableFrom(+Class1, +Class2) :-
 2189
 2190jIsAssignableFrom(Class1, Class2) :-
 2191	jni_func(11, Class1, Class2, @(true)).
 2192
 2193%------------------------------------------------------------------------------
 2194
 2195%type   jNewBooleanArray(int, boolean_array)
 2196
 2197% jNewBooleanArray(+Length, -Array) :-
 2198
 2199jNewBooleanArray(Length, Array) :-
 2200	jni_func(175, Length, Array).
 2201
 2202%------------------------------------------------------------------------------
 2203
 2204%type   jNewByteArray(int, byte_array)
 2205
 2206% jNewByteArray(+Length, -Array) :-
 2207
 2208jNewByteArray(Length, Array) :-
 2209	jni_func(176, Length, Array).
 2210
 2211%------------------------------------------------------------------------------
 2212
 2213%type   jNewCharArray(int, char_array)
 2214
 2215% jNewCharArray(+Length, -Array) :-
 2216
 2217jNewCharArray(Length, Array) :-
 2218	jni_func(177, Length, Array).
 2219
 2220%------------------------------------------------------------------------------
 2221
 2222%type   jNewDoubleArray(int, double_array)
 2223
 2224% jNewDoubleArray(+Length, -Array) :-
 2225
 2226jNewDoubleArray(Length, Array) :-
 2227	jni_func(182, Length, Array).
 2228
 2229%------------------------------------------------------------------------------
 2230
 2231%type   jNewFloatArray(int, float_array)
 2232
 2233% jNewFloatArray(+Length, -Array) :-
 2234
 2235jNewFloatArray(Length, Array) :-
 2236	jni_func(181, Length, Array).
 2237
 2238%------------------------------------------------------------------------------
 2239
 2240%type   jNewIntArray(int, int_array)
 2241
 2242% jNewIntArray(+Length, -Array) :-
 2243
 2244jNewIntArray(Length, Array) :-
 2245	jni_func(179, Length, Array).
 2246
 2247%------------------------------------------------------------------------------
 2248
 2249%type   jNewLongArray(int, long_array)
 2250
 2251% jNewLongArray(+Length, -Array) :-
 2252
 2253jNewLongArray(Length, Array) :-
 2254	jni_func(180, Length, Array).
 2255
 2256%------------------------------------------------------------------------------
 2257
 2258%type   jNewObject(class, method_id, types, datums, object)
 2259
 2260% jNewObject(+Class, +MethodID, +Types, +Params, -Obj) :-
 2261
 2262jNewObject(Class, MethodID, Types, Params, Obj) :-
 2263	jni_params_put(Params, Types, ParamBuf),
 2264	jni_func(30, Class, MethodID, ParamBuf, Obj).
 2265
 2266%------------------------------------------------------------------------------
 2267
 2268%type   jNewObjectArray(int, class, object, object_array)
 2269
 2270% jNewObjectArray(+Len, +Class, +InitVal, -Array) :-
 2271
 2272jNewObjectArray(Len, Class, InitVal, Array) :-
 2273	jni_func(172, Len, Class, InitVal, Array).
 2274
 2275%------------------------------------------------------------------------------
 2276
 2277%type   jNewShortArray(int, short_array)
 2278
 2279% jNewShortArray(+Length, -Array) :-
 2280
 2281jNewShortArray(Length, Array) :-
 2282	jni_func(178, Length, Array).
 2283
 2284%------------------------------------------------------------------------------
 2285
 2286%type   jSetBooleanArrayRegion(boolean_array, int, int, boolean_buf)
 2287
 2288% jSetBooleanArrayRegion(+Array, +Start, +Len, +Buf) :-
 2289
 2290jSetBooleanArrayRegion(Array, Start, Len, Buf) :-
 2291	jni_void(207, Array, Start, Len, Buf).
 2292
 2293%------------------------------------------------------------------------------
 2294
 2295%type   jSetBooleanField(object, field_id, boolean)
 2296
 2297% jSetBooleanField(+Obj, +FieldID, +Rbool) :-
 2298
 2299jSetBooleanField(Obj, FieldID, Rbool) :-
 2300	jni_void(105, Obj, FieldID, Rbool).
 2301
 2302%------------------------------------------------------------------------------
 2303
 2304%type   jSetByteArrayRegion(byte_array, int, int, byte_buf)
 2305
 2306% jSetByteArrayRegion(+Array, +Start, +Len, +Buf) :-
 2307
 2308jSetByteArrayRegion(Array, Start, Len, Buf) :-
 2309	jni_void(208, Array, Start, Len, Buf).
 2310
 2311%------------------------------------------------------------------------------
 2312
 2313%type   jSetByteField(object, field_id, byte)
 2314
 2315% jSetByteField(+Obj, +FieldID, +Rbyte) :-
 2316
 2317jSetByteField(Obj, FieldID, Rbyte) :-
 2318	jni_void(106, Obj, FieldID, Rbyte).
 2319
 2320%------------------------------------------------------------------------------
 2321
 2322%type   jSetCharArrayRegion(char_array, int, int, char_buf)
 2323
 2324% jSetCharArrayRegion(+Array, +Start, +Len, +Buf) :-
 2325
 2326jSetCharArrayRegion(Array, Start, Len, Buf) :-
 2327	jni_void(209, Array, Start, Len, Buf).
 2328
 2329%------------------------------------------------------------------------------
 2330
 2331%type   jSetCharField(object, field_id, char)
 2332
 2333% jSetCharField(+Obj, +FieldID, +Rchar) :-
 2334
 2335jSetCharField(Obj, FieldID, Rchar) :-
 2336	jni_void(107, Obj, FieldID, Rchar).
 2337
 2338%------------------------------------------------------------------------------
 2339
 2340%type   jSetDoubleArrayRegion(double_array, int, int, double_buf)
 2341
 2342% jSetDoubleArrayRegion(+Array, +Start, +Len, +Buf) :-
 2343
 2344jSetDoubleArrayRegion(Array, Start, Len, Buf) :-
 2345	jni_void(214, Array, Start, Len, Buf).
 2346
 2347%------------------------------------------------------------------------------
 2348
 2349%type   jSetDoubleField(object, field_id, double)
 2350
 2351% jSetDoubleField(+Obj, +FieldID, +Rdouble) :-
 2352
 2353jSetDoubleField(Obj, FieldID, Rdouble) :-
 2354	jni_void(112, Obj, FieldID, Rdouble).
 2355
 2356%------------------------------------------------------------------------------
 2357
 2358%type   jSetFloatArrayRegion(float_array, int, int, float_buf)
 2359
 2360% jSetFloatArrayRegion(+Array, +Start, +Len, +Buf) :-
 2361
 2362jSetFloatArrayRegion(Array, Start, Len, Buf) :-
 2363	jni_void(213, Array, Start, Len, Buf).
 2364
 2365%------------------------------------------------------------------------------
 2366
 2367%type   jSetFloatField(object, field_id, float)
 2368
 2369% jSetFloatField(+Obj, +FieldID, +Rfloat) :-
 2370
 2371jSetFloatField(Obj, FieldID, Rfloat) :-
 2372	jni_void(111, Obj, FieldID, Rfloat).
 2373
 2374%------------------------------------------------------------------------------
 2375
 2376%type   jSetIntArrayRegion(int_array, int, int, int_buf)
 2377
 2378% jSetIntArrayRegion(+Array, +Start, +Len, +Buf) :-
 2379
 2380jSetIntArrayRegion(Array, Start, Len, Buf) :-
 2381	jni_void(211, Array, Start, Len, Buf).
 2382
 2383%------------------------------------------------------------------------------
 2384
 2385%type   jSetIntField(object, field_id, int)
 2386
 2387% jSetIntField(+Obj, +FieldID, +Rint) :-
 2388
 2389jSetIntField(Obj, FieldID, Rint) :-
 2390	jni_void(109, Obj, FieldID, Rint).
 2391
 2392%------------------------------------------------------------------------------
 2393
 2394%type   jSetLongArrayRegion(long_array, int, int, long_buf)
 2395
 2396% jSetLongArrayRegion(+Array, +Start, +Len, +Buf) :-
 2397
 2398jSetLongArrayRegion(Array, Start, Len, Buf) :-
 2399	jni_void(212, Array, Start, Len, Buf).
 2400
 2401%------------------------------------------------------------------------------
 2402
 2403%type   jSetLongField(object, field_id, long)
 2404
 2405% jSetLongField(+Obj, +FieldID, +Rlong) :-
 2406
 2407jSetLongField(Obj, FieldID, Rlong) :-
 2408	jni_void(110, Obj, FieldID, Rlong).
 2409
 2410%------------------------------------------------------------------------------
 2411
 2412%type   jSetObjectArrayElement(object_array, int, object)
 2413
 2414% jSetObjectArrayElement(+Array, +Index, +Obj) :-
 2415
 2416jSetObjectArrayElement(Array, Index, Obj) :-
 2417	jni_void(174, Array, Index, Obj).
 2418
 2419%------------------------------------------------------------------------------
 2420
 2421%type   jSetObjectField(object, field_id, object)
 2422
 2423% jSetObjectField(+Obj, +FieldID, +RObj) :-
 2424
 2425jSetObjectField(Obj, FieldID, Robj) :-
 2426	jni_void(104, Obj, FieldID, Robj).
 2427
 2428%------------------------------------------------------------------------------
 2429
 2430%type   jSetShortArrayRegion(short_array, int, int, short_buf)
 2431
 2432% jSetShortArrayRegion(+Array, +Start, +Len, +Buf) :-
 2433
 2434jSetShortArrayRegion(Array, Start, Len, Buf) :-
 2435	jni_void(210, Array, Start, Len, Buf).
 2436
 2437%------------------------------------------------------------------------------
 2438
 2439%type   jSetShortField(object, field_id, short)
 2440
 2441% jSetShortField(+Obj, +FieldID, +Rshort) :-
 2442
 2443jSetShortField(Obj, FieldID, Rshort) :-
 2444	jni_void(108, Obj, FieldID, Rshort).
 2445
 2446%------------------------------------------------------------------------------
 2447
 2448%type   jSetStaticBooleanField(class, field_id, boolean)
 2449
 2450% jSetStaticBooleanField(+Class, +FieldID, +Rbool) :-
 2451
 2452jSetStaticBooleanField(Class, FieldID, Rbool) :-
 2453	jni_void(155, Class, FieldID, Rbool).
 2454
 2455%------------------------------------------------------------------------------
 2456
 2457%type   jSetStaticByteField(class, field_id, byte)
 2458
 2459% jSetStaticByteField(+Class, +FieldID, +Rbyte) :-
 2460
 2461jSetStaticByteField(Class, FieldID, Rbyte) :-
 2462	jni_void(156, Class, FieldID, Rbyte).
 2463
 2464%------------------------------------------------------------------------------
 2465
 2466%type   jSetStaticCharField(class, field_id, char)
 2467
 2468% jSetStaticCharField(+Class, +FieldID, +Rchar) :-
 2469
 2470jSetStaticCharField(Class, FieldID, Rchar) :-
 2471	jni_void(157, Class, FieldID, Rchar).
 2472
 2473%------------------------------------------------------------------------------
 2474
 2475%type   jSetStaticDoubleField(class, field_id, double)
 2476
 2477% jSetStaticDoubleField(+Class, +FieldID, +Rdouble) :-
 2478
 2479jSetStaticDoubleField(Class, FieldID, Rdouble) :-
 2480	jni_void(162, Class, FieldID, Rdouble).
 2481
 2482%------------------------------------------------------------------------------
 2483
 2484%type   jSetStaticFloatField(class, field_id, float)
 2485
 2486% jSetStaticFloatField(+Class, +FieldID, +Rfloat) :-
 2487
 2488jSetStaticFloatField(Class, FieldID, Rfloat) :-
 2489	jni_void(161, Class, FieldID, Rfloat).
 2490
 2491%------------------------------------------------------------------------------
 2492
 2493%type   jSetStaticIntField(class, field_id, int)
 2494
 2495% jSetStaticIntField(+Class, +FieldID, +Rint) :-
 2496
 2497jSetStaticIntField(Class, FieldID, Rint) :-
 2498	jni_void(159, Class, FieldID, Rint).
 2499
 2500%------------------------------------------------------------------------------
 2501
 2502%type   jSetStaticLongField(class, field_id, long)
 2503
 2504% jSetStaticLongField(+Class, +FieldID, +Rlong) :-
 2505
 2506jSetStaticLongField(Class, FieldID, Rlong) :-
 2507	jni_void(160, Class, FieldID, Rlong).
 2508
 2509%------------------------------------------------------------------------------
 2510
 2511%type   jSetStaticObjectField(class, field_id, object)
 2512
 2513% jSetStaticObjectField(+Class, +FieldID, +Robj) :-
 2514
 2515jSetStaticObjectField(Class, FieldID, Robj) :-
 2516	jni_void(154, Class, FieldID, Robj).
 2517
 2518%------------------------------------------------------------------------------
 2519
 2520%type   jSetStaticShortField(class, field_id, short)
 2521
 2522% jSetStaticShortField(+Class, +FieldID, +Rshort) :-
 2523
 2524jSetStaticShortField(Class, FieldID, Rshort) :-
 2525	jni_void(158, Class, FieldID, Rshort).
 2526
 2527%------------------------------------------------------------------------------
 2528
 2529% jni_params_put(+Params, +Types, -ParamBuf)  :-
 2530%   the old form used a static buffer, hence was not re-entrant;
 2531%   the new form allocates a buffer of one jvalue per arg,
 2532%   puts the (converted) args into respective elements, then returns it
 2533%   (the caller is responsible for freeing it)
 2534
 2535jni_params_put(As, Ts, ParamBuf)     :-
 2536	jni_ensure_jvm,                     % in case e.g. NewStringUTF() is called
 2537	length(As, N),
 2538	jni_type_to_xput_code(jvalue, Xc), % Xc will be 15
 2539	jni_alloc_buffer(Xc, N, ParamBuf),
 2540	jni_params_put_1(As, 0, Ts, ParamBuf).
 2541
 2542%------------------------------------------------------------------------------
 2543
 2544% jni_params_put_1(+Params, +N, +JPLTypes, +ParamBuf) :-
 2545%   Params is a (full or partial) list of args-not-yet-stashed,
 2546%   and Types are their (JPL) types (e.g. 'boolean');
 2547%   N is the arg and buffer index (0+) at which the head of Params is to be stashed;
 2548%   the old form used a static buffer and hence was non-reentrant;
 2549%   the new form uses a dynamically allocated buffer (which oughta be freed after use)
 2550%
 2551%NB if the (user-provided) actual params were to be unsuitable for conversion
 2552%NB to the method-required types, this would fail silently (without freeing the buffer);
 2553%NB it's not clear whether the overloaded-method-resolution ensures that all args
 2554%NB are convertible
 2555
 2556jni_params_put_1([], _, [], _).
 2557
 2558jni_params_put_1([A|As], N, [Tjni|Ts], ParamBuf) :-     % type checking?
 2559	(   jni_type_to_xput_code(Tjni, Xc)
 2560	->  (       A = {Term}                              % a quoted general term?
 2561	->      jni_term_to_jref( Term, Ax)             % convert it to a @(Tag) ref to a new Term instance
 2562	;       A = Ax
 2563	),
 2564	jni_param_put(N, Xc, Ax, ParamBuf)              % foreign
 2565	;   fail                                            % oughta raise an exception?
 2566	),
 2567	N2 is N+1,
 2568	jni_params_put_1(As, N2, Ts, ParamBuf).             % stash remaining params (if any)
 2569
 2570%------------------------------------------------------------------------------
 2571
 2572% jni_type_to_xput_code(+JspType, -JniXputCode) :-
 2573%   NB JniXputCode determines widening and casting in foreign code
 2574%   NB the codes could be compiled into jni_method_spec_cache etc.
 2575%   instead of, or as well as, types (for - small - efficiency gain)
 2576
 2577jni_type_to_xput_code(boolean,      1).     % JNI_XPUT_BOOLEAN
 2578
 2579jni_type_to_xput_code(byte,         2).     % JNI_XPUT_BYTE
 2580
 2581jni_type_to_xput_code(char,         3).     % JNI_XPUT_CHAR
 2582
 2583jni_type_to_xput_code(short,        4).     % JNI_XPUT_SHORT
 2584
 2585jni_type_to_xput_code(int,          5).     % JNI_XPUT_INT
 2586
 2587jni_type_to_xput_code(long,         6).     % JNI_XPUT_LONG
 2588
 2589jni_type_to_xput_code(float,        7).     % JNI_XPUT_FLOAT
 2590
 2591jni_type_to_xput_code(double,       8).     % JNI_XPUT_DOUBLE
 2592
 2593jni_type_to_xput_code(class(_,_),   12).    % JNI_XPUT_REF
 2594
 2595jni_type_to_xput_code(array(_),     12).    % JNI_XPUT_REF
 2596
 2597jni_type_to_xput_code(jvalue,       15).    % JNI_XPUT_JVALUE
 2598
 2599%------------------------------------------------------------------------------
 2600
 2601% jpl_class_to_constructor_array(+Class, -MethodArray) :-
 2602%   might this be done more efficiently in foreign code? or in Java?
 2603
 2604jpl_class_to_constructor_array(Cx, Ma) :-
 2605	jpl_classname_to_class('java.lang.Class', CC),      % cacheable?
 2606	jGetMethodID(
 2607	CC,
 2608	getConstructors,
 2609	method([],array(class([java,lang,reflect],['Constructor']))),
 2610	MID
 2611	),                                                  % cacheable?
 2612	jCallObjectMethod(Cx, MID, [], [], Ma).
 2613
 2614%------------------------------------------------------------------------------
 2615
 2616% jpl_class_to_constructors(+Class, -Methods) :-
 2617
 2618jpl_class_to_constructors(Cx, Ms) :-
 2619	jpl_class_to_constructor_array(Cx, Ma),
 2620	jpl_object_array_to_list(Ma, Ms).
 2621
 2622%------------------------------------------------------------------------------
 2623
 2624% jpl_class_to_field_array(+Class, -FieldArray) :-
 2625
 2626jpl_class_to_field_array(Cx, Fa) :-
 2627	jpl_classname_to_class('java.lang.Class', CC),      % cacheable?
 2628	jGetMethodID(
 2629	CC,
 2630	getFields,
 2631	method([],array(class([java,lang,reflect],['Field']))),
 2632	MID
 2633	),                                                  % cacheable?
 2634	jCallObjectMethod(Cx, MID, [], [], Fa).
 2635
 2636%------------------------------------------------------------------------------
 2637
 2638% jpl_class_to_fields(+Class, -Fields) :-
 2639%   do this in Java (ditto for methods)?
 2640
 2641jpl_class_to_fields(C, Fs) :-
 2642	jpl_class_to_field_array(C, Fa),
 2643	jpl_object_array_to_list(Fa, Fs).
 2644
 2645%------------------------------------------------------------------------------
 2646
 2647% jpl_class_to_method_array(+Class, -MethodArray) :-
 2648%   migrate into foreign code for efficiency?
 2649
 2650jpl_class_to_method_array(Cx, Ma) :-
 2651	jpl_classname_to_class('java.lang.Class', CC),      % cacheable?
 2652	jGetMethodID(
 2653	CC,
 2654	getMethods,
 2655	method([],array(class([java,lang,reflect],['Method']))),
 2656	MID
 2657	),                                                  % cacheable?
 2658	jCallObjectMethod(Cx, MID, [], [], Ma).
 2659
 2660%------------------------------------------------------------------------------
 2661
 2662% jpl_class_to_methods(+Class, -Methods) :-
 2663%   also used for constructors
 2664%   do this in Java (ditto for fields)?
 2665
 2666jpl_class_to_methods(Cx, Ms) :-
 2667	jpl_class_to_method_array(Cx, Ma),
 2668	jpl_object_array_to_list(Ma, Ms).
 2669
 2670%------------------------------------------------------------------------------
 2671
 2672% jpl_constructor_to_modifiers(+Method, -Modifiers) :-
 2673%   migrate into foreign code for efficiency?
 2674
 2675jpl_constructor_to_modifiers(X, Ms) :-
 2676	jpl_classname_to_class('java.lang.reflect.Constructor', Cx),   % cached?
 2677	jpl_method_to_modifiers_1(X, Cx, Ms).
 2678
 2679%------------------------------------------------------------------------------
 2680
 2681% jpl_constructor_to_name(+Method, -Name) :-
 2682%   it is a JNI convention that each constructor behaves (at least,
 2683%   for reflection), as a method whose name is '<init>'
 2684
 2685jpl_constructor_to_name(_X, '<init>').
 2686
 2687%------------------------------------------------------------------------------
 2688
 2689% jpl_constructor_to_parameter_types(+Method, -ParameterTypes) :-
 2690%   migrate to foreign code for efficiency?
 2691
 2692jpl_constructor_to_parameter_types(X, Tfps) :-
 2693	jpl_classname_to_class('java.lang.reflect.Constructor', Cx),   % cached?
 2694	jpl_method_to_parameter_types_1(X, Cx, Tfps).
 2695
 2696%------------------------------------------------------------------------------
 2697
 2698% jpl_constructor_to_return_type(+Method, -Type) :-
 2699%   it is a JNI convention that, for the purposes of retrieving a MethodID,
 2700%   a constructor has a return type of 'void'
 2701
 2702jpl_constructor_to_return_type(_X, void).
 2703
 2704%------------------------------------------------------------------------------
 2705
 2706% jpl_field_spec(+Type, -Index, -Name, -Modifiers, -MID, -FieldType) :-
 2707%   I'm unsure whether arrays have fields, but if they do, this will handle them correctly
 2708
 2709jpl_field_spec(T, I, N, Mods, MID, Tf) :-
 2710	(   jpl_field_spec_is_cached(T)
 2711	->  jpl_field_spec_cache(T, I, N, Mods, MID, Tf)
 2712	;   jpl_type_to_class(T, C),
 2713	jpl_class_to_fields(C, Fs),
 2714	(   T = array(_BaseType)    % regardless of base type...
 2715	->  Tci = array(_)          % ...the "cache index" type is this
 2716	;   Tci = T
 2717	),
 2718	jpl_field_spec_1(C, Tci, Fs),
 2719	jpl_assert(jpl_field_spec_is_cached(Tci)),
 2720	jpl_field_spec_cache(Tci, I, N, Mods, MID, Tf)
 2721	).
 2722
 2723%------------------------------------------------------------------------------
 2724
 2725jpl_field_spec_1(C, Tci, Fs) :-
 2726	(   nth1(I, Fs, F),
 2727	jpl_field_to_name(F, N),
 2728	jpl_field_to_modifiers(F, Mods),
 2729	jpl_field_to_type(F, Tf),
 2730	(   member(static, Mods)
 2731	->  jGetStaticFieldID(C, N, Tf, MID)
 2732	;   jGetFieldID(C, N, Tf, MID)
 2733	),
 2734	jpl_assert(jpl_field_spec_cache(Tci,I,N,Mods,MID,Tf)),
 2735	fail
 2736	;   true
 2737	).
 2738
 2739%------------------------------------------------------------------------------
 2740
 2741:- dynamic jpl_field_spec_cache/6.      % document this...
 2742
 2743%------------------------------------------------------------------------------
 2744
 2745:- dynamic jpl_field_spec_is_cached/1.  % document this...
 2746
 2747%------------------------------------------------------------------------------
 2748
 2749%type   jpl_field_to_modifiers(object, ordset(modifier))
 2750
 2751% jpl_field_to_modifiers(+Field, -Modifiers) :-
 2752
 2753jpl_field_to_modifiers(F, Ms) :-
 2754	jpl_classname_to_class('java.lang.reflect.Field', Cf),
 2755	jpl_method_to_modifiers_1(F, Cf, Ms).
 2756
 2757%------------------------------------------------------------------------------
 2758
 2759% jpl_field_to_name(+Field, -Name) :-
 2760
 2761jpl_field_to_name(F, N) :-
 2762	jpl_classname_to_class('java.lang.reflect.Field', Cf),
 2763	jpl_member_to_name_1(F, Cf, N).
 2764
 2765%------------------------------------------------------------------------------
 2766
 2767%type   jpl_field_to_type(object, type)
 2768
 2769% jpl_field_to_type(+Field, -Type) :-
 2770
 2771jpl_field_to_type(F, Tf) :-
 2772	jpl_classname_to_class('java.lang.reflect.Field', Cf),
 2773	jGetMethodID(Cf, getType, method([],class([java,lang],['Class'])), MID),
 2774	jCallObjectMethod(F, MID, [], [], Cr),
 2775	jpl_class_to_type(Cr, Tf).
 2776
 2777%------------------------------------------------------------------------------
 2778
 2779%type   jpl_method_spec(type, integer, name, arity, ordset(modifier), method_id, type, list(type))
 2780
 2781% jpl_method_spec(+Type, -Index, -Name, -Arity, -Modifiers, -MID, -ReturnType, -ParameterTypes) :-
 2782%   generates pertinent details of all accessible methods of Type (class/2 or array/1),
 2783%   populating or using the cache as appropriate
 2784
 2785jpl_method_spec(T, I, N, A, Mods, MID, Tr, Tfps) :-
 2786	(   jpl_method_spec_is_cached(T)
 2787	->  jpl_method_spec_cache(T, I, N, A, Mods, MID, Tr, Tfps)
 2788	;   jpl_type_to_class(T, C),
 2789	jpl_class_to_constructors(C, Xs),
 2790	jpl_class_to_methods(C, Ms),
 2791	(   T = array(_BaseType)    % regardless of base type...
 2792	->  Tci = array(_)          % ...the "cache index" type is this
 2793	;   Tci = T
 2794	),
 2795	jpl_method_spec_1(C, Tci, Xs, Ms),
 2796	jpl_assert(jpl_method_spec_is_cached(Tci)),
 2797	jpl_method_spec_cache(Tci, I, N, A, Mods, MID, Tr, Tfps)
 2798	).
 2799
 2800%------------------------------------------------------------------------------
 2801
 2802%type   jpl_method_spec_1(class, partial_type, list(method), list(method))
 2803
 2804% jpl_method_spec_1(+ClassObject, +CacheIndexType, +Constructors, +Methods) :-
 2805%   if the original type is e.g. array(byte) then CacheIndexType is array(_) else it is that type;
 2806
 2807jpl_method_spec_1(C, Tci, Xs, Ms) :-
 2808	(   (   nth1(I, Xs, X),     % generate constructors, numbered from 1
 2809	    jpl_constructor_to_name(X, N),
 2810	    jpl_constructor_to_modifiers(X, Mods),
 2811	    jpl_constructor_to_return_type(X, Tr),
 2812	    jpl_constructor_to_parameter_types(X, Tfps)
 2813	;   length(Xs, J0),
 2814	    nth1(J, Ms, M),     % generate members, continuing numbering
 2815	    I is J0+J,
 2816	    jpl_method_to_name(M, N),
 2817	    jpl_method_to_modifiers(M, Mods),
 2818	    jpl_method_to_return_type(M, Tr),
 2819	    jpl_method_to_parameter_types(M, Tfps)
 2820	),
 2821	length(Tfps, A), % arity
 2822	(   member(static, Mods)
 2823	->  jGetStaticMethodID(C, N, method(Tfps,Tr), MID)
 2824	;   jGetMethodID(C, N, method(Tfps,Tr), MID)
 2825	),
 2826	jpl_assert(jpl_method_spec_cache(Tci,I,N,A,Mods,MID,Tr,Tfps)),
 2827	fail
 2828	;   true
 2829	).
 2830
 2831%------------------------------------------------------------------------------
 2832
 2833:- dynamic jpl_method_spec_cache/8. 2834
 2835%------------------------------------------------------------------------------
 2836
 2837:- dynamic jpl_method_spec_is_cached/1. 2838
 2839%------------------------------------------------------------------------------
 2840
 2841% jpl_method_to_modifiers(+Method, -ModifierSet) :-
 2842
 2843jpl_method_to_modifiers(M, Ms) :-
 2844	jpl_classname_to_class('java.lang.reflect.Method', Cm),
 2845	jpl_method_to_modifiers_1(M, Cm, Ms).
 2846
 2847%------------------------------------------------------------------------------
 2848
 2849%type   jpl_method_to_modifiers_1(object, object, ordset(modifier))
 2850
 2851% jpl_method_to_modifiers_1(+Method, +ConstructorClass, -ModifierSet) :-
 2852
 2853jpl_method_to_modifiers_1(XM, Cxm, Ms) :-
 2854	jGetMethodID(Cxm, getModifiers, method([],int), MID),
 2855	jCallIntMethod(XM, MID, [], [], I),
 2856	jpl_modifier_int_to_modifiers(I, Ms).
 2857
 2858%------------------------------------------------------------------------------
 2859
 2860% jpl_method_to_name(+Method, -Name) :-
 2861
 2862jpl_method_to_name(M, N) :-
 2863	jpl_classname_to_class('java.lang.reflect.Method', CM),
 2864	jpl_member_to_name_1(M, CM, N).
 2865
 2866%------------------------------------------------------------------------------
 2867
 2868jpl_member_to_name_1(M, CM, N) :-
 2869	jGetMethodID(CM, getName, method([],class([java,lang],['String'])), MID),
 2870	jCallObjectMethod(M, MID, [], [], N).
 2871
 2872%------------------------------------------------------------------------------
 2873
 2874% jpl_method_to_parameter_types(+Method, -Types) :-
 2875
 2876jpl_method_to_parameter_types(M, Tfps) :-
 2877	jpl_classname_to_class('java.lang.reflect.Method', Cm),
 2878	jpl_method_to_parameter_types_1(M, Cm, Tfps).
 2879
 2880%------------------------------------------------------------------------------
 2881
 2882% jpl_method_to_parameter_types_1(+XM, +Cxm, -Tfps) :-
 2883%   XM is (a JPL ref to) an instance of java.lang.reflect.[Constructor|Method]
 2884
 2885jpl_method_to_parameter_types_1(XM, Cxm, Tfps) :-
 2886	jGetMethodID(Cxm, getParameterTypes, method([],array(class([java,lang],['Class']))), MID),
 2887	jCallObjectMethod(XM, MID, [], [], Atp),
 2888	jpl_object_array_to_list(Atp, Ctps),
 2889	jpl_classes_to_types(Ctps, Tfps).
 2890
 2891%------------------------------------------------------------------------------
 2892
 2893% jpl_method_to_return_type(+Method, -Type) :-
 2894
 2895jpl_method_to_return_type(M, Tr) :-
 2896	jpl_classname_to_class('java.lang.reflect.Method', Cm),
 2897	jGetMethodID(Cm, getReturnType, method([],class([java,lang],['Class'])), MID),
 2898	jCallObjectMethod(M, MID, [], [], Cr),
 2899	jpl_class_to_type(Cr, Tr).
 2900
 2901%------------------------------------------------------------------------------
 2902
 2903jpl_modifier_bit(public,        0x001).
 2904jpl_modifier_bit(private,       0x002).
 2905jpl_modifier_bit(protected,     0x004).
 2906jpl_modifier_bit(static,        0x008).
 2907jpl_modifier_bit(final,         0x010).
 2908jpl_modifier_bit(synchronized,  0x020).
 2909jpl_modifier_bit(volatile,      0x040).
 2910jpl_modifier_bit(transient,     0x080).
 2911jpl_modifier_bit(native,        0x100).
 2912jpl_modifier_bit(interface,     0x200).
 2913jpl_modifier_bit(abstract,      0x400).
 2914
 2915%------------------------------------------------------------------------------
 2916
 2917%type   jpl_modifier_int_to_modifiers(integer, ordset(modifier))
 2918
 2919% jpl_modifier_int_to_modifiers(+Int, -ModifierSet) :-
 2920%   ModifierSet is an ordered (hence canonical) list,
 2921%   possibly empty (although I suspect never in practice?),
 2922%   of modifier atoms, e.g. [public,static]
 2923
 2924jpl_modifier_int_to_modifiers(I, Ms) :-
 2925	setof(
 2926	M,                                  %  should use e.g. set_of_all/3
 2927	B^(jpl_modifier_bit(M, B),
 2928	    (B /\ I) =\= 0
 2929	),
 2930	Ms
 2931	).
 2932
 2933%------------------------------------------------------------------------------
 2934
 2935% jpl_servlet_byref(+Config, +Request, +Response) :-
 2936%   this serves the "byref" servlet demo,
 2937%   exemplifying one tactic for implementing a servlet in Prolog
 2938%   by accepting the Request and Response objects as JPL references
 2939%   and accessing their members via JPL as required;
 2940%   see also jpl_servlet_byval/3
 2941
 2942jpl_servlet_byref(Config, Request, Response) :-
 2943	jpl_call(Config, getServletContext, [], Context),
 2944
 2945	jpl_call(Response, setStatus, [200], _),
 2946	jpl_call(Response, setContentType, ['text/html'], _),
 2947	jpl_call(Response, getWriter, [], W),
 2948
 2949	jpl_call(W, println, ['<html><head></head><body><h2>jpl_servlet_byref/3 says:</h2><pre>'], _),
 2950
 2951	jpl_call(W, println, ['\nservlet context stuff:'], _),
 2952
 2953	jpl_call(Context, getInitParameterNames, [], ContextInitParameterNameEnum),
 2954	jpl_enumeration_to_list(ContextInitParameterNameEnum, ContextInitParameterNames),
 2955	length(ContextInitParameterNames, NContextInitParameterNames),
 2956	concat_atom(['\tContext.InitParameters = ',NContextInitParameterNames], NContextInitParameterNamesMsg),
 2957	jpl_call(W, println, [NContextInitParameterNamesMsg], _),
 2958	(   member(ContextInitParameterName, ContextInitParameterNames),
 2959	jpl_call(Context, getInitParameter, [ContextInitParameterName], ContextInitParameter),
 2960	concat_atom(['\t\tContext.InitParameter[',ContextInitParameterName,'] = ',ContextInitParameter], ContextInitParameterMsg),
 2961	jpl_call(W, println, [ContextInitParameterMsg], _),
 2962	fail
 2963	;   true
 2964	),
 2965
 2966	jpl_call(Context, getMajorVersion, [], MajorVersion),
 2967	concat_atom(['\tContext.MajorVersion = ',MajorVersion], MajorVersionMsg),
 2968	jpl_call(W, println, [MajorVersionMsg], _),
 2969
 2970	jpl_call(Context, getMinorVersion, [], MinorVersion),
 2971	concat_atom(['\tContext.MinorVersion = ',MinorVersion], MinorVersionMsg),
 2972	jpl_call(W, println, [MinorVersionMsg], _),
 2973
 2974	jpl_call(Context, getServerInfo, [], ServerInfo),
 2975	concat_atom(['\tContext.ServerInfo = ',ServerInfo], ServerInfoMsg),
 2976	jpl_call(W, println, [ServerInfoMsg], _),
 2977
 2978	jpl_call(W, println, ['\nservlet config stuff:'], _),
 2979
 2980	jpl_call(Config, getServletName, [], ServletName),
 2981	(   ServletName == @(null)
 2982	->  ServletNameAtom = null
 2983	;   ServletNameAtom = ServletName
 2984	),
 2985	concat_atom(['\tConfig.ServletName = ',ServletNameAtom], ServletNameMsg),
 2986	jpl_call(W, println, [ServletNameMsg], _),
 2987
 2988	jpl_call(Config, getInitParameterNames, [], ConfigInitParameterNameEnum),
 2989	jpl_enumeration_to_list(ConfigInitParameterNameEnum, ConfigInitParameterNames),
 2990	length(ConfigInitParameterNames, NConfigInitParameterNames),
 2991	concat_atom(['\tConfig.InitParameters = ',NConfigInitParameterNames], NConfigInitParameterNamesMsg),
 2992	jpl_call(W, println, [NConfigInitParameterNamesMsg], _),
 2993	(   member(ConfigInitParameterName, ConfigInitParameterNames),
 2994	jpl_call(Config, getInitParameter, [ConfigInitParameterName], ConfigInitParameter),
 2995	concat_atom(['\t\tConfig.InitParameter[',ConfigInitParameterName,'] = ',ConfigInitParameter], ConfigInitParameterMsg),
 2996	jpl_call(W, println, [ConfigInitParameterMsg], _),
 2997	fail
 2998	;   true
 2999	),
 3000
 3001	jpl_call(W, println, ['\nrequest stuff:'], _),
 3002
 3003	jpl_call(Request, getAttributeNames, [], AttributeNameEnum),
 3004	jpl_enumeration_to_list(AttributeNameEnum, AttributeNames),
 3005	length(AttributeNames, NAttributeNames),
 3006	concat_atom(['\tRequest.Attributes = ',NAttributeNames], NAttributeNamesMsg),
 3007	jpl_call(W, println, [NAttributeNamesMsg], _),
 3008	(   member(AttributeName, AttributeNames),
 3009	jpl_call(Request, getAttribute, [AttributeName], Attribute),
 3010	jpl_call(Attribute, toString, [], AttributeString),
 3011	concat_atom(['\t\tRequest.Attribute[',AttributeName,'] = ',AttributeString], AttributeMsg),
 3012	jpl_call(W, println, [AttributeMsg], _),
 3013	fail
 3014	;   true
 3015	),
 3016
 3017	jpl_call(Request, getCharacterEncoding, [], CharacterEncoding),
 3018	(   CharacterEncoding == @(null)
 3019	->  CharacterEncodingAtom = ''
 3020	;   CharacterEncodingAtom = CharacterEncoding
 3021	),
 3022	concat_atom(['\tRequest.CharacterEncoding',' = ',CharacterEncodingAtom], CharacterEncodingMsg),
 3023	jpl_call(W, println, [CharacterEncodingMsg], _),
 3024
 3025	jpl_call(Request, getContentLength, [], ContentLength),
 3026	concat_atom(['\tRequest.ContentLength',' = ',ContentLength], ContentLengthMsg),
 3027	jpl_call(W, println, [ContentLengthMsg], _),
 3028
 3029	jpl_call(Request, getContentType, [], ContentType),
 3030	(   ContentType == @(null)
 3031	->  ContentTypeAtom = ''
 3032	;   ContentTypeAtom = ContentType
 3033	),
 3034	concat_atom(['\tRequest.ContentType',' = ',ContentTypeAtom], ContentTypeMsg),
 3035	jpl_call(W, println, [ContentTypeMsg], _),
 3036
 3037	jpl_call(Request, getParameterNames, [], ParameterNameEnum),
 3038	jpl_enumeration_to_list(ParameterNameEnum, ParameterNames),
 3039	length(ParameterNames, NParameterNames),
 3040	concat_atom(['\tRequest.Parameters = ',NParameterNames], NParameterNamesMsg),
 3041	jpl_call(W, println, [NParameterNamesMsg], _),
 3042	(   member(ParameterName, ParameterNames),
 3043	jpl_call(Request, getParameter, [ParameterName], Parameter),
 3044	concat_atom(['\t\tRequest.Parameter[',ParameterName,'] = ',Parameter], ParameterMsg),
 3045	jpl_call(W, println, [ParameterMsg], _),
 3046	fail
 3047	;   true
 3048	),
 3049
 3050	jpl_call(Request, getProtocol, [], Protocol),
 3051	concat_atom(['\tRequest.Protocol',' = ',Protocol], ProtocolMsg),
 3052	jpl_call(W, println, [ProtocolMsg], _),
 3053
 3054	jpl_call(Request, getRemoteAddr, [], RemoteAddr),
 3055	concat_atom(['\tRequest.RemoteAddr',' = ',RemoteAddr], RemoteAddrMsg),
 3056	jpl_call(W, println, [RemoteAddrMsg], _),
 3057
 3058	jpl_call(Request, getRemoteHost, [], RemoteHost),
 3059	concat_atom(['\tRequest.RemoteHost',' = ',RemoteHost], RemoteHostMsg),
 3060	jpl_call(W, println, [RemoteHostMsg], _),
 3061
 3062	jpl_call(Request, getScheme, [], Scheme),
 3063	concat_atom(['\tRequest.Scheme',' = ',Scheme], SchemeMsg),
 3064	jpl_call(W, println, [SchemeMsg], _),
 3065
 3066	jpl_call(Request, getServerName, [], ServerName),
 3067	concat_atom(['\tRequest.ServerName',' = ',ServerName], ServerNameMsg),
 3068	jpl_call(W, println, [ServerNameMsg], _),
 3069
 3070	jpl_call(Request, getServerPort, [], ServerPort),
 3071	concat_atom(['\tRequest.ServerPort',' = ',ServerPort], ServerPortMsg),
 3072	jpl_call(W, println, [ServerPortMsg], _),
 3073
 3074	jpl_call(Request, isSecure, [], @(Secure)),
 3075	concat_atom(['\tRequest.Secure',' = ',Secure], SecureMsg),
 3076	jpl_call(W, println, [SecureMsg], _),
 3077
 3078	jpl_call(W, println, ['\nHTTP request stuff:'], _),
 3079
 3080	jpl_call(Request, getAuthType, [], AuthType),
 3081	(   AuthType == @(null)
 3082	->  AuthTypeAtom = ''
 3083	;   AuthTypeAtom = AuthType
 3084	),
 3085	concat_atom(['\tRequest.AuthType',' = ',AuthTypeAtom], AuthTypeMsg),
 3086	jpl_call(W, println, [AuthTypeMsg], _),
 3087
 3088	jpl_call(Request, getContextPath, [], ContextPath),
 3089	(   ContextPath == @(null)
 3090	->  ContextPathAtom = ''
 3091	;   ContextPathAtom = ContextPath
 3092	),
 3093	concat_atom(['\tRequest.ContextPath',' = ',ContextPathAtom], ContextPathMsg),
 3094	jpl_call(W, println, [ContextPathMsg], _),
 3095
 3096	jpl_call(Request, getCookies, [], CookieArray),
 3097	(   CookieArray == @(null)
 3098	->  Cookies = []
 3099	;   jpl_array_to_list(CookieArray, Cookies)
 3100	),
 3101	length(Cookies, NCookies),
 3102	concat_atom(['\tRequest.Cookies',' = ',NCookies], NCookiesMsg),
 3103	jpl_call(W, println, [NCookiesMsg], _),
 3104	(   nth0(NCookie, Cookies, Cookie),
 3105	concat_atom(['\t\tRequest.Cookie[',NCookie,']'], CookieMsg),
 3106	jpl_call(W, println, [CookieMsg], _),
 3107
 3108	jpl_call(Cookie, getName, [], CookieName),
 3109	concat_atom(['\t\t\tRequest.Cookie.Name = ',CookieName], CookieNameMsg),
 3110	jpl_call(W, println, [CookieNameMsg], _),
 3111
 3112	jpl_call(Cookie, getValue, [], CookieValue),
 3113	concat_atom(['\t\t\tRequest.Cookie.Value = ',CookieValue], CookieValueMsg),
 3114	jpl_call(W, println, [CookieValueMsg], _),
 3115
 3116	jpl_call(Cookie, getPath, [], CookiePath),
 3117	(   CookiePath == @(null)
 3118	->  CookiePathAtom = ''
 3119	;   CookiePathAtom = CookiePath
 3120	),
 3121	concat_atom(['\t\t\tRequest.Cookie.Path = ',CookiePathAtom], CookiePathMsg),
 3122	jpl_call(W, println, [CookiePathMsg], _),
 3123
 3124	jpl_call(Cookie, getComment, [], CookieComment),
 3125	(   CookieComment == @(null)
 3126	->  CookieCommentAtom = ''
 3127	;   CookieCommentAtom = CookieComment
 3128	),
 3129	concat_atom(['\t\t\tRequest.Cookie.Comment = ',CookieCommentAtom], CookieCommentMsg),
 3130	jpl_call(W, println, [CookieCommentMsg], _),
 3131
 3132	jpl_call(Cookie, getDomain, [], CookieDomain),
 3133	(   CookieDomain == @(null)
 3134	->  CookieDomainAtom = ''
 3135	;   CookieDomainAtom = CookieDomain
 3136	),
 3137	concat_atom(['\t\t\tRequest.Cookie.Domain = ',CookieDomainAtom], CookieDomainMsg),
 3138	jpl_call(W, println, [CookieDomainMsg], _),
 3139
 3140	jpl_call(Cookie, getMaxAge, [], CookieMaxAge),
 3141	concat_atom(['\t\t\tRequest.Cookie.MaxAge = ',CookieMaxAge], CookieMaxAgeMsg),
 3142	jpl_call(W, println, [CookieMaxAgeMsg], _),
 3143
 3144	jpl_call(Cookie, getVersion, [], CookieVersion),
 3145	concat_atom(['\t\t\tRequest.Cookie.Version = ',CookieVersion], CookieVersionMsg),
 3146	jpl_call(W, println, [CookieVersionMsg], _),
 3147
 3148	jpl_call(Cookie, getSecure, [], @(CookieSecure)),
 3149	concat_atom(['\t\t\tRequest.Cookie.Secure',' = ',CookieSecure], CookieSecureMsg),
 3150	jpl_call(W, println, [CookieSecureMsg], _),
 3151
 3152	fail
 3153	;   true
 3154	),
 3155
 3156	jpl_call(W, println, ['</pre></body></html>'], _),
 3157
 3158	true.
 3159
 3160%------------------------------------------------------------------------------
 3161
 3162% jpl_servlet_byval(+MultiMap, -ContentType, -BodyAtom) :-
 3163%   this exemplifies an alternative (to jpl_servlet_byref) tactic
 3164%   for implementing a servlet in Prolog;
 3165%   most Request fields are extracted in Java before this is called,
 3166%   and passed in as a multimap (a map, some of whose values are maps)
 3167
 3168jpl_servlet_byval(MM, CT, Ba) :-
 3169	CT = 'text/html',
 3170	multimap_to_atom(MM, MMa),
 3171	concat_atom(['<html><head></head><body>',
 3172		     '<h2>jpl_servlet_byval/3 says:</h2><pre>',
 3173		     MMa,
 3174		     '</pre></body></html>'
 3175		    ], Ba).
 3176
 3177%------------------------------------------------------------------------------
 3178
 3179%type   jpl_cache_type_of_ref(jpl_type, ref)
 3180
 3181% jpl_cache_type_of_ref(+Type, +Ref) :-
 3182%   Type must be a proper (concrete) JPL type;
 3183%   Ref must be a proper JPL reference (not void);
 3184%   Type is memoed (if policy so dictates) as the type of the referenced object (unless it's null)
 3185%   by iref (so as not to disable atom-based GC)
 3186%   NB obsolete lemmas must be watched-out-for and removed
 3187
 3188jpl_cache_type_of_ref(T, @(Tag)) :-
 3189	(   jpl_assert_policy( jpl_iref_type_cache(_,_), no)
 3190	->  true
 3191	;   \+ ground(T)                            % shouldn't happen (implementation error)
 3192	->  write('[jpl_cache_type_of_ref/2: arg 1 is not ground]'), nl,    % oughta throw an exception
 3193	fail
 3194	;   \+ atom(Tag)                            % shouldn't happen (implementation error)
 3195	->  write('[jpl_cache_type_of_ref/2: arg 2 is not an atomic-tag ref]'), nl, % oughta throw an exception
 3196	fail
 3197	;   Tag == null                             % a null ref? (this is valid)
 3198	->  true                                    % silently ignore it
 3199	;   jni_tag_to_iref(Tag, Iref)
 3200	->  (   jpl_iref_type_cache(Iref, TC)       % we expect TC == T
 3201	->  (   T == TC
 3202	    ->  true
 3203	    ; % write('[JPL: found obsolete tag-type lemma...]'), nl,   % or keep statistics? (why?)
 3204		retractall(jpl_iref_type_cache(Iref,_)),
 3205		jpl_assert(jpl_iref_type_cache(Iref,T))
 3206	    )
 3207	;   jpl_assert(jpl_iref_type_cache(Iref,T))
 3208	)
 3209	;   write('[jpl_cache_type_of_ref/2: jni_tagatom_to_iref(Tag,_) failed]'), nl,  % oughta throw an exception
 3210	fail
 3211	).
 3212
 3213%------------------------------------------------------------------------------
 3214
 3215% jpl_class_tag_type_cache(-Tag, -ClassType) :-
 3216%   Tag is the tag part of an @(Tag) reference
 3217%   to a JVM instance of java.lang.Class
 3218%   which denotes ClassType;
 3219%   we index on Tag rather than on Iref so as to keep these objects around
 3220%   even after an atom garbage collection
 3221%   (if needed once, they are likely to be needed again)
 3222
 3223:- dynamic jpl_class_tag_type_cache/2. 3224
 3225%------------------------------------------------------------------------------
 3226
 3227% jpl_class_to_ancestor_classes(+Class, -AncestorClasses) :-
 3228%   AncestorClasses will be a list of (JPL references to) instances of java.lang.Class
 3229%   denoting the "implements" lineage (?), nearest first
 3230%   (the first member denotes the class which Class directly implements,
 3231%   the next (if any) denotes the class which *that* class implements,
 3232%   and so on to java.lang.Object)
 3233
 3234jpl_class_to_ancestor_classes(C, Cas) :-
 3235	(   jpl_class_to_super_class(C, Ca)
 3236	->  Cas = [Ca|Cas2],
 3237	jpl_class_to_ancestor_classes(Ca, Cas2)
 3238	;   Cas = []
 3239	).
 3240
 3241%------------------------------------------------------------------------------
 3242
 3243% jpl_class_to_classname(+Class, -ClassName) :-
 3244%   Class is a reference to a class object;
 3245%   ClassName is its canonical (?) source-syntax (dotted) name,
 3246%   e.g. 'java.util.Date'
 3247%   not used outside jni_junk and jpl_test (is this (still) true?);
 3248%   oughta use the available caches (but their indexing doesn't suit)
 3249
 3250jpl_class_to_classname(C, CN) :-
 3251	jpl_call(C, getName, [], CN).
 3252
 3253%------------------------------------------------------------------------------
 3254
 3255% jpl_class_to_raw_classname(+Class, -ClassName) :-
 3256%   hmm, I forget exactly what a "raw" classname is...
 3257
 3258jpl_class_to_raw_classname(Cobj, CN) :-
 3259	jpl_classname_to_class('java.lang.Class', CC),      % cached?
 3260	jGetMethodID(CC, getName, method([],class([java,lang],['String'])), MIDgetName),
 3261	jCallObjectMethod(Cobj, MIDgetName, [], [], S),
 3262	S = CN.
 3263
 3264%------------------------------------------------------------------------------
 3265
 3266% jpl_class_to_raw_classname_chars(+Class, -ClassnameChars) :-
 3267%   Class is a reference to a class object;
 3268%   ClassnameChars is a chars representation of its dotted name, e.g.
 3269%   "java.util.Date"
 3270
 3271jpl_class_to_raw_classname_chars(Cobj, CsCN) :-
 3272	jpl_class_to_raw_classname(Cobj, CN),
 3273	atom_codes(CN, CsCN).
 3274
 3275%------------------------------------------------------------------------------
 3276
 3277jpl_class_to_super_class(C, Cx) :-
 3278	jGetSuperclass(C, Cx),
 3279	Cx \== @(null),         % as returned when C is java.lang.Object, i.e. no superclass
 3280	jpl_cache_type_of_ref(class([java,lang],['Class']), Cx).
 3281
 3282%------------------------------------------------------------------------------
 3283
 3284% jpl_class_to_type(+ClassObject, -Type) :-
 3285%   ClassObject is a reference to a class object of Type
 3286%   NB should ensure that, if not found in cache, then cache is updated;
 3287%   intriguingly (?), getParameterTypes returns class objects with names
 3288%   'boolean', 'byte' etc. and even 'void' (?!)
 3289
 3290jpl_class_to_type(@(Tag), Type) :-
 3291	(   jpl_class_tag_type_cache(Tag, Tx)
 3292	->  true
 3293	;   jpl_class_to_raw_classname_chars(@(Tag), Cs),   % uncached
 3294	jpl_classname_chars_to_type(Cs, Tr),
 3295	jpl_type_to_canonical_type(Tr, Tx),             % map e.g. class([],[byte]) -> byte
 3296	jpl_assert(jpl_class_tag_type_cache(Tag,Tx))
 3297	->  true    % the elseif goal should be determinate, but just in case...
 3298	),
 3299	Type = Tx.
 3300
 3301%------------------------------------------------------------------------------
 3302
 3303jpl_classes_to_types([], []).
 3304
 3305jpl_classes_to_types([C|Cs], [T|Ts]) :-
 3306	jpl_class_to_type(C, T),
 3307	jpl_classes_to_types(Cs, Ts).
 3308
 3309%------------------------------------------------------------------------------
 3310
 3311jpl_classname_chars_to_type(Cs, Type) :-
 3312	(   phrase(jpl_type_classname_1(Type), Cs)
 3313	->  true
 3314	).
 3315
 3316%------------------------------------------------------------------------------
 3317
 3318% jpl_classname_to_class(+ClassName, -Class) :-
 3319%   ClassName unambiguously represents a class,
 3320%   e.g. 'java.lang.String'
 3321%   Class is a (canonical) reference to the corresponding class object;
 3322%   uses caches where the class is already encountered
 3323
 3324jpl_classname_to_class(N, C) :-
 3325	jpl_classname_to_type(N, T),    % cached
 3326	jpl_type_to_class(T, C).        % cached
 3327
 3328%------------------------------------------------------------------------------
 3329
 3330% jpl_classname_to_type(+Classname, -Type) :-
 3331%   Classname is a source-syntax (dotted) class name,
 3332%   e.g. 'java.util.Date', '[java.util.Date' or '[L'
 3333%   Type is its corresponding JPL type structure,
 3334%   e.g. class([java,util],['Date']), array(class([java,util],['Date'])), array(long)
 3335%
 3336%thinks
 3337%   by "classname" do I mean "typename"?
 3338%   should this throw an exception for unbound CN? is this public API?
 3339
 3340jpl_classname_to_type(CN, T) :-
 3341	(   jpl_classname_type_cache(CN, Tx)
 3342	->  Tx = T
 3343	;   atom_codes(CN, CsCN),
 3344	phrase(jpl_type_classname_1(T), CsCN)
 3345	->  jpl_assert(jpl_classname_type_cache(CN,T)),
 3346	true
 3347	).
 3348
 3349%------------------------------------------------------------------------------
 3350
 3351% jpl_classname_type_cache( -Classname, -Type) :-
 3352%   Classname is the atomic name of Type;
 3353%   NB may denote a class which cannot be found
 3354
 3355:- dynamic jpl_classname_type_cache/2. 3356
 3357%------------------------------------------------------------------------------
 3358
 3359% jpl_datum_to_type(+Datum, -Type) :-
 3360%   Datum must be a proper JPL representation
 3361%   of an instance of one (or more) Java types;
 3362%   Type is the unique most specialised type of which Datum denotes an instance;
 3363%   N.B. 3 is an instance of byte, char, short, int and long,
 3364%   of which byte and char are the joint, overlapping most specialised types,
 3365%   so this relates 3 to the pseudo subtype 'char_byte';
 3366%   see jpl_type_to_preferred_concrete_type/2 for converting inferred types
 3367%   to instantiable types
 3368
 3369jpl_datum_to_type(D, T) :-
 3370	(   jpl_value_to_type(D, T)
 3371	->  true
 3372	;   jpl_ref_to_type(D, T)
 3373	->  true
 3374	;   nonvar( D),
 3375	D = {Term}
 3376	->  (   cyclic_term(Term)
 3377	->  throw(error(type_error(acyclic,Term),
 3378			context(jpl_datum_to_type/2,'must be acyclic')))
 3379	;   atom( Term)
 3380	->  T = class([org,jpl7],['Atom'])
 3381	;   integer( Term)
 3382	->  T = class([org,jpl7],['Integer'])
 3383	;   float( Term)
 3384	->  T = class([org,jpl7],['Float'])
 3385	;   var( Term)
 3386	->  T = class([org,jpl7],['Variable'])
 3387	;   T = class([org,jpl7],['Compound'])
 3388	)
 3389	).
 3390
 3391%------------------------------------------------------------------------------
 3392
 3393jpl_datums_to_most_specific_common_ancestor_type([D], T) :-
 3394	jpl_datum_to_type(D, T).
 3395
 3396jpl_datums_to_most_specific_common_ancestor_type([D1,D2|Ds], T0) :-
 3397	jpl_datum_to_type(D1, T1),
 3398	jpl_type_to_ancestor_types(T1, Ts1),
 3399	jpl_datums_to_most_specific_common_ancestor_type_1([D2|Ds], [T1|Ts1], [T0|_]).
 3400
 3401%------------------------------------------------------------------------------
 3402
 3403jpl_datums_to_most_specific_common_ancestor_type_1([], Ts, Ts).
 3404
 3405jpl_datums_to_most_specific_common_ancestor_type_1([D|Ds], Ts1, Ts0) :-
 3406	jpl_datum_to_type(D, Tx),
 3407	jpl_lineage_types_type_to_common_lineage_types(Ts1, Tx, Ts2),
 3408	jpl_datums_to_most_specific_common_ancestor_type_1(Ds, Ts2, Ts0).
 3409
 3410%------------------------------------------------------------------------------
 3411
 3412% jpl_datums_to_types(+Datums, -Types) :-
 3413%   each member of Datums is a JPL value or ref,
 3414%   denoting an instance of some Java type,
 3415%   and the corresponding member of Types denotes the most specialised type
 3416%   of which it is an instance (including some I invented for the overlaps
 3417%   between char and short, etc,)
 3418
 3419jpl_datums_to_types([], []).
 3420
 3421jpl_datums_to_types([D|Ds], [T|Ts]) :-
 3422	jpl_datum_to_type(D, T),
 3423	jpl_datums_to_types(Ds, Ts).
 3424
 3425%------------------------------------------------------------------------------
 3426
 3427% jpl_false(-X) :-
 3428%   X is (by unification) the proper JPL datum which represents the Java boolean value 'false'
 3429%   c.f. jpl_is_false/1
 3430
 3431jpl_false(@(false)).
 3432
 3433%------------------------------------------------------------------------------
 3434
 3435% jpl_ground_is_type(+X) :-
 3436%   X, known to be ground, is (or at least superficially resembles :-) a JPL type
 3437
 3438jpl_ground_is_type(X) :-
 3439	jpl_primitive_type(X),
 3440	!.
 3441
 3442jpl_ground_is_type(array(X)) :-
 3443	jpl_ground_is_type(X).
 3444
 3445jpl_ground_is_type(class(_,_)).
 3446
 3447jpl_ground_is_type(method(_,_)).
 3448
 3449%------------------------------------------------------------------------------
 3450
 3451:- dynamic jpl_iref_type_cache/2. 3452
 3453%------------------------------------------------------------------------------
 3454
 3455% jpl_is_class(?X) :-
 3456%   X is a JPL ref to a java.lang.Class object
 3457
 3458jpl_is_class(X) :-
 3459	jpl_is_object(X),
 3460	jpl_object_to_type(X, class([java,lang],['Class'])).
 3461
 3462%------------------------------------------------------------------------------
 3463
 3464% jpl_is_false(?X) :-
 3465%   X is the proper JPL datum which represents the Java boolean value 'false';
 3466%   whatever, no further instantiation of X occurs
 3467
 3468jpl_is_false(X) :-
 3469	X == @(false).
 3470
 3471%------------------------------------------------------------------------------
 3472
 3473% jpl_is_fieldID(?X) :-
 3474%   X is a proper JPL field ID structure (jfieldID/1);
 3475%   applications should not be messing with these (?);
 3476%   whatever, no further instantiation of X occurs
 3477
 3478jpl_is_fieldID(jfieldID(X)) :-      % NB a var arg may get bound...
 3479	integer(X).
 3480
 3481%------------------------------------------------------------------------------
 3482
 3483% jpl_is_methodID(?X) :-
 3484%   X is a proper JPL method ID structure (jmethodID/1);
 3485%   applications should not be messing with these (?);
 3486%   whatever, no further instantiation of X occurs
 3487
 3488jpl_is_methodID(jmethodID(X)) :-   % NB a var arg may get bound...
 3489	integer(X).
 3490
 3491%------------------------------------------------------------------------------
 3492
 3493% jpl_is_null(?X) :-
 3494%   X is the proper JPL datum which represents Java's 'null' reference;
 3495%   whatever, no further instantiation of X occurs
 3496
 3497jpl_is_null(X) :-
 3498	X == @(null).
 3499
 3500%------------------------------------------------------------------------------
 3501
 3502% jpl_is_object(?X) :-
 3503%   X is a proper, plausible JPL object reference;
 3504%   NB this checks only syntax, not whether the object exists;
 3505%   whatever, no further instantiation of X occurs
 3506
 3507jpl_is_object(X) :-
 3508	jpl_is_ref(X),      % (syntactically, at least...)
 3509	X \== @(null).
 3510
 3511%------------------------------------------------------------------------------
 3512
 3513% jpl_is_object_type(+T) :-
 3514%   T is an object (class or array) type,
 3515%   not e.g. a primitive, null or void
 3516
 3517jpl_is_object_type(T) :-
 3518	\+ var(T),
 3519	jpl_non_var_is_object_type(T).
 3520
 3521%------------------------------------------------------------------------------
 3522
 3523% jpl_is_ref(?T) :-
 3524%   the arbitrary term T is a proper, syntactically plausible JPL reference,
 3525%   either to a Java object
 3526%   (which may not exist, although a jpl_is_current_ref/1 might be useful)
 3527%   or to Java's notional but important 'null' non-object;
 3528%   whatever, no further instantiation of X occurs;
 3529%   NB to distinguish tags from void/false/true,
 3530%   could check initial character(s) or length? or adopt strong/weak scheme...
 3531
 3532jpl_is_ref(@(Y)) :-
 3533	atom(Y),        % presumably a (garbage-collectable) tag
 3534	Y \== void,     % not a ref
 3535	Y \== false,    % not a ref
 3536	Y \== true.     % not a ref
 3537
 3538%------------------------------------------------------------------------------
 3539
 3540% jpl_is_true(?X) :-
 3541%   X is a proper JPL datum, representing the Java boolean value 'true';
 3542%   whatever, no further instantiation of X occurs
 3543
 3544jpl_is_true(X) :-
 3545	X == @(true).
 3546
 3547%------------------------------------------------------------------------------
 3548
 3549% jpl_is_type(+X) :-
 3550
 3551jpl_is_type(X) :-
 3552	ground(X),
 3553	jpl_ground_is_type(X).
 3554
 3555%------------------------------------------------------------------------------
 3556
 3557% jpl_is_void(?X) :-
 3558%   X is the proper JPL datum which represents the pseudo Java value 'void'
 3559%   (which is returned by jpl_call/4 when invoked on void methods);
 3560%   NB you can try passing 'void' back to Java, but it won't ever be interested;
 3561%   whatever, no further instantiation of X occurs
 3562
 3563jpl_is_void(X) :-
 3564	X == @(void).
 3565
 3566%------------------------------------------------------------------------------
 3567
 3568jpl_lineage_types_type_to_common_lineage_types(Ts, Tx, Ts0) :-
 3569	(   append(_, [Tx|Ts2], Ts)
 3570	->  [Tx|Ts2] = Ts0
 3571	;   jpl_type_to_super_type(Tx, Tx2)
 3572	->  jpl_lineage_types_type_to_common_lineage_types(Ts, Tx2, Ts0)
 3573	).
 3574
 3575%------------------------------------------------------------------------------
 3576
 3577jpl_non_var_is_object_type(class(_,_)).
 3578
 3579jpl_non_var_is_object_type(array(_)).
 3580
 3581%------------------------------------------------------------------------------
 3582
 3583% jpl_null(-X) :-
 3584%   X is (by unification) the proper JPL datum which represents the Java reference 'null';
 3585%   c.f. jpl_is_null/1
 3586
 3587jpl_null(@(null)).
 3588
 3589%------------------------------------------------------------------------------
 3590
 3591% jpl_object_array_to_list(+ArrayObject, -Values) :-
 3592%   Values is a list of JPL values (primitive values or object references)
 3593%   representing the respective elements of ArrayObject
 3594
 3595jpl_object_array_to_list(A, Vs) :-
 3596	jpl_array_to_length(A, N),
 3597	jpl_object_array_to_list_1(A, 0, N, Vs).
 3598
 3599%------------------------------------------------------------------------------
 3600
 3601% jpl_object_array_to_list_1(+A, +I, +N, -Xs) :-
 3602
 3603jpl_object_array_to_list_1(A, I, N, Xs) :-
 3604	(   I == N
 3605	->  Xs = []
 3606	;   jGetObjectArrayElement(A, I, X),
 3607	Xs = [X|Xs2],
 3608	J is I+1,
 3609	jpl_object_array_to_list_1(A, J, N, Xs2)
 3610	).
 3611
 3612%------------------------------------------------------------------------------
 3613
 3614% jpl_object_to_class(+Object, -Class) :-
 3615%   Object must be a valid object (should this throw an exception otherwise?);
 3616%   Class is a (canonical) reference to the (canonical) class object
 3617%   which represents the class of Object;
 3618%   NB wot's the point of caching the type if we don't look there first?
 3619
 3620jpl_object_to_class(Obj, C) :-
 3621	jGetObjectClass(Obj, C),
 3622	jpl_cache_type_of_ref(class([java,lang],['Class']), C).
 3623
 3624%------------------------------------------------------------------------------
 3625
 3626% jpl_object_to_type(+Object, -Type) :-
 3627%   Object must be a proper JPL reference to a Java object
 3628%   (i.e. a class or array instance, but not null, void or String);
 3629%   Type is the JPL type of that object
 3630
 3631jpl_object_to_type(@(Tag), Type) :-
 3632	jpl_tag_to_type(Tag, Type).
 3633
 3634%------------------------------------------------------------------------------
 3635
 3636jpl_object_type_to_super_type(T, Tx) :-
 3637	(   (   T = class(_,_)
 3638	;   T = array(_)
 3639	)
 3640	->  jpl_type_to_class(T, C),
 3641	jpl_class_to_super_class(C, Cx),
 3642	Cx \== @(null),
 3643	jpl_class_to_type(Cx, Tx)
 3644	).
 3645
 3646%------------------------------------------------------------------------------
 3647
 3648% jpl_primitive_buffer_to_array(+Type, +Xc, +Bp, +I, +Size, -Vcs) :-
 3649%   Bp points to a buffer of (sufficient) Type values;
 3650%   Vcs will be unbound on entry,
 3651%   and on exit will be a list of Size of them, starting at index I
 3652%   (the buffer is indexed from zero)
 3653
 3654jpl_primitive_buffer_to_array(T, Xc, Bp, I, Size, [Vc|Vcs]) :-
 3655	jni_fetch_buffer_value(Bp, I, Vc, Xc),
 3656	Ix is I+1,
 3657	(   Ix < Size
 3658	->  jpl_primitive_buffer_to_array(T, Xc, Bp, Ix, Size, Vcs)
 3659	;   Vcs = []
 3660	).
 3661
 3662%------------------------------------------------------------------------------
 3663
 3664jpl_primitive_type(boolean).
 3665jpl_primitive_type(char).
 3666jpl_primitive_type(byte).
 3667jpl_primitive_type(short).
 3668jpl_primitive_type(int).
 3669jpl_primitive_type(long).
 3670jpl_primitive_type(float).
 3671jpl_primitive_type(double).
 3672
 3673%------------------------------------------------------------------------------
 3674
 3675% jpl_primitive_type_default_value(-Type, -Value) :-
 3676%   each element of any array of (primitive) Type created by jpl_new/3,
 3677%   or any instance of (primitive) Type created by jpl_new/3,
 3678%   should be initialised to Value (to mimic Java semantics)
 3679
 3680jpl_primitive_type_default_value(boolean, @(false)).
 3681jpl_primitive_type_default_value(char,    0).
 3682jpl_primitive_type_default_value(byte,    0).
 3683jpl_primitive_type_default_value(short,   0).
 3684jpl_primitive_type_default_value(int,     0).
 3685jpl_primitive_type_default_value(long,    0).
 3686jpl_primitive_type_default_value(float,   0.0).
 3687jpl_primitive_type_default_value(double,  0.0).
 3688
 3689%------------------------------------------------------------------------------
 3690
 3691jpl_primitive_type_super_type(T, Tx) :-
 3692	(   jpl_type_fits_type_direct_prim(T, Tx)
 3693	;   jpl_type_fits_type_direct_xtra(T, Tx)
 3694	).
 3695
 3696%------------------------------------------------------------------------------
 3697
 3698% jpl_primitive_type_term_to_value(+Type, +Term, -Val) :-
 3699%   Term, after widening iff appropriate, represents an instance of Type;
 3700%   Val is the instance of Type which it represents (often the same thing);
 3701%   currently used only by jpl_new_1 when creating an "instance"
 3702%   of a primitive type (which may be misguided completism - you can't
 3703%   do that in Java)
 3704
 3705jpl_primitive_type_term_to_value(Type, Term, Val) :-
 3706	(   jpl_primitive_type_term_to_value_1(Type, Term, Val)
 3707	->  true
 3708	).
 3709
 3710%------------------------------------------------------------------------------
 3711
 3712% jpl_primitive_type_term_to_value_1(+Type, +RawValue, -WidenedValue) :-
 3713%   I'm not worried about structure duplication here
 3714%   NB this oughta be done in foreign code...
 3715
 3716jpl_primitive_type_term_to_value_1(boolean, @(false), @(false)).
 3717
 3718jpl_primitive_type_term_to_value_1(boolean, @(true), @(true)).
 3719
 3720jpl_primitive_type_term_to_value_1(char, I, I) :-
 3721	integer(I),
 3722	I >= 0,
 3723	I =< 65535.         %  (2**16)-1.
 3724
 3725jpl_primitive_type_term_to_value_1(byte, I, I) :-
 3726	integer(I),
 3727	I >= 128,           % -(2**7)
 3728	I =< 127.           %  (2**7)-1
 3729
 3730jpl_primitive_type_term_to_value_1(short, I, I) :-
 3731	integer(I),
 3732	I >= -32768,        % -(2**15)
 3733	I =<  32767.        %  (2**15)-1
 3734
 3735jpl_primitive_type_term_to_value_1(int, I, I) :-
 3736	integer(I),
 3737	I >= -2147483648,   % -(2**31)
 3738	I =<  2147483647.   %  (2**31)-1
 3739
 3740jpl_primitive_type_term_to_value_1(long, I, I) :-
 3741	integer(I),
 3742	I >= -9223372036854775808,  % -(2**63)
 3743	I =<  9223372036854775807.  %  (2**63)-1
 3744
 3745jpl_primitive_type_term_to_value_1(float, I, F) :-
 3746	integer(I),
 3747	F is float(I).
 3748
 3749jpl_primitive_type_term_to_value_1(float, F, F) :-
 3750	float(F).
 3751
 3752jpl_primitive_type_term_to_value_1(double, I, F) :-
 3753	integer(I),
 3754	F is float(I).
 3755
 3756jpl_primitive_type_term_to_value_1(double, F, F) :-
 3757	float(F).
 3758
 3759%------------------------------------------------------------------------------
 3760
 3761jpl_primitive_type_to_ancestor_types(T, Ts) :-
 3762	(   jpl_primitive_type_super_type(T, Ta)
 3763	->  Ts = [Ta|Tas],
 3764	jpl_primitive_type_to_ancestor_types(Ta, Tas)
 3765	;   Ts = []
 3766	).
 3767
 3768%------------------------------------------------------------------------------
 3769
 3770jpl_primitive_type_to_super_type(T, Tx) :-
 3771	jpl_primitive_type_super_type(T, Tx).
 3772
 3773%------------------------------------------------------------------------------
 3774
 3775% jpl_ref_to_type(+Ref, -Type) :-
 3776%   Ref must be a proper JPL reference (to an object, null or void);
 3777%   Type is its type
 3778
 3779jpl_ref_to_type(@(X), T) :-
 3780	(   X == null
 3781	->  T = null
 3782	;   X == void
 3783	->  T = void
 3784	;   jpl_tag_to_type(X, T)
 3785	).
 3786
 3787%------------------------------------------------------------------------------
 3788
 3789% jpl_tag_to_type(+Tag, -Type) :-
 3790%   Tag must be an (atomic) object tag;
 3791%   Type is its type (either from the cache or by reflection);
 3792
 3793jpl_tag_to_type(Tag, Type) :-
 3794	jni_tag_to_iref(Tag, Iref),
 3795	(   jpl_iref_type_cache(Iref, T)
 3796	->  true                                % T is Tag's type
 3797	;   jpl_object_to_class(@(Tag), Cobj), % else get ref to class obj
 3798	jpl_class_to_type(Cobj, T),         % get type of class it denotes
 3799	jpl_assert(jpl_iref_type_cache(Iref,T))
 3800	),
 3801	Type = T.
 3802
 3803%------------------------------------------------------------------------------
 3804
 3805% jpl_true(-X) :-
 3806%   X is (by unification) the proper JPL datum which represents the Java boolean value 'true';
 3807%cf jpl_is_true/1
 3808
 3809jpl_true(@(true)).
 3810
 3811%------------------------------------------------------------------------------
 3812
 3813% jpl_type_fits_type(+TypeX, +TypeY) :-
 3814%   TypeX and TypeY must each be proper JPL types;
 3815%   this succeeds iff TypeX is assignable to TypeY
 3816
 3817jpl_type_fits_type(Tx, Ty) :-
 3818	(   jpl_type_fits_type_1(Tx, Ty)
 3819	->  true
 3820	).
 3821
 3822%------------------------------------------------------------------------------
 3823
 3824% jpl_type_fits_type_1(+T1, +T2) :-
 3825%   it doesn't matter that this leaves choicepoints; it serves only jpl_type_fits_type/2
 3826
 3827jpl_type_fits_type_1(T, T).
 3828
 3829jpl_type_fits_type_1(class(Ps1,Cs1), class(Ps2,Cs2)) :-
 3830	jpl_type_to_class(class(Ps1,Cs1), C1),
 3831	jpl_type_to_class(class(Ps2,Cs2), C2),
 3832	jIsAssignableFrom(C1, C2).
 3833
 3834jpl_type_fits_type_1(array(T1), class(Ps2,Cs2)) :-
 3835	jpl_type_to_class(array(T1), C1),
 3836	jpl_type_to_class(class(Ps2,Cs2), C2),
 3837	jIsAssignableFrom(C1, C2).
 3838
 3839jpl_type_fits_type_1(array(T1), array(T2)) :-
 3840	jpl_type_to_class(array(T1), C1),
 3841	jpl_type_to_class(array(T2), C2),
 3842	jIsAssignableFrom(C1, C2).
 3843
 3844jpl_type_fits_type_1(null, class(_,_)).
 3845
 3846jpl_type_fits_type_1(null, array(_)).
 3847
 3848jpl_type_fits_type_1(T1, T2) :-
 3849	jpl_type_fits_type_xprim(T1, T2).
 3850
 3851%------------------------------------------------------------------------------
 3852
 3853jpl_type_fits_type_direct_prim(float, double).
 3854jpl_type_fits_type_direct_prim(long,  float).
 3855jpl_type_fits_type_direct_prim(int,   long).
 3856jpl_type_fits_type_direct_prim(char,  int).
 3857jpl_type_fits_type_direct_prim(short, int).
 3858jpl_type_fits_type_direct_prim(byte,  short).
 3859
 3860%------------------------------------------------------------------------------
 3861
 3862jpl_type_fits_type_direct_xprim(Tp, Tq) :-
 3863	jpl_type_fits_type_direct_prim(Tp, Tq).
 3864
 3865jpl_type_fits_type_direct_xprim(Tp, Tq) :-
 3866	jpl_type_fits_type_direct_xtra(Tp, Tq).
 3867
 3868%------------------------------------------------------------------------------
 3869
 3870% jpl_type_fits_type_direct_xtra(-PseudoType, -ConcreteType) :-
 3871%   this predicate defines the direct subtype-supertype relationships
 3872%   which involve the intersection pseudo types char_int, char_short and char_byte
 3873
 3874jpl_type_fits_type_direct_xtra(char_int,   int).    % char_int is a direct subtype of int
 3875jpl_type_fits_type_direct_xtra(char_int,   char).   % etc.
 3876jpl_type_fits_type_direct_xtra(char_short, short).
 3877jpl_type_fits_type_direct_xtra(char_short, char).
 3878jpl_type_fits_type_direct_xtra(char_byte,  byte).
 3879jpl_type_fits_type_direct_xtra(char_byte,  char).
 3880
 3881jpl_type_fits_type_direct_xtra(overlong,   float).  % 6/Oct/2006 experiment
 3882
 3883%------------------------------------------------------------------------------
 3884
 3885% jpl_type_fits_type_xprim(-Tp, -T) :-
 3886%   indeterminate;
 3887%   serves only jpl_type_fits_type_1/2
 3888
 3889jpl_type_fits_type_xprim(Tp, T) :-
 3890	jpl_type_fits_type_direct_xprim(Tp, Tq),
 3891	(   Tq = T
 3892	;   jpl_type_fits_type_xprim(Tq, T)
 3893	).
 3894
 3895%------------------------------------------------------------------------------
 3896
 3897% jpl_type_to_ancestor_types(+T, -Tas) :-
 3898%   this does not accommodate the assignability of null,
 3899%   but that's OK (?) since "type assignability" and "type ancestry" are not equivalent
 3900
 3901jpl_type_to_ancestor_types(T, Tas) :-
 3902	(   (   T = class(_,_)
 3903	;   T = array(_)
 3904	)
 3905	->  jpl_type_to_class(T, C),
 3906	jpl_class_to_ancestor_classes(C, Cas),
 3907	jpl_classes_to_types(Cas, Tas)
 3908	;   jpl_primitive_type_to_ancestor_types(T, Tas)
 3909	->  true
 3910	).
 3911
 3912%------------------------------------------------------------------------------
 3913
 3914% jpl_type_to_canonical_type(+Type, -CanonicalType) :-
 3915%   Type must be a type, not necessarily canonical;
 3916%   CanonicalType will be equivalent and canonical
 3917
 3918%eg jpl_type_to_canonical_type(class([],[byte]), byte)
 3919
 3920jpl_type_to_canonical_type(array(T), array(Tc)) :-
 3921	!,
 3922	jpl_type_to_canonical_type(T, Tc).
 3923
 3924jpl_type_to_canonical_type(class([],[void]), void) :-
 3925	!.
 3926
 3927jpl_type_to_canonical_type(class([],[N]), N) :-
 3928	jpl_primitive_type(N),
 3929	!.
 3930
 3931jpl_type_to_canonical_type(class(Ps,Cs), class(Ps,Cs)) :-
 3932	!.
 3933
 3934jpl_type_to_canonical_type(void, void) :-
 3935	!.
 3936
 3937jpl_type_to_canonical_type(P, P) :-
 3938	jpl_primitive_type(P).
 3939
 3940%------------------------------------------------------------------------------
 3941
 3942% jpl_type_to_class(+Type, -ClassObject) :-
 3943%   incomplete types are now never cached (or otherwise passed around);
 3944%   jFindClass throws an exception if FCN can't be found
 3945
 3946%nb if this is public API maybe oughta restore the ground(T) check and throw exception
 3947
 3948jpl_type_to_class(T, @(Tag)) :-
 3949  % ground(T),  % 9/Nov/2004 removed this spurious (?) check
 3950	(   jpl_class_tag_type_cache(ClassTag,T)
 3951	->  Tag = ClassTag
 3952	;   (   jpl_type_to_findclassname(T, FCN)   % peculiar syntax for FindClass()
 3953	->  jFindClass(FCN, @(ClassTag)),       % which caches type of @ClassTag
 3954	  % jpl_cache_type_of_ref(T, @(ClassTag))
 3955	    jpl_cache_type_of_ref(class([java,lang],['Class']), @(ClassTag))    % 9/Nov/2004 bugfix (?)
 3956	),
 3957	jpl_assert(jpl_class_tag_type_cache(ClassTag,T))
 3958	),
 3959	Tag = ClassTag.
 3960
 3961%------------------------------------------------------------------------------
 3962
 3963% jpl_type_to_nicename(+Type, -NiceName) :-
 3964%   Type, which is a class or array type (not sure about the others...),
 3965%   is denoted by ClassName in dotted syntax
 3966
 3967%nb is this used? is "nicename" well defined and necessary?
 3968%nb this could use caching if indexing were amenable
 3969
 3970%eg jpl_type_to_nicename(class([java,util],['Date']), 'java.util.Date')
 3971%eg jpl_type_to_nicename(boolean, boolean)
 3972
 3973%cf jpl_type_to_classname/2
 3974
 3975jpl_type_to_nicename(T, NN) :-
 3976	(   jpl_primitive_type( T)
 3977	->  NN = T
 3978	;   (   phrase(jpl_type_classname_1(T), Cs)
 3979	->  atom_codes(CNx, Cs),                                % green commit to first solution
 3980	    NN = CNx
 3981	)
 3982	).
 3983
 3984%------------------------------------------------------------------------------
 3985
 3986% jpl_type_to_classname(+Type, -ClassName) :-
 3987%   Type, which is a class or array type (not sure about the others...),
 3988%   is denoted by ClassName in dotted syntax
 3989
 3990%eg jpl_type_to_classname(class([java,util],['Date']), 'java.util.Date')
 3991
 3992%cf jpl_type_to_nicename/2
 3993
 3994jpl_type_to_classname(T, CN) :-
 3995	(   phrase(jpl_type_classname_1(T), Cs)
 3996	->  atom_codes(CNx, Cs),                                % green commit to first solution
 3997	CN = CNx
 3998	).
 3999
 4000%------------------------------------------------------------------------------
 4001
 4002% jpl_type_to_descriptor(+Type, -Descriptor) :-
 4003%   Type (denoting any Java type)
 4004%   (can also be a JPL method/2 structure (?!))
 4005%   is represented by Descriptor (JVM internal syntax)
 4006%   I'd cache this, but I'd prefer more efficient indexing on types (hashed?)
 4007
 4008jpl_type_to_descriptor(T, D) :-
 4009	(   phrase(jpl_type_descriptor_1(T), Cs)
 4010	->  atom_codes(Dx, Cs),
 4011	D = Dx
 4012	).
 4013
 4014%------------------------------------------------------------------------------
 4015
 4016% jpl_type_to_findclassname(+Type, -FindClassName) :-
 4017%   FindClassName denotes Type (class or array only)
 4018%   in the syntax required peculiarly by FindClass()
 4019
 4020jpl_type_to_findclassname(T, FCN) :-
 4021	(   phrase(jpl_type_findclassname(T), Cs)
 4022	->  atom_codes(FCNx, Cs),
 4023	FCN = FCNx
 4024	).
 4025
 4026%------------------------------------------------------------------------------
 4027
 4028% jpl_type_to_super_type(+Type, -SuperType) :-
 4029%   Type oughta be a proper JPL type;
 4030%   SuperType is the (at most one) type which it directly implements (if it's a class);
 4031%   if Type denotes a class, this works only if that class can be found;
 4032%   if Type = array(Type) then I dunno what happens...
 4033
 4034jpl_type_to_super_type(T, Tx) :-
 4035	(   jpl_object_type_to_super_type(T, Tx)
 4036	->  true
 4037	;   jpl_primitive_type_to_super_type(T, Tx)
 4038	->  true
 4039	).
 4040
 4041%------------------------------------------------------------------------------
 4042
 4043% jpl_type_to_preferred_concrete_type( +Type, -ConcreteType) :-
 4044%   Type must be a canonical JPL type,
 4045%   possibly a pseudo (inferred) type such as char_int or array(char_byte);
 4046%   ConcreteType is the preferred concrete (Java-instantiable) type;
 4047%   introduced 16/Apr/2005 to fix bug whereby jpl_list_to_array([1,2,3],A) failed
 4048%   because the lists's inferred type of array(char_byte) is not Java-instantiable
 4049
 4050jpl_type_to_preferred_concrete_type( T, Tc) :-
 4051	(   jpl_type_to_preferred_concrete_type_1( T, TcX)
 4052	->  Tc = TcX
 4053	).
 4054
 4055%------------------------------------------------------------------------------
 4056
 4057jpl_type_to_preferred_concrete_type_1( char_int, int).
 4058
 4059jpl_type_to_preferred_concrete_type_1( char_short, short).
 4060
 4061jpl_type_to_preferred_concrete_type_1( char_byte, byte).
 4062
 4063jpl_type_to_preferred_concrete_type_1( array(T), array(Tc)) :-
 4064	jpl_type_to_preferred_concrete_type_1( T, Tc).
 4065
 4066jpl_type_to_preferred_concrete_type_1( T, T).
 4067
 4068%------------------------------------------------------------------------------
 4069
 4070% jpl_types_fit_type(+Types, +Type) :-
 4071%   each member of Types is (independently) (if that means anything)
 4072%   assignable to Type
 4073%   e.g. for dynamic type check when attempting to assign list of values to array
 4074
 4075jpl_types_fit_type([], _).
 4076
 4077jpl_types_fit_type([T1|T1s], T2) :-
 4078	jpl_type_fits_type(T1, T2),
 4079	jpl_types_fit_type(T1s, T2).
 4080
 4081%------------------------------------------------------------------------------
 4082
 4083% jpl_types_fit_types(+Types1, +Types2) :-
 4084%   each member type of Types1 "fits" the respective member type of Types2
 4085
 4086jpl_types_fit_types([], []).
 4087
 4088jpl_types_fit_types([T1|T1s], [T2|T2s]) :-
 4089	jpl_type_fits_type(T1, T2),
 4090	jpl_types_fit_types(T1s, T2s).
 4091
 4092%------------------------------------------------------------------------------
 4093
 4094% jpl_value_to_type(+Value, -Type) :-
 4095%   Value must be a proper JPL datum other than a ref
 4096%   i.e. primitive, String or void;
 4097%   it is of (unique most specific) Type,
 4098%   which may be one of the pseudo types char_byte, char_short or char_int
 4099
 4100jpl_value_to_type(V, T) :-
 4101	ground(V),                          % critically assumed by jpl_value_to_type_1/2
 4102	(   jpl_value_to_type_1(V, Tv)      % 2nd arg must be unbound
 4103	->  T = Tv
 4104	).
 4105
 4106%------------------------------------------------------------------------------
 jpl_value_to_type_1(+Value, -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

 4122jpl_value_to_type_1(@(false), boolean) :- !.
 4123jpl_value_to_type_1(@(true), boolean) :- !.
 4124jpl_value_to_type_1(A, class([java,lang],['String'])) :-   % yes it's a "value"
 4125	atom(A), !.
 4126jpl_value_to_type_1(I, T) :-
 4127	integer(I), !,
 4128	(   I >= 0
 4129	->  (   I  < 128
 4130	    ->  T  = char_byte
 4131	    ;   I  < 32768   		 ->  T = char_short
 4132	    ;   I  < 65536   		 ->  T = char_int
 4133	    ;   I  < 2147483648   	 ->  T = int
 4134	    ;   I =< 9223372036854775807 ->  T = long
 4135	    				  ;  T = overlong
 4136	    )
 4137	;   I >= -128		      ->  T = byte
 4138	;   I >= -32768		      ->  T = short
 4139	;   I >= -2147483648          ->  T = int
 4140	;   I >= -9223372036854775808 ->  T = long
 4141				       ;  T = overlong
 4142	).
 4143jpl_value_to_type_1(F, float) :-
 4144	float(F).
 4145
 4146%------------------------------------------------------------------------------
 4147
 4148% jpl_void(-X) :-
 4149%   X is (by unification) the proper JPL datum which represents the pseudo Java value 'void';
 4150%   c.f. jpl_is_void/1
 4151
 4152jpl_void(@(void)).
 4153
 4154%------------------------------------------------------------------------------
 4155
 4156%type   jpl_array_to_length(array, integer)
 4157
 4158% jpl_array_to_length(+ArrayObject, -Length) :-
 4159%   must validate ArrayObject before making the JNI call...
 4160
 4161jpl_array_to_length(A, N) :-
 4162	(   jpl_ref_to_type(A, array(_))    % can this be done cheaper e.g. in foreign code?
 4163	->  jGetArrayLength(A, N)           % *must* be array, else undefined (crash?)
 4164	).
 4165
 4166%------------------------------------------------------------------------------
 4167
 4168%type   jpl_array_to_list(array, list(datum))
 4169
 4170% jpl_array_to_list(+Array, -Elements) :-
 4171
 4172jpl_array_to_list(A, Es) :-
 4173	jpl_array_to_length(A, Len),
 4174	(   Len > 0
 4175	->  LoBound is 0,
 4176	HiBound is Len-1,
 4177	jpl_get(A, LoBound-HiBound, Es)
 4178	;   Es = []
 4179	).
 4180
 4181%------------------------------------------------------------------------------
 4182
 4183%type   jpl_datums_to_array(list(datum), array)
 4184
 4185% jpl_datums_to_array(+Ds, -A) :-
 4186%   A will be a ref to a new JVM array,
 4187%   whose base type is the most specific Java type
 4188%   of which each member of Datums is (directly or indirectly) an instance;
 4189%   NB this fails (without warning, currently) if:
 4190%       Ds is an empty list (no base type can be inferred)
 4191%       Ds contains a primitive value and an object or array ref (no common supertype)
 4192
 4193jpl_datums_to_array(Ds, A) :-
 4194	ground(Ds),
 4195	jpl_datums_to_most_specific_common_ancestor_type(Ds, T),    % T may be pseudo e.g. char_byte
 4196	jpl_type_to_preferred_concrete_type( T, Tc),    % bugfix added 16/Apr/2005
 4197	jpl_new(array(Tc), Ds, A).
 4198
 4199%------------------------------------------------------------------------------
 4200
 4201%type   jpl_enumeration_element(object, datum)
 4202
 4203% jpl_enumeration_element(+Enumeration, -Element) :-
 4204%   generates each Element from the Enumeration;
 4205%   if the element is a java.lang.String then Element will be an atom;
 4206%   if the element is null then Element will (oughta) be null;
 4207%   otherwise I reckon it has to be an object ref
 4208
 4209jpl_enumeration_element(En, E) :-
 4210	(   jpl_call(En, hasMoreElements, [], @(true))
 4211	->  jpl_call(En, nextElement, [], Ex),
 4212	(   E = Ex
 4213	;   jpl_enumeration_element(En, E)
 4214	)
 4215	).
 4216
 4217%------------------------------------------------------------------------------
 4218
 4219%type   jpl_enumeration_to_list(object, list(datum))
 4220
 4221% jpl_enumeration_to_list(+Enumeration, -Elements) :-
 4222
 4223jpl_enumeration_to_list(EN, Es) :-
 4224	(   jpl_call(EN, hasMoreElements, [], @(true))
 4225	->  jpl_call(EN, nextElement, [], E),
 4226	Es = [E|Es1],
 4227	jpl_enumeration_to_list(EN, Es1)
 4228	;   Es = []
 4229	).
 4230
 4231%------------------------------------------------------------------------------
 4232
 4233%type   jpl_hashtable_pair(object, pair(datum,datum))
 4234
 4235% jpl_hashtable_pair(+HashTable, -KeyValuePair) :-
 4236%   generates Key-Value pairs from the given HashTable
 4237%   NB String is converted to atom but Integer is presumably returned as an object ref
 4238%   (i.e. as elsewhere, no auto unboxing);
 4239%nb this is anachronistic (oughta use the Map interface?)
 4240
 4241jpl_hashtable_pair(HT, K-V) :-
 4242	jpl_call(HT, keys, [], Ek),
 4243	jpl_enumeration_to_list(Ek, Ks),
 4244	member(K, Ks),
 4245	jpl_call(HT, get, [K], V).
 4246
 4247%------------------------------------------------------------------------------
 4248
 4249%type   jpl_iterator_element(object, datum)
 4250
 4251% jpl_iterator_element(+Iterator, -Element) :-
 4252
 4253jpl_iterator_element(I, E) :-
 4254	(   jpl_call(I, hasNext, [], @(true))
 4255	->  (   jpl_call(I, next, [], E)        % surely it's steadfast...
 4256	;   jpl_iterator_element(I, E)
 4257	)
 4258	).
 4259
 4260%------------------------------------------------------------------------------
 4261
 4262%type   jpl_list_to_array(list(datum), array)
 4263
 4264% jpl_list_to_array(+Datums, -Array) :-
 4265%   Datums is a proper list of JPL datums (values or refs);
 4266%   if they have a most specific common supertype,
 4267%   Array is an array, of that base type,
 4268%   whose respective elements are Datums
 4269
 4270jpl_list_to_array(Ds, A) :-
 4271	jpl_datums_to_array(Ds, A).
 4272
 4273%------------------------------------------------------------------------------
 4274
 4275%type   jpl_terms_to_array(list(term), array)
 4276
 4277% jpl_terms_to_array(+Terms, -Array) :-
 4278%   Terms is a proper list of arbitrary terms;
 4279%   Array is an array of jpl.Term,
 4280%   whose elements represent the respective members of the list
 4281
 4282jpl_terms_to_array(Ts, A) :-
 4283	jpl_terms_to_array_1(Ts, Ts2),
 4284	jpl_new( array(class([org,jpl7],['Term'])), Ts2, A).
 4285
 4286%------------------------------------------------------------------------------
 4287
 4288jpl_terms_to_array_1([], []).
 4289
 4290jpl_terms_to_array_1([T|Ts], [{T}|Ts2]) :-
 4291	jpl_terms_to_array_1(Ts, Ts2).
 4292
 4293%------------------------------------------------------------------------------
 4294
 4295%type   jpl_map_element(object, pair(datum,datum))
 4296
 4297% jpl_map_element(+Map, -KeyValue) :-
 4298%   Map must be an instance of any implementation of the java.util.Map interface;
 4299%   this generates each Key-Value pair from the Map
 4300
 4301jpl_map_element(M, K-V) :-
 4302	jpl_call(M, entrySet, [], ES),
 4303	jpl_set_element(ES, E),
 4304	jpl_call(E, getKey, [], K),
 4305	jpl_call(E, getValue, [], V).
 4306
 4307%------------------------------------------------------------------------------
 4308
 4309%type   jpl_set_element(object, datum)
 4310
 4311% jpl_set_element(+Set, -Element) :-
 4312
 4313jpl_set_element(S, E) :-
 4314	jpl_call(S, iterator, [], I),
 4315	jpl_iterator_element(I, E).
 4316
 4317%------------------------------------------------------------------------------
 4318
 4319% is_pair(?T) :-
 4320%   I define a half-decent "pair" as having a ground key (any val)
 4321
 4322is_pair(0) :- !, fail.
 4323is_pair(Key-_Val) :-
 4324	ground(Key).
 4325
 4326%------------------------------------------------------------------------------
 4327
 4328is_pairs(0) :- !, fail.
 4329is_pairs([]).
 4330is_pairs([H|T]) :-
 4331	is_pair(H),
 4332	is_pairs(T).
 4333
 4334%------------------------------------------------------------------------------
 4335
 4336multimap_to_atom(KVs, A) :-
 4337	multimap_to_atom_1(KVs, "", Cz, []),
 4338	flatten(Cz, Cs),
 4339	atom_codes(A, Cs).
 4340
 4341%------------------------------------------------------------------------------
 4342
 4343multimap_to_atom_1([], _, Cs, Cs).
 4344multimap_to_atom_1([K-V|KVs], T, Cs1, Cs0) :-
 4345	atom_codes(K, CsK),
 4346	Cs1 = [T,CsK," = "|Cs2],
 4347	(   is_list(V)
 4348	->  (   is_pairs(V)
 4349	    ->  V = V2
 4350	    ;   findall(N-Ve, nth1(N, V, Ve), V2)
 4351	    ),
 4352	    T2 = ["    ",T],
 4353	    Cs2 = [10|Cs2a],
 4354	    multimap_to_atom_1(V2, T2, Cs2a, Cs3)
 4355	;   term_to_codes(V, CsV),
 4356	    Cs2 = [CsV,10|Cs3]
 4357	),
 4358	multimap_to_atom_1(KVs, T, Cs3, Cs0).
 4359
 4360%------------------------------------------------------------------------------
 term_to_codes(+Term, ?Codes)
unifies Codes with a printed representation of Term.
To be done
- Sort of quoting requirements and use format(codes(Codes), ...)
 4369term_to_codes(Term, Codes) :-
 4370	(   atom(Term)
 4371	->  Term = A                % avoid superfluous quotes
 4372	;   system:term_to_atom(Term, A)
 4373	),
 4374	atom_codes(A, Codes).
 4375
 4376%------------------------------------------------------------------------------
 4377
 4378		 /*******************************
 4379		 *            MESSAGES          *
 4380		 *******************************/
 4381
 4382:- multifile
 4383	prolog:error_message/3. 4384
 4385prolog:error_message(java_exception(Ex)) -->
 4386	(   { jpl_call(Ex, toString, [], Msg)
 4387	    }
 4388	->  [ 'Java exception: ~w'-[Msg] ]
 4389	;   [ 'Java exception: ~w'-[Ex] ]
 4390	).
 4391
 4392
 4393		 /*******************************
 4394		 *             PATHS            *
 4395		 *******************************/
 4396
 4397:- multifile user:file_search_path/2. 4398:- dynamic   user:file_search_path/2. 4399
 4400user:file_search_path(jar, swi(lib)).
 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.
 4410add_search_path(Path, Dir) :-
 4411	(   getenv(Path, Old)
 4412	->  (   current_prolog_flag(windows, true)
 4413	    ->	Sep = (;)
 4414	    ;	Sep = (:)
 4415	    ),
 4416	    (	concat_atom(Current, Sep, Old),
 4417		memberchk(Dir, Current)
 4418	    ->	true			% already present
 4419	    ;	concat_atom([Old, Sep, Dir], New),
 4420		setenv(Path, New)
 4421	    )
 4422	;   setenv(Path, Dir)
 4423	).
 search_path_separator(-Sep:atom)
Separator used the the OS in PATH, LD_LIBRARY_PATH, CLASSPATH, etc.
 4430search_path_separator((;)) :-
 4431	current_prolog_flag(windows, true), !.
 4432search_path_separator(:).
 4433
 4434		 /*******************************
 4435		 *         LOAD THE JVM         *
 4436		 *******************************/
 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.

 4454check_java_environment :-
 4455	check_lib(java),
 4456	check_lib(jvm).
 4457
 4458check_lib(Name) :-
 4459	check_shared_object(Name, File, EnvVar, Absolute),
 4460	(   Absolute == (-)
 4461	->  (   current_prolog_flag(windows, true)
 4462	    ->  A = '%', Z = '%'
 4463	    ;   A = '$', Z = ''
 4464	    ),
 4465	    (format(string(Msg), 'Please add directory holding ~w to ~w~w~w',
 4466		   [ File, A, EnvVar, Z ])),
 4467	    throw(error(existence_error(library, Name),
 4468			context(_, Msg)))
 4469	;   true
 4470	).
 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.
 4479check_shared_object(Name, File, EnvVar, Absolute) :-
 4480	libfile(Name, File),
 4481	library_search_path(Path, EnvVar),
 4482	(   member(Dir, Path),
 4483	    concat_atom([Dir, File], /, Absolute),
 4484	    exists_file(Absolute)
 4485	->  true
 4486	;   Absolute = (-)
 4487	).
 4488
 4489libfile(Base, File) :-
 4490	current_prolog_flag(unix, true), !,
 4491	atom_concat(lib, Base, F0),
 4492	current_prolog_flag(shared_object_extension, Ext),
 4493	file_name_extension(F0, Ext, File).
 4494libfile(Base, File) :-
 4495	current_prolog_flag(windows, true), !,
 4496	current_prolog_flag(shared_object_extension, Ext),
 4497	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.
 4506library_search_path(Path, EnvVar) :-
 4507	current_prolog_flag(shared_object_search_path, EnvVar),
 4508	search_path_separator(Sep),
 4509	(   getenv(EnvVar, Env),
 4510	    concat_atom(Path, Sep, Env)
 4511	->  true
 4512	;   Path = []
 4513	).
 add_jpl_to_classpath
Add jpl.jar to CLASSPATH to facilitate callbacks
 4520add_jpl_to_classpath :-
 4521	absolute_file_name(jar('jpl.jar'),
 4522			   [ access(read)
 4523			   ], JplJAR), !,
 4524	(   getenv('CLASSPATH', Old)
 4525	->  true
 4526	;   Old = '.'
 4527	),
 4528	(       current_prolog_flag(windows, true)
 4529	->      Separator = ';'
 4530	;       Separator = ':'
 4531	),
 4532	concat_atom([Old,JplJAR], Separator, New),
 4533	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.
 4542libjpl(File) :-
 4543	(   current_prolog_flag(unix, true)
 4544	->  File = foreign(libjpl)
 4545	;   File = foreign(jpl)
 4546	).
 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.
 4555add_jpl_to_ldpath(JPL) :-
 4556	absolute_file_name(JPL, File, [file_type(executable), file_errors(fail)]), !,
 4557	file_directory_name(File, Dir),
 4558	prolog_to_os_filename(Dir, OsDir),
 4559	current_prolog_flag(shared_object_search_path, PathVar),
 4560	add_search_path(PathVar, OsDir).
 4561add_jpl_to_ldpath(_).
 add_java_to_ldpath is det
Adds the directories holding jvm.dll and java.dll to the %PATH%. This appears to work on Windows. Unfortunately most Unix systems appear to inspect the content of LD_LIBRARY_PATH only once.
 4569add_java_to_ldpath :-
 4570	current_prolog_flag(windows, true), !,
 4571	% JDK directories
 4572	add_java_dir(jvm, '\\jre\\bin\\client', Extra1),
 4573	add_java_dir(java, '\\jre\\bin', Extra2),
 4574	% JRE directories
 4575	add_java_dir(jvm, '\\bin\\client', Extra3),
 4576	add_java_dir(java, '\\bin', Extra4), % Will add unneeded JAVA_HOME/bin to PATH, when JDK is used, but it shouldn't affect dll loading
 4577	flatten([Extra1, Extra2, Extra3, Extra4], Extra),
 4578	(   Extra \== []
 4579	->  print_message(informational,
 4580			  (format('Added ~w to %PATH%', [Extra]))),
 4581	    getenv('PATH', Path0),
 4582	    concat_atom([Path0|Extra], ';', Path),
 4583	    setenv('PATH', Path)
 4584	;   true
 4585	).
 4586add_java_to_ldpath.
 4587
 4588add_java_dir(DLL, SubPath, Dirs) :-
 4589	(   check_shared_object(DLL, _, _Var, Abs),
 4590	    Abs \== (-)
 4591	->  Dirs = []
 4592	;   java_home(JavaHome)
 4593	->  atom_concat(JavaHome, SubPath, ClientDir),
 4594	    (exists_directory(ClientDir) -> Dirs = [ClientDir] ; Dirs = [])
 4595	;   Dirs = []
 4596	).
 java_home(-Home) is semidet
Find the home location of Java.
Arguments:
Home- JAVA home in OS notation
 4604java_home_win_key(jre, 'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Runtime Environment').
 4605java_home_win_key(jdk, 'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Development Kit').
 4606
 4607java_home(Home) :-
 4608	getenv('JAVA_HOME', Home),
 4609	exists_directory(Home), !.
 4610:- if(current_prolog_flag(windows, true)). 4611java_home(Home) :-
 4612	java_home_win_key(_, Key0),	% currently user can't specify whether jre or jdk is preferable
 4613	catch(win_registry_get_value(Key0, 'CurrentVersion', Version), _, fail),
 4614	concat_atom([Key0, Version], /, Key),
 4615	win_registry_get_value(Key, 'JavaHome', Home),
 4616	exists_directory(Home), !.
 4617:- else. 4618java_home(Home) :-
 4619	member(Home, [ '/usr/lib/java',
 4620		       '/usr/local/lib/java'
 4621		     ]),
 4622	exists_directory(Home), !.
 4623:- endif. 4624
 4625:- dynamic
 4626	jvm_ready/0. 4627:- volatile
 4628	jvm_ready/0. 4629
 4630%%%:- module_transparent(link_swiplcs/1).
 4631
 4632load_swiplcs:- use_module(clipl),
 4633   context_module(X), user:link_swiplcs(X),
 4634   post_load_swipl.
 4635
 4636post_load_swipl:-set_prolog_flag(debug,true).
 4637
 4638setup_jvm :-
 4639	jvm_ready, !.
 4640%%logicmoo
 4641%%%setup_jvm :- load_swiplcs,assert(jvm_ready),!.
 4642setup_jvm:-!.
 4643setup_jvm :-
 4644	add_jpl_to_classpath,
 4645	add_java_to_ldpath,
 4646	libjpl(JPL),
 4647	add_jpl_to_ldpath(JPL),
 4648	catch(load_foreign_library(JPL), E, report_java_setup_problem(E)),
 4649	assert(jvm_ready).
 4650
 4651report_java_setup_problem(E) :-
 4652	print_message(error, E),
 4653	check_java_environment.
 4654
 4655% :- initialization(setup_jvm, now).
 4656
 4657% jpl_c_lib_version("4.0.30319.42000").