34
35:- module(jpl,
36 [ jpl_get_default_jvm_opts/1,
37 jpl_set_default_jvm_opts/1,
38 jpl_get_actual_jvm_opts/1,
39 jpl_pl_lib_version/1,
40 jpl_c_lib_version/1,
41 jpl_pl_syntax/1,
42 jpl_new/3,
43 jpl_call/4,
44 jpl_get/3,
45 jpl_set/3,
46 jpl_servlet_byref/3,
47 jpl_servlet_byval/3,
48 jpl_class_to_classname/2,
49 jpl_class_to_type/2,
50 jpl_classname_to_class/2,
51 jpl_classname_to_type/2, 52 jpl_datum_to_type/2,
53 jpl_entityname_to_type/2, 54 jpl_false/1,
55 jpl_is_class/1,
56 jpl_is_false/1,
57 jpl_is_null/1,
58 jpl_is_object/1,
59 jpl_is_object_type/1,
60 jpl_is_ref/1,
61 jpl_is_true/1,
62 jpl_is_type/1,
63 jpl_is_void/1,
64 jpl_null/1,
65 jpl_object_to_class/2,
66 jpl_object_to_type/2,
67 jpl_primitive_type/1,
68 jpl_ref_to_type/2,
69 jpl_true/1,
70 jpl_type_to_class/2,
71 jpl_type_to_classname/2, 72 jpl_type_to_entityname/2, 73 jpl_void/1,
74 jpl_array_to_length/2,
75 jpl_array_to_list/2,
76 jpl_datums_to_array/2,
77 jpl_enumeration_element/2,
78 jpl_enumeration_to_list/2,
79 jpl_hashtable_pair/2,
80 jpl_iterator_element/2,
81 jpl_list_to_array/2,
82 jpl_terms_to_array/2,
83 jpl_array_to_terms/2,
84 jpl_map_element/2,
85 jpl_set_element/2
86 ]). 87:- autoload(library(apply),[maplist/2]). 88:- use_module(library(debug),[assertion/1, debugging/1,debug/3]). 89:- use_module(library(yall)). 90:- autoload(library(lists),
91 [member/2,nth0/3,nth1/3,append/3,flatten/2,select/3]). 92:- autoload(library(shlib),[load_foreign_library/1]). 93
100
102:- set_prolog_flag(generate_debug_info, false). 103
104
132
133jpl_new(X, Params, V) :-
134 ( var(X)
135 -> throwme(jpl_new,x_is_var)
136 ; jpl_is_type(X) 137 -> Type = X
138 ; atom(X) 139 -> ( jpl_entityname_to_type(X, Type)
140 -> true
141 ; throwme(jpl_new,x_not_classname(X))
142 )
143 ; throwme(jpl_new,x_not_instantiable(X))
144 ),
145 jpl_new_1(Type, Params, Vx),
146 ( nonvar(V),
147 V = {Term} 148 -> ( jni_jref_to_term(Vx, TermX) 149 -> Term = TermX
150 ; throwme(jpl_new,not_a_jpl_term(Vx))
151 )
152 ; V = Vx
153 ).
154
155
165
166jpl_new_1(class(Ps,Cs), Params, Vx) :-
167 !, 168 Tx = class(Ps,Cs),
169 ( var(Params)
170 -> throwme(jpl_new_class,params_is_var)
171 ; \+ is_list(Params)
172 -> throwme(jpl_new_class,params_is_not_list(Params))
173 ; true
174 ),
175 length(Params, A), 176 jpl_type_to_class(Tx, Cx), 177 N = '<init>', 178 Tr = void, 179 findall(
180 z3(I,MID,Tfps),
181 jpl_method_spec(Tx, I, N, A, _Mods, MID, Tr, Tfps), 182 Z3s
183 ),
184 ( Z3s == [] 185 -> ( jpl_call(Cx, isInterface, [], @(true))
186 -> throwme(jpl_new_class,class_is_interface(Tx))
187 ; throwme(jpl_new_class,class_without_constructor(Tx,A))
188 )
189 ; ( catch(
190 jpl_datums_to_types(Params, Taps), 191 192 error(type_error(acyclic,Te),context(_,Msg)),
193 throwme(jpl_new_class,acyclic(Te,Msg)) 194 )
195 -> true
196 ; throwme(jpl_new_class,bad_jpl_datum(Params))
197 ),
198 findall(
199 z3(I,MID,Tfps), 200 ( member(z3(I,MID,Tfps), Z3s),
201 jpl_types_fit_types(Taps, Tfps) 202 ),
203 Z3sA
204 ),
205 ( Z3sA == [] 206 -> ( Z3s = [_]
207 -> throwme(jpl_new_class,single_constructor_mismatch(Tx/A))
208 ; throwme(jpl_new_class,any_constructor_mismatch(Params))
209 )
210 ; Z3sA = [z3(I,MID,Tfps)]
211 -> true
212 ; jpl_z3s_to_most_specific_z3(Z3sA, z3(I,MID,Tfps))
213 -> true
214 ; throwme(jpl_new_class,constructor_multimatch(Params))
215 )
216 ),
217 catch(
218 jNewObject(Cx, MID, Tfps, Params, Vx),
219 error(java_exception(_), 'java.lang.InstantiationException'),
220 throwme(jpl_new_class,class_is_abstract(Tx)) 221 ),
222 jpl_cache_type_of_ref(Tx, Vx). 223
224jpl_new_1(array(T), Params, Vx) :-
225 !,
226 ( var(Params)
227 -> throwme(jpl_new_array,params_is_var)
228 ; integer(Params) 229 -> ( Params >= 0
230 -> Len is Params
231 ; throwme(jpl_new_array,params_is_negative(Params))
232 )
233 ; is_list(Params) 234 -> length(Params, Len)
235 ),
236 jpl_new_array(T, Len, Vx), 237 ( nth0(I, Params, Param), 238 jpl_set(Vx, I, Param),
239 fail
240 ; true
241 ),
242 jpl_cache_type_of_ref(array(T), Vx). 243
244jpl_new_1(T, _Params, _Vx) :- 245 jpl_primitive_type(T),
246 !,
247 throwme(jpl_new_primitive,primitive_type_requested(T)).
248 249 250 251 252 253 254 255 256
257jpl_new_1(T, _, _) :- throwme(jpl_new_catchall,catchall(T)).
258
259
263
264jpl_new_array(boolean, Len, A) :-
265 jNewBooleanArray(Len, A).
266jpl_new_array(byte, Len, A) :-
267 jNewByteArray(Len, A).
268jpl_new_array(char, Len, A) :-
269 jNewCharArray(Len, A).
270jpl_new_array(short, Len, A) :-
271 jNewShortArray(Len, A).
272jpl_new_array(int, Len, A) :-
273 jNewIntArray(Len, A).
274jpl_new_array(long, Len, A) :-
275 jNewLongArray(Len, A).
276jpl_new_array(float, Len, A) :-
277 jNewFloatArray(Len, A).
278jpl_new_array(double, Len, A) :-
279 jNewDoubleArray(Len, A).
280jpl_new_array(array(T), Len, A) :-
281 jpl_type_to_class(array(T), C),
282 jNewObjectArray(Len, C, @(null), A). 283jpl_new_array(class(Ps,Cs), Len, A) :-
284 jpl_type_to_class(class(Ps,Cs), C),
285 jNewObjectArray(Len, C, @(null), A).
286
287
306
307jpl_call(X, Mspec, Params, R) :-
308 ( jpl_object_to_type(X, Type) 309 -> Obj = X,
310 Kind = instance
311 ; var(X)
312 -> throwme(jpl_call,arg1_is_var)
313 ; atom(X)
314 -> ( jpl_entityname_to_type(X, Type) 315 -> ( jpl_type_to_class(Type, ClassObj)
316 -> Kind = static
317 ; throwme(jpl_call,no_such_class(X))
318 )
319 ; throwme(jpl_call,arg1_is_bad(X))
320 )
321 ; X = class(_,_)
322 -> Type = X,
323 jpl_type_to_class(Type, ClassObj),
324 Kind = static
325 ; X = array(_)
326 -> throwme(jpl_call,arg1_is_array(X))
327 ; throwme(jpl_call,arg1_is_bad(X))
328 ),
329 ( atom(Mspec) 330 -> true
331 ; var(Mspec)
332 -> throwme(jpl_call,mspec_is_var)
333 ; throwme(jpl_call,mspec_is_bad(Mspec))
334 ),
335 ( is_list(Params)
336 -> ( catch(
337 jpl_datums_to_types(Params, Taps),
338 339 error(type_error(acyclic,Te),context(_,Msg)),
340 throwme(jpl_call,acyclic(Te,Msg)) 341 )
342 -> true
343
344 ; throwme(jpl_call,nonconvertible_params(Params))
345 ),
346 length(Params, A)
347 ; var(Params)
348 -> throwme(jpl_call,arg3_is_var)
349 ; throwme(jpl_call,arg3_is_bad(Params))
350 ),
351 ( Kind == instance
352 -> jpl_call_instance(Type, Obj, Mspec, Params, Taps, A, Rx)
353 ; jpl_call_static(Type, ClassObj, Mspec, Params, Taps, A, Rx)
354 ),
355 ( nonvar(R),
356 R = {Term} 357 -> ( jni_jref_to_term(Rx, TermX) 358 -> Term = TermX
359 ; throwme(jpl_call,not_a_jpl_term(Rx))
360 )
361 ; R = Rx
362 ).
363
364
371
372jpl_call_instance(Type, Obj, Mname, Params, Taps, A, Rx) :-
373 findall( 374 z5(I,Mods,MID,Tr,Tfps),
375 jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
376 Z5s
377 ),
378 ( Z5s = []
379 -> throwme(jpl_call_instance,no_such_method(Mname/A))
380 ; findall(
381 z5(I,Mods,MID,Tr,Tfps), 382 ( member(z5(I,Mods,MID,Tr,Tfps), Z5s),
383 jpl_types_fit_types(Taps, Tfps) 384 ),
385 Z5sA 386 ),
387 ( Z5sA == []
388 -> throwme(jpl_call_instance,param_not_assignable(Params))
389 ; Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
390 -> true 391 ; jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
392 -> true 393 ; throwme(jpl_call_instance,multiple_most_specific(Mname/Params))
394 )
395 ),
396 ( member(static, Mods) 397 -> jpl_object_to_class(Obj, ClassObj), 398 jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx) 399 ; jpl_call_instance_method(Tr, Obj, MID, Tfps, Params, Rx) 400 ).
401
402
410
411jpl_call_static(Type, ClassObj, Mname, Params, Taps, A, Rx) :-
412 findall( 413 z5(I,Mods,MID,Tr,Tfps),
414 ( jpl_method_spec(Type, I, Mname, A, Mods, MID, Tr, Tfps),
415 member(static, Mods)
416 ),
417 Z5s
418 ),
419 ( Z5s = []
420 -> throwme(jpl_call_static,no_such_method(Mname))
421 ; findall(
422 z5(I,Mods,MID,Tr,Tfps),
423 ( member(z5(I,Mods,MID,Tr,Tfps), Z5s),
424 jpl_types_fit_types(Taps, Tfps) 425 ),
426 Z5sA 427 ),
428 ( Z5sA == []
429 -> throwme(jpl_call_static,param_not_assignable(Params))
430 ; Z5sA = [z5(I,Mods,MID,Tr,Tfps)]
431 -> true 432 ; jpl_z5s_to_most_specific_z5(Z5sA, z5(I,Mods,MID,Tr,Tfps))
433 -> true 434 ; throwme(jpl_call_instance,multiple_most_specific(Mname/Params))
435 )
436 ),
437 jpl_call_static_method(Tr, ClassObj, MID, Tfps, Params, Rx).
438
439
441
442jpl_call_instance_method(void, Class, MID, Tfps, Ps, R) :-
443 jCallVoidMethod(Class, MID, Tfps, Ps),
444 jpl_void(R).
445jpl_call_instance_method(boolean, Class, MID, Tfps, Ps, R) :-
446 jCallBooleanMethod(Class, MID, Tfps, Ps, R).
447jpl_call_instance_method(byte, Class, MID, Tfps, Ps, R) :-
448 jCallByteMethod(Class, MID, Tfps, Ps, R).
449jpl_call_instance_method(char, Class, MID, Tfps, Ps, R) :-
450 jCallCharMethod(Class, MID, Tfps, Ps, R).
451jpl_call_instance_method(short, Class, MID, Tfps, Ps, R) :-
452 jCallShortMethod(Class, MID, Tfps, Ps, R).
453jpl_call_instance_method(int, Class, MID, Tfps, Ps, R) :-
454 jCallIntMethod(Class, MID, Tfps, Ps, R).
455jpl_call_instance_method(long, Class, MID, Tfps, Ps, R) :-
456 jCallLongMethod(Class, MID, Tfps, Ps, R).
457jpl_call_instance_method(float, Class, MID, Tfps, Ps, R) :-
458 jCallFloatMethod(Class, MID, Tfps, Ps, R).
459jpl_call_instance_method(double, Class, MID, Tfps, Ps, R) :-
460 jCallDoubleMethod(Class, MID, Tfps, Ps, R).
461jpl_call_instance_method(array(_), Class, MID, Tfps, Ps, R) :-
462 jCallObjectMethod(Class, MID, Tfps, Ps, R).
463jpl_call_instance_method(class(_,_), Class, MID, Tfps, Ps, R) :-
464 jCallObjectMethod(Class, MID, Tfps, Ps, R).
465
466
468
469jpl_call_static_method(void, Class, MID, Tfps, Ps, R) :-
470 jCallStaticVoidMethod(Class, MID, Tfps, Ps),
471 jpl_void(R).
472jpl_call_static_method(boolean, Class, MID, Tfps, Ps, R) :-
473 jCallStaticBooleanMethod(Class, MID, Tfps, Ps, R).
474jpl_call_static_method(byte, Class, MID, Tfps, Ps, R) :-
475 jCallStaticByteMethod(Class, MID, Tfps, Ps, R).
476jpl_call_static_method(char, Class, MID, Tfps, Ps, R) :-
477 jCallStaticCharMethod(Class, MID, Tfps, Ps, R).
478jpl_call_static_method(short, Class, MID, Tfps, Ps, R) :-
479 jCallStaticShortMethod(Class, MID, Tfps, Ps, R).
480jpl_call_static_method(int, Class, MID, Tfps, Ps, R) :-
481 jCallStaticIntMethod(Class, MID, Tfps, Ps, R).
482jpl_call_static_method(long, Class, MID, Tfps, Ps, R) :-
483 jCallStaticLongMethod(Class, MID, Tfps, Ps, R).
484jpl_call_static_method(float, Class, MID, Tfps, Ps, R) :-
485 jCallStaticFloatMethod(Class, MID, Tfps, Ps, R).
486jpl_call_static_method(double, Class, MID, Tfps, Ps, R) :-
487 jCallStaticDoubleMethod(Class, MID, Tfps, Ps, R).
488jpl_call_static_method(array(_), Class, MID, Tfps, Ps, R) :-
489 jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
490jpl_call_static_method(class(_,_), Class, MID, Tfps, Ps, R) :-
491 jCallStaticObjectMethod(Class, MID, Tfps, Ps, R).
492
493
522
523jpl_get(X, Fspec, V) :-
524 ( jpl_object_to_type(X, Type)
525 -> Obj = X,
526 jpl_get_instance(Type, Type, Obj, Fspec, Vx) 527 ; var(X)
528 -> throwme(jpl_get,arg1_is_var)
529 ; jpl_is_type(X) 530 -> Type = X,
531 ( jpl_type_to_class(Type, ClassObj)
532 -> jpl_get_static(Type, ClassObj, Fspec, Vx)
533 ; throwme(jpl_get,named_class_not_found(Type))
534 )
535 ; atom(X)
536 -> ( jpl_entityname_to_type(X, Type) 537 -> ( jpl_type_to_class(Type, ClassObj)
538 -> jpl_get_static(Type, ClassObj, Fspec, Vx)
539 ; throwme(jpl_get,named_class_not_found(Type))
540 )
541 ; throwme(jpl_get,arg1_is_bad(X))
542 )
543 ; throwme(jpl_get,arg1_is_bad_2(X))
544 ),
545 ( nonvar(V),
546 V = {Term} 547 -> ( jni_jref_to_term(Vx, TermX) 548 -> Term = TermX
549 ; throwme(jpl_get,not_a_jpl_term(X))
550 )
551 ; V = Vx
552 ).
553
554
555
556
563
564jpl_get_static(Type, ClassObj, Fname, Vx) :-
565 ( atom(Fname) 566 -> true
567 ; var(Fname)
568 -> throwme(jpl_get_static,arg2_is_var)
569 ; throwme(jpl_get_static,arg2_is_bad(Fname))
570 ),
571 572 findall(
573 z4(I,Mods,FID,Tf),
574 ( jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
575 member(static, Mods)
576 ),
577 Z4s
578 ),
579 ( Z4s = []
580 -> throwme(jpl_get_static,no_such_field(Fname))
581 ; Z4s = [z4(I,_Mods,FID,Tf)]
582 -> jpl_get_static_field(Tf, ClassObj, FID, Vx)
583 ; throwme(jpl_get_static,multiple_fields(Fname))
584 ).
585
586
587
589
590jpl_get_instance(class(_,_), Type, Obj, Fname, Vx) :-
591 ( atom(Fname) 592 -> true
593 ; var(Fname)
594 -> throwme(jpl_get_instance,arg2_is_var)
595 ; throwme(jpl_get_instance,arg2_is_bad(Fname))
596 ),
597 findall(
598 z4(I,Mods,FID,Tf),
599 jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
600 Z4s
601 ),
602 ( Z4s = []
603 -> throwme(jpl_get_instance,no_such_field(Fname))
604 ; Z4s = [z4(I,Mods,FID,Tf)]
605 -> ( member(static, Mods)
606 -> jpl_object_to_class(Obj, ClassObj),
607 jpl_get_static_field(Tf, ClassObj, FID, Vx)
608 ; jpl_get_instance_field(Tf, Obj, FID, Vx)
609 )
610 ; throwme(jpl_get_instance,multiple_fields(Fname))
611 ).
612
613
614jpl_get_instance(array(ElementType), _, Array, Fspec, Vx) :-
615 ( var(Fspec)
616 -> throwme(jpl_get_instance_array,arg2_is_var)
617 ; integer(Fspec)
618 -> ( Fspec < 0 619 -> throwme(jpl_get_instance_array,arg2_is_bad(Fspec))
620 ; jGetArrayLength(Array, Len),
621 Fspec >= Len 622 -> throwme(jpl_get_instance_array,arg2_is_too_large(Fspec))
623 ; jpl_get_array_element(ElementType, Array, Fspec, Vx)
624 )
625 ; Fspec = N-M 626 -> ( integer(N),
627 integer(M)
628 -> ( N >= 0,
629 M >= N
630 -> jGetArrayLength(Array, Len),
631 ( N >= Len
632 -> throwme(jpl_get_instance_array,bad_range_low(N-M))
633 ; M >= Len
634 -> throwme(jpl_get_instance_array,bad_range_high(N-M))
635 ; jpl_get_array_elements(ElementType, Array, N, M, Vx)
636 )
637 ; throwme(jpl_get_instance_array,bad_range_pair_values(N-M))
638 )
639 ; throwme(jpl_get_instance_array,bad_range_pair_types(N-M))
640 )
641 ; atom(Fspec)
642 -> ( Fspec == length 643 -> jGetArrayLength(Array, Vx)
644 ; throwme(jpl_get_instance_array,no_such_field(Fspec))
645 )
646 ; throwme(jpl_get_instance_array,wrong_spec(Fspec))
647 ).
648
649
650
659
660jpl_get_array_element(Type, Array, Index, Vc) :-
661 ( ( Type = class(_,_)
662 ; Type = array(_)
663 )
664 -> jGetObjectArrayElement(Array, Index, Vr)
665 ; jpl_primitive_type(Type)
666 -> jni_type_to_xput_code(Type, Xc),
667 jni_alloc_buffer(Xc, 1, Bp), 668 jpl_get_primitive_array_region(Type, Array, Index, 1, Bp),
669 jni_fetch_buffer_value(Bp, 0, Vr, Xc), 670 jni_free_buffer(Bp)
671 ),
672 Vr = Vc. 673
674
680
681jpl_get_array_elements(ElementType, Array, N, M, Vs) :-
682 ( ( ElementType = class(_,_)
683 ; ElementType = array(_)
684 )
685 -> jpl_get_object_array_elements(Array, N, M, Vs)
686 ; jpl_get_primitive_array_elements(ElementType, Array, N, M, Vs)
687 ).
688
689
690jpl_get_instance_field(boolean, Obj, FieldID, V) :-
691 jGetBooleanField(Obj, FieldID, V).
692jpl_get_instance_field(byte, Obj, FieldID, V) :-
693 jGetByteField(Obj, FieldID, V).
694jpl_get_instance_field(char, Obj, FieldID, V) :-
695 jGetCharField(Obj, FieldID, V).
696jpl_get_instance_field(short, Obj, FieldID, V) :-
697 jGetShortField(Obj, FieldID, V).
698jpl_get_instance_field(int, Obj, FieldID, V) :-
699 jGetIntField(Obj, FieldID, V).
700jpl_get_instance_field(long, Obj, FieldID, V) :-
701 jGetLongField(Obj, FieldID, V).
702jpl_get_instance_field(float, Obj, FieldID, V) :-
703 jGetFloatField(Obj, FieldID, V).
704jpl_get_instance_field(double, Obj, FieldID, V) :-
705 jGetDoubleField(Obj, FieldID, V).
706jpl_get_instance_field(class(_,_), Obj, FieldID, V) :-
707 jGetObjectField(Obj, FieldID, V).
708jpl_get_instance_field(array(_), Obj, FieldID, V) :-
709 jGetObjectField(Obj, FieldID, V).
710
711
720
721jpl_get_object_array_elements(Array, Lo, Hi, Vcs) :-
722 ( Lo =< Hi
723 -> Vcs = [Vc|Vcs2],
724 jGetObjectArrayElement(Array, Lo, Vc),
725 Next is Lo+1,
726 jpl_get_object_array_elements(Array, Next, Hi, Vcs2)
727 ; Vcs = []
728 ).
729
730
737
738jpl_get_primitive_array_elements(ElementType, Array, Lo, Hi, Vcs) :-
739 Size is Hi-Lo+1,
740 ( Size == 0
741 -> Vcs = []
742 ; jni_type_to_xput_code(ElementType, Xc),
743 jni_alloc_buffer(Xc, Size, Bp),
744 jpl_get_primitive_array_region(ElementType, Array, Lo, Size, Bp),
745 jpl_primitive_buffer_to_array(ElementType, Xc, Bp, 0, Size, Vcs),
746 jni_free_buffer(Bp)
747 ).
748
749
750jpl_get_primitive_array_region(boolean, Array, Lo, S, I) :-
751 jGetBooleanArrayRegion(Array, Lo, S, jbuf(I,boolean)).
752jpl_get_primitive_array_region(byte, Array, Lo, S, I) :-
753 jGetByteArrayRegion(Array, Lo, S, jbuf(I,byte)).
754jpl_get_primitive_array_region(char, Array, Lo, S, I) :-
755 jGetCharArrayRegion(Array, Lo, S, jbuf(I,char)).
756jpl_get_primitive_array_region(short, Array, Lo, S, I) :-
757 jGetShortArrayRegion(Array, Lo, S, jbuf(I,short)).
758jpl_get_primitive_array_region(int, Array, Lo, S, I) :-
759 jGetIntArrayRegion(Array, Lo, S, jbuf(I,int)).
760jpl_get_primitive_array_region(long, Array, Lo, S, I) :-
761 jGetLongArrayRegion(Array, Lo, S, jbuf(I,long)).
762jpl_get_primitive_array_region(float, Array, Lo, S, I) :-
763 jGetFloatArrayRegion(Array, Lo, S, jbuf(I,float)).
764jpl_get_primitive_array_region(double, Array, Lo, S, I) :-
765 jGetDoubleArrayRegion(Array, Lo, S, jbuf(I,double)).
766
767
768jpl_get_static_field(boolean, Array, FieldID, V) :-
769 jGetStaticBooleanField(Array, FieldID, V).
770jpl_get_static_field(byte, Array, FieldID, V) :-
771 jGetStaticByteField(Array, FieldID, V).
772jpl_get_static_field(char, Array, FieldID, V) :-
773 jGetStaticCharField(Array, FieldID, V).
774jpl_get_static_field(short, Array, FieldID, V) :-
775 jGetStaticShortField(Array, FieldID, V).
776jpl_get_static_field(int, Array, FieldID, V) :-
777 jGetStaticIntField(Array, FieldID, V).
778jpl_get_static_field(long, Array, FieldID, V) :-
779 jGetStaticLongField(Array, FieldID, V).
780jpl_get_static_field(float, Array, FieldID, V) :-
781 jGetStaticFloatField(Array, FieldID, V).
782jpl_get_static_field(double, Array, FieldID, V) :-
783 jGetStaticDoubleField(Array, FieldID, V).
784jpl_get_static_field(class(_,_), Array, FieldID, V) :-
785 jGetStaticObjectField(Array, FieldID, V).
786jpl_get_static_field(array(_), Array, FieldID, V) :-
787 jGetStaticObjectField(Array, FieldID, V).
788
789
806
807jpl_set(X, Fspec, V) :-
808 ( jpl_object_to_type(X, Type) 809 -> Obj = X,
810 catch(
811 jpl_set_instance(Type, Type, Obj, Fspec, V), 812 813 error(type_error(acyclic,Te),context(_,Msg)),
814 throwme(jpl_set,acyclic(Te,Msg)) 815 )
816 ; var(X)
817 -> throwme(jpl_set,arg1_is_var)
818 ; ( atom(X)
819 -> ( jpl_entityname_to_type(X, Type) 820 -> true
821 ; throwme(jpl_set,classname_does_not_resolve(X))
822 )
823 ; ( X = class(_,_) 824 ; X = array(_) 825 )
826 -> Type = X
827 ),
828 ( jpl_type_to_class(Type, ClassObj) 829 -> true
830 ; throwme(jpl_set,named_class_not_found(Type))
831 )
832 -> catch(
833 jpl_set_static(Type, ClassObj, Fspec, V),
834 835 error(type_error(acyclic,Te),context(_,Msg)),
836 throwme(jpl_set,acyclic(Te,Msg)) 837 )
838 ; throwme(jpl_set,arg1_is_bad(X))
839 ).
840
841
851
852jpl_set_instance(class(_,_), Type, Obj, Fname, V) :- 853 ( atom(Fname) 854 -> true
855 ; var(Fname)
856 -> throwme(jpl_set_instance_class,arg2_is_var)
857 ; throwme(jpl_set_instance_class,arg2_is_bad(Fname))
858 ),
859 findall(
860 z4(I,Mods,FID,Tf),
861 jpl_field_spec(Type, I, Fname, Mods, FID, Tf), 862 Z4s
863 ),
864 ( Z4s = []
865 -> throwme(jpl_set_instance_class,no_such_field(Fname))
866 ; Z4s = [z4(I,Mods,FID,Tf)]
867 -> ( member(final, Mods)
868 -> throwme(jpl_set_instance_class,field_is_final(Fname))
869 ; jpl_datum_to_type(V, Tv)
870 -> ( jpl_type_fits_type(Tv, Tf)
871 -> ( member(static, Mods)
872 -> jpl_object_to_class(Obj, ClassObj),
873 jpl_set_static_field(Tf, ClassObj, FID, V)
874 ; jpl_set_instance_field(Tf, Obj, FID, V) 875 )
876 ; throwme(jpl_set_instance_class,incompatible_value(Tf,V))
877 )
878 ; throwme(jpl_set_instance_class,arg3_is_bad(V))
879 )
880 ; throwme(jpl_set_instance_class,multiple_fields(Fname)) 881 ).
882
883
884
885jpl_set_instance(array(Type), _, Obj, Fspec, V) :-
886 ( is_list(V) 887 -> Vs = V
888 ; var(V)
889 -> throwme(jpl_set_instance_array,arg3_is_var)
890 ; Vs = [V] 891 ),
892 length(Vs, Iv),
893 ( var(Fspec)
894 -> throwme(jpl_set_instance_array,arg2_is_var)
895 ; integer(Fspec) 896 -> ( Fspec < 0
897 -> throwme(jpl_set_instance_array,arg2_is_bad(Fspec))
898 ; Iv is 1
899 -> N is Fspec
900 ; Iv is 0
901 -> throwme(jpl_set_instance_array,no_values(Fspec,Vs))
902 ; throwme(jpl_set_instance_array,more_than_one_value(Fspec,Vs))
903 )
904 ; Fspec = N-M 905 -> ( integer(N),
906 integer(M)
907 -> ( N >= 0,
908 Size is (M-N)+1,
909 Size >= 0
910 -> ( Size == Iv
911 -> true
912 ; Size < Iv
913 -> throwme(jpl_set_instance_array,too_few_values(N-M,Vs))
914 ; throwme(jpl_set_instance_array,too_many_values(N-M,Vs))
915 )
916 ; throwme(jpl_set_instance_array,bad_range_pair_values(N-M))
917 )
918 ; throwme(jpl_set_instance_array,bad_range_pair_types(N-M))
919 )
920 ; atom(Fspec)
921 -> ( Fspec == length
922 -> throwme(jpl_set_instance_array,cannot_assign_to_final_field)
923 ; throwme(jpl_set_instance_array,no_such_field(Fspec))
924 )
925 ; throwme(jpl_set_instance_array,arg2_is_bad_2(Fspec))
926 ),
927 jpl_set_array(Type, Obj, N, Iv, Vs).
928
929
941
942jpl_set_static(Type, ClassObj, Fname, V) :-
943 ( atom(Fname) 944 -> true
945 ; var(Fname)
946 -> throwme(jpl_set_static,arg2_is_unbound)
947 ; throwme(jpl_set_static,arg2_is_bad(Fname))
948 ),
949 findall( 950 z4(I,Mods,FID,Tf),
951 ( jpl_field_spec(Type, I, Fname, Mods, FID, Tf),
952 member(static, Mods)
953 ),
954 Z4s
955 ),
956 ( Z4s = []
957 -> throwme(jpl_set_static,no_such_public_static_field(field,Fname))
958 ; Z4s = [z4(I,Mods,FID,Tf)] 959 -> ( member(final, Mods)
960 -> throwme(jpl_set_static,cannot_assign_final_field(Fname))
961 ; jpl_datum_to_type(V, Tv)
962 -> ( jpl_type_fits_type(Tv, Tf)
963 -> jpl_set_static_field(Tf, ClassObj, FID, V)
964 ; throwme(jpl_set_static,value_not_assignable(Tf,V))
965 )
966 ; throwme(jpl_set_static,arg3_is_bad(field_value,V))
967 )
968 ; throwme(jpl_set_static,multiple_matches(field,Fname))
969 ).
970
971
978
979jpl_set_array(T, A, N, I, Ds) :-
980 ( jpl_datums_to_types(Ds, Tds) 981 -> ( jpl_types_fit_type(Tds, T) 982 -> true
983 ; throwme(jpl_set_array,not_all_values_assignable(T,Ds))
984 )
985 ; throwme(jpl_set_array,not_all_values_convertible(T,Ds))
986 ),
987 ( ( T = class(_,_)
988 ; T = array(_) 989 )
990 -> ( nth0(J, Ds, D), 991 Nd is N+J, 992 ( D = {Tq} 993 -> jni_term_to_jref(Tq, D2) 994 ; D = D2
995 ),
996 jSetObjectArrayElement(A, Nd, D2),
997 fail 998 ; true
999 )
1000 ; jpl_primitive_type(T) 1001 -> jni_type_to_xput_code(T, Xc),
1002 jni_alloc_buffer(Xc, I, Bp), 1003 jpl_set_array_1(Ds, T, 0, Bp),
1004 jpl_set_elements(T, A, N, I, Bp),
1005 jni_free_buffer(Bp)
1006 ;
1007 1008 throwme(jpl_set_array,element_type_unknown(array_element_type,T))
1009 ).
1010
1011
1019
1020jpl_set_array_1([], _, _, _).
1021jpl_set_array_1([V|Vs], Tprim, Ib, Bp) :-
1022 jni_type_to_xput_code(Tprim, Xc),
1023 jni_stash_buffer_value(Bp, Ib, V, Xc),
1024 Ibnext is Ib+1,
1025 jpl_set_array_1(Vs, Tprim, Ibnext, Bp).
1026
1027
1028jpl_set_elements(boolean, Obj, N, I, Bp) :-
1029 jSetBooleanArrayRegion(Obj, N, I, jbuf(Bp,boolean)).
1030jpl_set_elements(char, Obj, N, I, Bp) :-
1031 jSetCharArrayRegion(Obj, N, I, jbuf(Bp,char)).
1032jpl_set_elements(byte, Obj, N, I, Bp) :-
1033 jSetByteArrayRegion(Obj, N, I, jbuf(Bp,byte)).
1034jpl_set_elements(short, Obj, N, I, Bp) :-
1035 jSetShortArrayRegion(Obj, N, I, jbuf(Bp,short)).
1036jpl_set_elements(int, Obj, N, I, Bp) :-
1037 jSetIntArrayRegion(Obj, N, I, jbuf(Bp,int)).
1038jpl_set_elements(long, Obj, N, I, Bp) :-
1039 jSetLongArrayRegion(Obj, N, I, jbuf(Bp,long)).
1040jpl_set_elements(float, Obj, N, I, Bp) :-
1041 jSetFloatArrayRegion(Obj, N, I, jbuf(Bp,float)).
1042jpl_set_elements(double, Obj, N, I, Bp) :-
1043 jSetDoubleArrayRegion(Obj, N, I, jbuf(Bp,double)).
1044
1045
1050
1051jpl_set_instance_field(boolean, Obj, FieldID, V) :-
1052 jSetBooleanField(Obj, FieldID, V).
1053jpl_set_instance_field(byte, Obj, FieldID, V) :-
1054 jSetByteField(Obj, FieldID, V).
1055jpl_set_instance_field(char, Obj, FieldID, V) :-
1056 jSetCharField(Obj, FieldID, V).
1057jpl_set_instance_field(short, Obj, FieldID, V) :-
1058 jSetShortField(Obj, FieldID, V).
1059jpl_set_instance_field(int, Obj, FieldID, V) :-
1060 jSetIntField(Obj, FieldID, V).
1061jpl_set_instance_field(long, Obj, FieldID, V) :-
1062 jSetLongField(Obj, FieldID, V).
1063jpl_set_instance_field(float, Obj, FieldID, V) :-
1064 jSetFloatField(Obj, FieldID, V).
1065jpl_set_instance_field(double, Obj, FieldID, V) :-
1066 jSetDoubleField(Obj, FieldID, V).
1067jpl_set_instance_field(class(_,_), Obj, FieldID, V) :- 1068 ( V = {T} 1069 -> jni_term_to_jref(T, V2) 1070 ; V = V2
1071 ),
1072 jSetObjectField(Obj, FieldID, V2).
1073jpl_set_instance_field(array(_), Obj, FieldID, V) :-
1074 jSetObjectField(Obj, FieldID, V).
1075
1076
1081
1082jpl_set_static_field(boolean, Obj, FieldID, V) :-
1083 jSetStaticBooleanField(Obj, FieldID, V).
1084jpl_set_static_field(byte, Obj, FieldID, V) :-
1085 jSetStaticByteField(Obj, FieldID, V).
1086jpl_set_static_field(char, Obj, FieldID, V) :-
1087 jSetStaticCharField(Obj, FieldID, V).
1088jpl_set_static_field(short, Obj, FieldID, V) :-
1089 jSetStaticShortField(Obj, FieldID, V).
1090jpl_set_static_field(int, Obj, FieldID, V) :-
1091 jSetStaticIntField(Obj, FieldID, V).
1092jpl_set_static_field(long, Obj, FieldID, V) :-
1093 jSetStaticLongField(Obj, FieldID, V).
1094jpl_set_static_field(float, Obj, FieldID, V) :-
1095 jSetStaticFloatField(Obj, FieldID, V).
1096jpl_set_static_field(double, Obj, FieldID, V) :-
1097 jSetStaticDoubleField(Obj, FieldID, V).
1098jpl_set_static_field(class(_,_), Obj, FieldID, V) :- 1099 ( V = {T} 1100 -> jni_term_to_jref(T, V2) 1101 ; V = V2
1102 ),
1103 jSetStaticObjectField(Obj, FieldID, V2).
1104jpl_set_static_field(array(_), Obj, FieldID, V) :-
1105 jSetStaticObjectField(Obj, FieldID, V).
1106
1107
1112
1113jpl_get_default_jvm_opts(Opts) :-
1114 jni_get_default_jvm_opts(Opts).
1115
1116
1120
1121jpl_set_default_jvm_opts(Opts) :-
1122 is_list(Opts),
1123 length(Opts, N),
1124 jni_set_default_jvm_opts(N, Opts).
1125
1126
1132
1133jpl_get_actual_jvm_opts(Opts) :-
1134 jni_get_actual_jvm_opts(Opts).
1135
1139
1144
1145:- dynamic jpl_field_spec_cache/6. 1146:- dynamic jpl_field_spec_is_cached/1. 1147:- dynamic jpl_method_spec_cache/8. 1148:- dynamic jpl_method_spec_is_cached/1. 1149:- dynamic jpl_iref_type_cache/2. 1150
1156
1157:- dynamic jpl_classname_type_cache/2. 1158
1170
1171:- dynamic jpl_class_tag_type_cache/2. 1172
1195
1196jpl_assert(Fact) :-
1197 ( jpl_assert_policy(Fact, yes)
1198 -> assertz(Fact)
1199 ; true
1200 ).
1201
1205
1206jpl_assert_policy(jpl_field_spec_cache(_,_,_,_,_,_), yes).
1207jpl_assert_policy(jpl_field_spec_is_cached(_), YN) :-
1208 jpl_assert_policy(jpl_field_spec_cache(_,_,_,_,_,_), YN).
1209
1210jpl_assert_policy(jpl_method_spec_cache(_,_,_,_,_,_,_,_), yes).
1211jpl_assert_policy(jpl_method_spec_is_cached(_), YN) :-
1212 jpl_assert_policy(jpl_method_spec_cache(_,_,_,_,_,_,_,_), YN).
1213
1214jpl_assert_policy(jpl_class_tag_type_cache(_,_), yes).
1215jpl_assert_policy(jpl_classname_type_cache(_,_), yes).
1216jpl_assert_policy(jpl_iref_type_cache(_,_), no). 1217
1223
1224jpl_tidy_iref_type_cache(Iref) :-
1225 1226 retractall(jpl_iref_type_cache(Iref,_)),
1227 true.
1228
1229jpl_fergus_find_candidate([], Candidate, Candidate, []).
1230jpl_fergus_find_candidate([X|Xs], Candidate0, Candidate, Rest) :-
1231 ( jpl_fergus_greater(X, Candidate0)
1232 -> Candidate1 = X,
1233 Rest = [Candidate0|Rest1]
1234 ; Candidate1 = Candidate0,
1235 Rest = [X|Rest1]
1236 ),
1237 jpl_fergus_find_candidate(Xs, Candidate1, Candidate, Rest1).
1238
1239
1240jpl_fergus_greater(z5(_,_,_,_,Tps1), z5(_,_,_,_,Tps2)) :-
1241 jpl_types_fit_types(Tps1, Tps2).
1242jpl_fergus_greater(z3(_,_,Tps1), z3(_,_,Tps2)) :-
1243 jpl_types_fit_types(Tps1, Tps2).
1244
1245
1253
1254jpl_fergus_is_the_greatest([X|Xs], Greatest) :-
1255 jpl_fergus_find_candidate(Xs, X, Greatest, Rest),
1256 forall(
1257 member(R, Rest),
1258 jpl_fergus_greater(Greatest, R)
1259 ).
1260
1261
1268
1269jpl_z3s_to_most_specific_z3(Zs, Z) :-
1270 jpl_fergus_is_the_greatest(Zs, Z).
1271
1272
1279
1280jpl_z5s_to_most_specific_z5(Zs, Z) :-
1281 jpl_fergus_is_the_greatest(Zs, Z).
1282
1283
1296
1297jpl_pl_lib_version(VersionString) :-
1298 jpl_pl_lib_version(Major, Minor, Patch, Status),
1299 atomic_list_concat([Major,'.',Minor,'.',Patch,'-',Status], VersionString).
1300
1301
1315
1316jpl_pl_lib_version(7, 6, 1, stable). 1317
1330
1331
1342
1344
1345jpl_java_lib_version(V) :-
1346 jpl_call('org.jpl7.JPL', version_string, [], V).
1347
1348
1350
1351jpl_pl_lib_path(Path) :-
1352 module_property(jpl, file(Path)).
1353
1354
1356
1357jpl_c_lib_path(Path) :-
1358 shlib:current_library(_, _, Path, jpl, _),
1359 !.
1360
1361
1363
1364jpl_java_lib_path(Path) :-
1365 jpl_call('org.jpl7.JPL', jarPath, [], Path).
1366
1367
1369
1370jCallBooleanMethod(Obj, MethodID, Types, Params, Rbool) :-
1371 jni_params_put(Params, Types, ParamBuf),
1372 jni_func(39, Obj, MethodID, ParamBuf, Rbool).
1373
1374
1375
1377
1378jCallByteMethod(Obj, MethodID, Types, Params, Rbyte) :-
1379 jni_params_put(Params, Types, ParamBuf),
1380 jni_func(42, Obj, MethodID, ParamBuf, Rbyte).
1381
1382
1383
1385
1386jCallCharMethod(Obj, MethodID, Types, Params, Rchar) :-
1387 jni_params_put(Params, Types, ParamBuf),
1388 jni_func(45, Obj, MethodID, ParamBuf, Rchar).
1389
1390
1392
1393jCallDoubleMethod(Obj, MethodID, Types, Params, Rdouble) :-
1394 jni_params_put(Params, Types, ParamBuf),
1395 jni_func(60, Obj, MethodID, ParamBuf, Rdouble).
1396
1397
1399
1400jCallFloatMethod(Obj, MethodID, Types, Params, Rfloat) :-
1401 jni_params_put(Params, Types, ParamBuf),
1402 jni_func(57, Obj, MethodID, ParamBuf, Rfloat).
1403
1404
1406
1407jCallIntMethod(Obj, MethodID, Types, Params, Rint) :-
1408 jni_params_put(Params, Types, ParamBuf),
1409 jni_func(51, Obj, MethodID, ParamBuf, Rint).
1410
1411
1413
1414jCallLongMethod(Obj, MethodID, Types, Params, Rlong) :-
1415 jni_params_put(Params, Types, ParamBuf),
1416 jni_func(54, Obj, MethodID, ParamBuf, Rlong).
1417
1418
1420
1421jCallObjectMethod(Obj, MethodID, Types, Params, Robj) :-
1422 jni_params_put(Params, Types, ParamBuf),
1423 jni_func(36, Obj, MethodID, ParamBuf, Robj).
1424
1425
1427
1428jCallShortMethod(Obj, MethodID, Types, Params, Rshort) :-
1429 jni_params_put(Params, Types, ParamBuf),
1430 jni_func(48, Obj, MethodID, ParamBuf, Rshort).
1431
1432
1434
1435jCallStaticBooleanMethod(Class, MethodID, Types, Params, Rbool) :-
1436 jni_params_put(Params, Types, ParamBuf),
1437 jni_func(119, Class, MethodID, ParamBuf, Rbool).
1438
1439
1441
1442jCallStaticByteMethod(Class, MethodID, Types, Params, Rbyte) :-
1443 jni_params_put(Params, Types, ParamBuf),
1444 jni_func(122, Class, MethodID, ParamBuf, Rbyte).
1445
1446
1448
1449jCallStaticCharMethod(Class, MethodID, Types, Params, Rchar) :-
1450 jni_params_put(Params, Types, ParamBuf),
1451 jni_func(125, Class, MethodID, ParamBuf, Rchar).
1452
1453
1455
1456jCallStaticDoubleMethod(Class, MethodID, Types, Params, Rdouble) :-
1457 jni_params_put(Params, Types, ParamBuf),
1458 jni_func(140, Class, MethodID, ParamBuf, Rdouble).
1459
1460
1462
1463jCallStaticFloatMethod(Class, MethodID, Types, Params, Rfloat) :-
1464 jni_params_put(Params, Types, ParamBuf),
1465 jni_func(137, Class, MethodID, ParamBuf, Rfloat).
1466
1467
1469
1470jCallStaticIntMethod(Class, MethodID, Types, Params, Rint) :-
1471 jni_params_put(Params, Types, ParamBuf),
1472 jni_func(131, Class, MethodID, ParamBuf, Rint).
1473
1474
1476
1477jCallStaticLongMethod(Class, MethodID, Types, Params, Rlong) :-
1478 jni_params_put(Params, Types, ParamBuf),
1479 jni_func(134, Class, MethodID, ParamBuf, Rlong).
1480
1481
1483
1484jCallStaticObjectMethod(Class, MethodID, Types, Params, Robj) :-
1485 jni_params_put(Params, Types, ParamBuf),
1486 jni_func(116, Class, MethodID, ParamBuf, Robj).
1487
1488
1490
1491jCallStaticShortMethod(Class, MethodID, Types, Params, Rshort) :-
1492 jni_params_put(Params, Types, ParamBuf),
1493 jni_func(128, Class, MethodID, ParamBuf, Rshort).
1494
1495
1497
1498jCallStaticVoidMethod(Class, MethodID, Types, Params) :-
1499 jni_params_put(Params, Types, ParamBuf),
1500 jni_void(143, Class, MethodID, ParamBuf).
1501
1502
1504
1505jCallVoidMethod(Obj, MethodID, Types, Params) :-
1506 jni_params_put(Params, Types, ParamBuf),
1507 jni_void(63, Obj, MethodID, ParamBuf).
1508
1509
1511
1512jFindClass(ClassName, Class) :-
1513 jni_func(6, ClassName, Class).
1514
1515
1517
1518jGetArrayLength(Array, Size) :-
1519 jni_func(171, Array, Size).
1520
1521
1523
1524jGetBooleanArrayRegion(Array, Start, Len, Buf) :-
1525 jni_void(199, Array, Start, Len, Buf).
1526
1527
1529
1530jGetBooleanField(Obj, FieldID, Rbool) :-
1531 jni_func(96, Obj, FieldID, Rbool).
1532
1533
1535
1536jGetByteArrayRegion(Array, Start, Len, Buf) :-
1537 jni_void(200, Array, Start, Len, Buf).
1538
1539
1541
1542jGetByteField(Obj, FieldID, Rbyte) :-
1543 jni_func(97, Obj, FieldID, Rbyte).
1544
1545
1547
1548jGetCharArrayRegion(Array, Start, Len, Buf) :-
1549 jni_void(201, Array, Start, Len, Buf).
1550
1551
1553
1554jGetCharField(Obj, FieldID, Rchar) :-
1555 jni_func(98, Obj, FieldID, Rchar).
1556
1557
1559
1560jGetDoubleArrayRegion(Array, Start, Len, Buf) :-
1561 jni_void(206, Array, Start, Len, Buf).
1562
1563
1565
1566jGetDoubleField(Obj, FieldID, Rdouble) :-
1567 jni_func(103, Obj, FieldID, Rdouble).
1568
1569
1571
1572jGetFieldID(Class, Name, Type, FieldID) :-
1573 jpl_type_to_java_field_descriptor(Type, FD),
1574 jni_func(94, Class, Name, FD, FieldID).
1575
1576
1578
1579jGetFloatArrayRegion(Array, Start, Len, Buf) :-
1580 jni_void(205, Array, Start, Len, Buf).
1581
1582
1584
1585jGetFloatField(Obj, FieldID, Rfloat) :-
1586 jni_func(102, Obj, FieldID, Rfloat).
1587
1588
1590
1591jGetIntArrayRegion(Array, Start, Len, Buf) :-
1592 jni_void(203, Array, Start, Len, Buf).
1593
1594
1596
1597jGetIntField(Obj, FieldID, Rint) :-
1598 jni_func(100, Obj, FieldID, Rint).
1599
1600
1602
1603jGetLongArrayRegion(Array, Start, Len, Buf) :-
1604 jni_void(204, Array, Start, Len, Buf).
1605
1606
1608
1609jGetLongField(Obj, FieldID, Rlong) :-
1610 jni_func(101, Obj, FieldID, Rlong).
1611
1612
1614
1615jGetMethodID(Class, Name, Type, MethodID) :-
1616 jpl_type_to_java_method_descriptor(Type, MD),
1617 jni_func(33, Class, Name, MD, MethodID).
1618
1619
1621
1622jGetObjectArrayElement(Array, Index, Obj) :-
1623 jni_func(173, Array, Index, Obj).
1624
1625
1627
1628jGetObjectClass(Object, Class) :-
1629 jni_func(31, Object, Class).
1630
1631
1633
1634jGetObjectField(Obj, FieldID, Robj) :-
1635 jni_func(95, Obj, FieldID, Robj).
1636
1637
1639
1640jGetShortArrayRegion(Array, Start, Len, Buf) :-
1641 jni_void(202, Array, Start, Len, Buf).
1642
1643
1645
1646jGetShortField(Obj, FieldID, Rshort) :-
1647 jni_func(99, Obj, FieldID, Rshort).
1648
1649
1651
1652jGetStaticBooleanField(Class, FieldID, Rbool) :-
1653 jni_func(146, Class, FieldID, Rbool).
1654
1655
1657
1658jGetStaticByteField(Class, FieldID, Rbyte) :-
1659 jni_func(147, Class, FieldID, Rbyte).
1660
1661
1663
1664jGetStaticCharField(Class, FieldID, Rchar) :-
1665 jni_func(148, Class, FieldID, Rchar).
1666
1667
1669
1670jGetStaticDoubleField(Class, FieldID, Rdouble) :-
1671 jni_func(153, Class, FieldID, Rdouble).
1672
1673
1675
1676jGetStaticFieldID(Class, Name, Type, FieldID) :-
1677 jpl_type_to_java_field_descriptor(Type, TD), 1678 jni_func(144, Class, Name, TD, FieldID).
1679
1680
1682
1683jGetStaticFloatField(Class, FieldID, Rfloat) :-
1684 jni_func(152, Class, FieldID, Rfloat).
1685
1686
1688
1689jGetStaticIntField(Class, FieldID, Rint) :-
1690 jni_func(150, Class, FieldID, Rint).
1691
1692
1694
1695jGetStaticLongField(Class, FieldID, Rlong) :-
1696 jni_func(151, Class, FieldID, Rlong).
1697
1698
1700
1701jGetStaticMethodID(Class, Name, Type, MethodID) :-
1702 jpl_type_to_java_method_descriptor(Type, TD),
1703 jni_func(113, Class, Name, TD, MethodID).
1704
1705
1707
1708jGetStaticObjectField(Class, FieldID, Robj) :-
1709 jni_func(145, Class, FieldID, Robj).
1710
1711
1713
1714jGetStaticShortField(Class, FieldID, Rshort) :-
1715 jni_func(149, Class, FieldID, Rshort).
1716
1717
1719
1720jGetSuperclass(Class1, Class2) :-
1721 jni_func(10, Class1, Class2).
1722
1723
1725
1726jIsAssignableFrom(Class1, Class2) :-
1727 jni_func(11, Class1, Class2, @(true)).
1728
1729
1731
1732jNewBooleanArray(Length, Array) :-
1733 jni_func(175, Length, Array).
1734
1735
1737
1738jNewByteArray(Length, Array) :-
1739 jni_func(176, Length, Array).
1740
1741
1743
1744jNewCharArray(Length, Array) :-
1745 jni_func(177, Length, Array).
1746
1747
1749
1750jNewDoubleArray(Length, Array) :-
1751 jni_func(182, Length, Array).
1752
1753
1755
1756jNewFloatArray(Length, Array) :-
1757 jni_func(181, Length, Array).
1758
1759
1761
1762jNewIntArray(Length, Array) :-
1763 jni_func(179, Length, Array).
1764
1765
1767
1768jNewLongArray(Length, Array) :-
1769 jni_func(180, Length, Array).
1770
1771
1773
1774jNewObject(Class, MethodID, Types, Params, Obj) :-
1775 jni_params_put(Params, Types, ParamBuf),
1776 jni_func(30, Class, MethodID, ParamBuf, Obj).
1777
1778
1780
1781jNewObjectArray(Len, Class, InitVal, Array) :-
1782 jni_func(172, Len, Class, InitVal, Array).
1783
1784
1786
1787jNewShortArray(Length, Array) :-
1788 jni_func(178, Length, Array).
1789
1790
1792
1793jSetBooleanArrayRegion(Array, Start, Len, Buf) :-
1794 jni_void(207, Array, Start, Len, Buf).
1795
1796
1798
1799jSetBooleanField(Obj, FieldID, Rbool) :-
1800 jni_void(105, Obj, FieldID, Rbool).
1801
1802
1804
1805jSetByteArrayRegion(Array, Start, Len, Buf) :-
1806 jni_void(208, Array, Start, Len, Buf).
1807
1808
1810
1811jSetByteField(Obj, FieldID, Rbyte) :-
1812 jni_void(106, Obj, FieldID, Rbyte).
1813
1814
1816
1817jSetCharArrayRegion(Array, Start, Len, Buf) :-
1818 jni_void(209, Array, Start, Len, Buf).
1819
1820
1822
1823jSetCharField(Obj, FieldID, Rchar) :-
1824 jni_void(107, Obj, FieldID, Rchar).
1825
1826
1828
1829jSetDoubleArrayRegion(Array, Start, Len, Buf) :-
1830 jni_void(214, Array, Start, Len, Buf).
1831
1832
1834
1835jSetDoubleField(Obj, FieldID, Rdouble) :-
1836 jni_void(112, Obj, FieldID, Rdouble).
1837
1838
1840
1841jSetFloatArrayRegion(Array, Start, Len, Buf) :-
1842 jni_void(213, Array, Start, Len, Buf).
1843
1844
1846
1847jSetFloatField(Obj, FieldID, Rfloat) :-
1848 jni_void(111, Obj, FieldID, Rfloat).
1849
1850
1852
1853jSetIntArrayRegion(Array, Start, Len, Buf) :-
1854 jni_void(211, Array, Start, Len, Buf).
1855
1856
1858
1859jSetIntField(Obj, FieldID, Rint) :-
1860 jni_void(109, Obj, FieldID, Rint).
1861
1862
1864
1865jSetLongArrayRegion(Array, Start, Len, Buf) :-
1866 jni_void(212, Array, Start, Len, Buf).
1867
1868
1870
1871jSetLongField(Obj, FieldID, Rlong) :-
1872 jni_void(110, Obj, FieldID, Rlong).
1873
1874
1876
1877jSetObjectArrayElement(Array, Index, Obj) :-
1878 jni_void(174, Array, Index, Obj).
1879
1880
1882
1883jSetObjectField(Obj, FieldID, Robj) :-
1884 jni_void(104, Obj, FieldID, Robj).
1885
1886
1888
1889jSetShortArrayRegion(Array, Start, Len, Buf) :-
1890 jni_void(210, Array, Start, Len, Buf).
1891
1892
1894
1895jSetShortField(Obj, FieldID, Rshort) :-
1896 jni_void(108, Obj, FieldID, Rshort).
1897
1898
1900
1901jSetStaticBooleanField(Class, FieldID, Rbool) :-
1902 jni_void(155, Class, FieldID, Rbool).
1903
1904
1906
1907jSetStaticByteField(Class, FieldID, Rbyte) :-
1908 jni_void(156, Class, FieldID, Rbyte).
1909
1910
1912
1913jSetStaticCharField(Class, FieldID, Rchar) :-
1914 jni_void(157, Class, FieldID, Rchar).
1915
1916
1918
1919jSetStaticDoubleField(Class, FieldID, Rdouble) :-
1920 jni_void(162, Class, FieldID, Rdouble).
1921
1922
1924
1925jSetStaticFloatField(Class, FieldID, Rfloat) :-
1926 jni_void(161, Class, FieldID, Rfloat).
1927
1928
1930
1931jSetStaticIntField(Class, FieldID, Rint) :-
1932 jni_void(159, Class, FieldID, Rint).
1933
1934
1936
1937jSetStaticLongField(Class, FieldID, Rlong) :-
1938 jni_void(160, Class, FieldID, Rlong).
1939
1940
1942
1943jSetStaticObjectField(Class, FieldID, Robj) :-
1944 jni_void(154, Class, FieldID, Robj).
1945
1946
1948
1949jSetStaticShortField(Class, FieldID, Rshort) :-
1950 jni_void(158, Class, FieldID, Rshort).
1951
1952
1959
1960jni_params_put(As, Ts, ParamBuf) :-
1961 jni_ensure_jvm, 1962 length(As, N),
1963 jni_type_to_xput_code(jvalue, Xc), 1964 jni_alloc_buffer(Xc, N, ParamBuf),
1965 jni_params_put_1(As, 0, Ts, ParamBuf).
1966
1967
1983
1984jni_params_put_1([], _, [], _).
1985jni_params_put_1([A|As], N, [Tjni|Ts], ParamBuf) :- 1986 ( jni_type_to_xput_code(Tjni, Xc)
1987 -> ( A = {Term} 1988 -> jni_term_to_jref(Term, Ax) 1989 ; A = Ax
1990 ),
1991 jni_param_put(N, Xc, Ax, ParamBuf) 1992 ; fail 1993 ),
1994 N2 is N+1,
1995 jni_params_put_1(As, N2, Ts, ParamBuf). 1996
1997
2004
2005jni_type_to_xput_code(boolean, 1). 2006jni_type_to_xput_code(byte, 2). 2007jni_type_to_xput_code(char, 3). 2008jni_type_to_xput_code(short, 4). 2009jni_type_to_xput_code(int, 5). 2010jni_type_to_xput_code(long, 6). 2011jni_type_to_xput_code(float, 7). 2012jni_type_to_xput_code(double, 8). 2013jni_type_to_xput_code(class(_,_), 12). 2014jni_type_to_xput_code(array(_), 12). 2015jni_type_to_xput_code(jvalue, 15). 2016
2017
2021
2022jpl_class_to_constructor_array(Cx, Ma) :-
2023 jpl_entityname_to_class('java.lang.Class', CC), 2024 jGetMethodID( CC, getConstructors, method([],array(class([java,lang,reflect],['Constructor']))), MID), 2025 jCallObjectMethod(Cx, MID, [], [], Ma).
2026
2027
2029
2030jpl_class_to_constructors(Cx, Ms) :-
2031 jpl_class_to_constructor_array(Cx, Ma),
2032 jpl_object_array_to_list(Ma, Ms).
2033
2034
2036
2037jpl_class_to_field_array(Cx, Fa) :-
2038 jpl_entityname_to_class('java.lang.Class', CC), 2039 jGetMethodID(CC, getFields, method([],array(class([java,lang,reflect],['Field']))), MID), 2040 jCallObjectMethod(Cx, MID, [], [], Fa).
2041
2042
2046
2047jpl_class_to_fields(C, Fs) :-
2048 jpl_class_to_field_array(C, Fa),
2049 jpl_object_array_to_list(Fa, Fs).
2050
2051
2055
2056jpl_class_to_method_array(Cx, Ma) :-
2057 jpl_entityname_to_class('java.lang.Class', CC), 2058 jGetMethodID(CC, getMethods, method([],array(class([java,lang,reflect],['Method']))), MID), 2059 jCallObjectMethod(Cx, MID, [], [], Ma).
2060
2061
2067
2068jpl_class_to_methods(Cx, Ms) :-
2069 jpl_class_to_method_array(Cx, Ma),
2070 jpl_object_array_to_list(Ma, Ms).
2071
2072
2076
2077jpl_constructor_to_modifiers(X, Ms) :-
2078 jpl_entityname_to_class('java.lang.reflect.Constructor', Cx), 2079 jpl_method_to_modifiers_1(X, Cx, Ms).
2080
2081
2086
2087jpl_constructor_to_name(_X, '<init>').
2088
2089
2093
2094jpl_constructor_to_parameter_types(X, Tfps) :-
2095 jpl_entityname_to_class('java.lang.reflect.Constructor', Cx), 2096 jpl_method_to_parameter_types_1(X, Cx, Tfps).
2097
2098
2103
2104jpl_constructor_to_return_type(_X, void).
2105
2106
2110
2111jpl_field_spec(T, I, N, Mods, MID, Tf) :-
2112 ( jpl_field_spec_is_cached(T)
2113 -> jpl_field_spec_cache(T, I, N, Mods, MID, Tf)
2114 ; jpl_type_to_class(T, C),
2115 jpl_class_to_fields(C, Fs),
2116 ( T = array(_BaseType) 2117 -> Tci = array(_) 2118 ; Tci = T
2119 ),
2120 jpl_field_spec_1(C, Tci, Fs),
2121 jpl_assert(jpl_field_spec_is_cached(Tci)),
2122 jpl_field_spec_cache(Tci, I, N, Mods, MID, Tf)
2123 ).
2124
2125
2126jpl_field_spec_1(C, Tci, Fs) :-
2127 ( nth1(I, Fs, F),
2128 jpl_field_to_name(F, N),
2129 jpl_field_to_modifiers(F, Mods),
2130 jpl_field_to_type(F, Tf),
2131 ( member(static, Mods)
2132 -> jGetStaticFieldID(C, N, Tf, MID)
2133 ; jGetFieldID(C, N, Tf, MID)
2134 ),
2135 jpl_assert(jpl_field_spec_cache(Tci,I,N,Mods,MID,Tf)),
2136 fail
2137 ; true
2138 ).
2139
2140
2141
2143
2144jpl_field_to_modifiers(F, Ms) :-
2145 jpl_entityname_to_class('java.lang.reflect.Field', Cf),
2146 jpl_method_to_modifiers_1(F, Cf, Ms).
2147
2148
2150
2151jpl_field_to_name(F, N) :-
2152 jpl_entityname_to_class('java.lang.reflect.Field', Cf),
2153 jpl_member_to_name_1(F, Cf, N).
2154
2155
2157
2158jpl_field_to_type(F, Tf) :-
2159 jpl_entityname_to_class('java.lang.reflect.Field', Cf),
2160 jGetMethodID(Cf, getType, method([],class([java,lang],['Class'])), MID),
2161 jCallObjectMethod(F, MID, [], [], Cr),
2162 jpl_class_to_type(Cr, Tf).
2163
2164
2169
2170jpl_method_spec(T, I, N, A, Mods, MID, Tr, Tfps) :-
2171 ( jpl_method_spec_is_cached(T)
2172 -> jpl_method_spec_cache(T, I, N, A, Mods, MID, Tr, Tfps)
2173 ; jpl_type_to_class(T, C),
2174 jpl_class_to_constructors(C, Xs),
2175 jpl_class_to_methods(C, Ms),
2176 ( T = array(_BaseType) 2177 -> Tci = array(_) 2178 ; Tci = T
2179 ),
2180 jpl_method_spec_1(C, Tci, Xs, Ms),
2181 jpl_assert(jpl_method_spec_is_cached(Tci)),
2182 jpl_method_spec_cache(Tci, I, N, A, Mods, MID, Tr, Tfps)
2183 ).
2184
2185
2189
2190jpl_method_spec_1(C, Tci, Xs, Ms) :-
2191 ( ( nth1(I, Xs, X), 2192 jpl_constructor_to_name(X, N),
2193 jpl_constructor_to_modifiers(X, Mods),
2194 jpl_constructor_to_return_type(X, Tr),
2195 jpl_constructor_to_parameter_types(X, Tfps)
2196 ; length(Xs, J0),
2197 nth1(J, Ms, M), 2198 I is J0+J,
2199 jpl_method_to_name(M, N),
2200 jpl_method_to_modifiers(M, Mods),
2201 jpl_method_to_return_type(M, Tr),
2202 jpl_method_to_parameter_types(M, Tfps)
2203 ),
2204 length(Tfps, A), 2205 ( member(static, Mods)
2206 -> jGetStaticMethodID(C, N, method(Tfps,Tr), MID)
2207 ; jGetMethodID(C, N, method(Tfps,Tr), MID)
2208 ),
2209 jpl_assert(jpl_method_spec_cache(Tci,I,N,A,Mods,MID,Tr,Tfps)),
2210 fail
2211 ; true
2212 ).
2213
2214
2215
2217
2218jpl_method_to_modifiers(M, Ms) :-
2219 jpl_entityname_to_class('java.lang.reflect.Method', Cm),
2220 jpl_method_to_modifiers_1(M, Cm, Ms).
2221
2222
2224
2225jpl_method_to_modifiers_1(XM, Cxm, Ms) :-
2226 jGetMethodID(Cxm, getModifiers, method([],int), MID),
2227 jCallIntMethod(XM, MID, [], [], I),
2228 jpl_modifier_int_to_modifiers(I, Ms).
2229
2230
2232
2233jpl_method_to_name(M, N) :-
2234 jpl_entityname_to_class('java.lang.reflect.Method', CM),
2235 jpl_member_to_name_1(M, CM, N).
2236
2237
2239
2240jpl_member_to_name_1(M, CM, N) :-
2241 jGetMethodID(CM, getName, method([],class([java,lang],['String'])), MID),
2242 jCallObjectMethod(M, MID, [], [], N).
2243
2244
2246
2247jpl_method_to_parameter_types(M, Tfps) :-
2248 jpl_entityname_to_class('java.lang.reflect.Method', Cm),
2249 jpl_method_to_parameter_types_1(M, Cm, Tfps).
2250
2251
2255
2256jpl_method_to_parameter_types_1(XM, Cxm, Tfps) :-
2257 jGetMethodID(Cxm, getParameterTypes, method([],array(class([java,lang],['Class']))), MID),
2258 jCallObjectMethod(XM, MID, [], [], Atp),
2259 jpl_object_array_to_list(Atp, Ctps),
2260 jpl_classes_to_types(Ctps, Tfps).
2261
2262
2264
2265jpl_method_to_return_type(M, Tr) :-
2266 jpl_entityname_to_class('java.lang.reflect.Method', Cm),
2267 jGetMethodID(Cm, getReturnType, method([],class([java,lang],['Class'])), MID),
2268 jCallObjectMethod(M, MID, [], [], Cr),
2269 jpl_class_to_type(Cr, Tr).
2270
2271
2272jpl_modifier_bit(public, 0x001).
2273jpl_modifier_bit(private, 0x002).
2274jpl_modifier_bit(protected, 0x004).
2275jpl_modifier_bit(static, 0x008).
2276jpl_modifier_bit(final, 0x010).
2277jpl_modifier_bit(synchronized, 0x020).
2278jpl_modifier_bit(volatile, 0x040).
2279jpl_modifier_bit(transient, 0x080).
2280jpl_modifier_bit(native, 0x100).
2281jpl_modifier_bit(interface, 0x200).
2282jpl_modifier_bit(abstract, 0x400).
2283
2284
2290
2291jpl_modifier_int_to_modifiers(I, Ms) :-
2292 setof(
2293 M, 2294 B^( jpl_modifier_bit(M, B),
2295 (B /\ I) =\= 0
2296 ),
2297 Ms
2298 ).
2299
2300
2311
2312jpl_cache_type_of_ref(T, Ref) :-
2313 ( jpl_assert_policy(jpl_iref_type_cache(_,_), no)
2314 -> true
2315 ; \+ ground(T) 2316 -> write('[jpl_cache_type_of_ref/2: arg 1 is not ground]'), nl, 2317 fail
2318 ; Ref == @(null) 2319 -> true 2320 ; ( jpl_iref_type_cache(Ref, TC) 2321 -> ( T == TC
2322 -> true
2323 ; 2324 retractall(jpl_iref_type_cache(Ref,_)),
2325 jpl_assert(jpl_iref_type_cache(Ref,T))
2326 )
2327 ; jpl_assert(jpl_iref_type_cache(Ref,T))
2328 )
2329 ).
2330
2331
2339
2340jpl_class_to_ancestor_classes(C, Cas) :-
2341 ( jpl_class_to_super_class(C, Ca)
2342 -> Cas = [Ca|Cas2],
2343 jpl_class_to_ancestor_classes(Ca, Cas2)
2344 ; Cas = []
2345 ).
2346
2347
2363
2364jpl_class_to_classname(C, CN) :-
2365 jpl_call(C, getName, [], CN).
2366
2367
2376
2377jpl_class_to_entityname(Class, EntityName) :-
2378 jpl_entityname_to_class('java.lang.Class', CC), 2379 jGetMethodID(CC, getName, method([],class([java,lang],['String'])), MIDgetName), 2380 jCallObjectMethod(Class, MIDgetName, [], [], S),
2381 S = EntityName.
2382
2383
2384jpl_class_to_super_class(C, Cx) :-
2385 jGetSuperclass(C, Cx),
2386 Cx \== @(null), 2387 jpl_cache_type_of_ref(class([java,lang],['Class']), Cx).
2388
2389
2400
2401jpl_class_to_type(Class, Type) :-
2402 assertion(blob(Class,jref)), 2403 ( jpl_class_tag_type_cache(Class, Tx) 2404 -> true
2405 ; jpl_class_to_entityname(Class, EN), 2406 jpl_entityname_to_type(EN, Tr),
2407 jpl_type_to_canonical_type(Tr, Tx), 2408 jpl_assert(jpl_class_tag_type_cache(Class,Tx))
2409 -> true 2410 ),
2411 Type = Tx.
2412
2413
2414jpl_classes_to_types([], []).
2415jpl_classes_to_types([C|Cs], [T|Ts]) :-
2416 jpl_class_to_type(C, T),
2417 jpl_classes_to_types(Cs, Ts).
2418
2419
2427
2428jpl_entityname_to_class(EntityName, Class) :-
2429 jpl_entityname_to_type(EntityName, T), 2430 jpl_type_to_class(T, Class). 2431
2439
2440jpl_classname_to_class(EntityName, Class) :-
2441 jpl_entityname_to_class(EntityName, Class). 2442
2446
2479
2480jpl_entityname_to_type(EntityName, Type) :-
2481 assertion(atomic(EntityName)),
2482 (jpl_classname_type_cache(EntityName, Tx)
2483 -> (Tx = Type)
2484 ; jpl_entityname_to_type_with_caching(EntityName, Type)).
2485
2486jpl_entityname_to_type_with_caching(EN, T) :-
2487 (atom_codes(EN,Cs),phrase(jpl_entityname(T), Cs))
2488 -> jpl_assert(jpl_classname_type_cache(EN,T)).
2489
2493
2494jpl_type_to_entityname(Type, EntityName) :-
2495 assertion(ground(Type)),
2496 phrase(jpl_entityname(Type), Cs),
2497 atom_codes(EntityName, Cs).
2498
2507
2508jpl_classname_to_type(EntityName, Type) :-
2509 jpl_entityname_to_type(EntityName, Type).
2510
2519
2522
2523jpl_type_to_classname(Type, EntityName) :-
2524 jpl_type_to_entityname(Type, EntityName).
2525
2527
2528
2540
2541jpl_datum_to_type(D, T) :-
2542 ( jpl_value_to_type(D, T)
2543 -> true
2544 ; jpl_ref_to_type(D, T)
2545 -> true
2546 ; nonvar(D),
2547 D = {Term}
2548 -> ( cyclic_term(Term)
2549 -> throwme(jpl_datum_to_type,is_cyclic(Term))
2550 ; atom(Term)
2551 -> T = class([org,jpl7],['Atom'])
2552 ; integer(Term)
2553 -> T = class([org,jpl7],['Integer'])
2554 ; float(Term)
2555 -> T = class([org,jpl7],['Float'])
2556 ; var(Term)
2557 -> T = class([org,jpl7],['Variable'])
2558 ; T = class([org,jpl7],['Compound'])
2559 )
2560 ).
2561
2562
2563jpl_datums_to_most_specific_common_ancestor_type([D], T) :-
2564 jpl_datum_to_type(D, T).
2565jpl_datums_to_most_specific_common_ancestor_type([D1,D2|Ds], T0) :-
2566 jpl_datum_to_type(D1, T1),
2567 jpl_type_to_ancestor_types(T1, Ts1),
2568 jpl_datums_to_most_specific_common_ancestor_type_1([D2|Ds], [T1|Ts1], [T0|_]).
2569
2570
2571jpl_datums_to_most_specific_common_ancestor_type_1([], Ts, Ts).
2572jpl_datums_to_most_specific_common_ancestor_type_1([D|Ds], Ts1, Ts0) :-
2573 jpl_datum_to_type(D, Tx),
2574 jpl_lineage_types_type_to_common_lineage_types(Ts1, Tx, Ts2),
2575 jpl_datums_to_most_specific_common_ancestor_type_1(Ds, Ts2, Ts0).
2576
2577
2585
2586jpl_datums_to_types([], []).
2587jpl_datums_to_types([D|Ds], [T|Ts]) :-
2588 jpl_datum_to_type(D, T),
2589 jpl_datums_to_types(Ds, Ts).
2590
2591
2598
2599jpl_ground_is_type(X) :-
2600 jpl_primitive_type(X),
2601 !.
2602jpl_ground_is_type(array(X)) :-
2603 jpl_ground_is_type(X).
2604jpl_ground_is_type(class(_,_)). 2605jpl_ground_is_type(method(_,_)). 2606
2607
2608
2609
2610jpl_lineage_types_type_to_common_lineage_types(Ts, Tx, Ts0) :-
2611 ( append(_, [Tx|Ts2], Ts)
2612 -> [Tx|Ts2] = Ts0
2613 ; jpl_type_to_super_type(Tx, Tx2)
2614 -> jpl_lineage_types_type_to_common_lineage_types(Ts, Tx2, Ts0)
2615 ).
2616
2617
2618jpl_non_var_is_object_type(class(_,_)).
2619
2620jpl_non_var_is_object_type(array(_)).
2621
2622
2627
2628jpl_object_array_to_list(A, Vs) :-
2629 jpl_array_to_length(A, N),
2630 jpl_object_array_to_list_1(A, 0, N, Vs).
2631
2632
2634
2635jpl_object_array_to_list_1(A, I, N, Xs) :-
2636 ( I == N
2637 -> Xs = []
2638 ; jGetObjectArrayElement(A, I, X),
2639 Xs = [X|Xs2],
2640 J is I+1,
2641 jpl_object_array_to_list_1(A, J, N, Xs2)
2642 ).
2643
2644
2653
2654jpl_object_to_class(Obj, C) :-
2655 jpl_is_object(Obj),
2656 jGetObjectClass(Obj, C),
2657 jpl_cache_type_of_ref(class([java,lang],['Class']), C).
2658
2659
2666
2667jpl_object_to_type(Ref, Type) :-
2668 jpl_is_object(Ref),
2669 ( jpl_iref_type_cache(Ref, T)
2670 -> true 2671 ; jpl_object_to_class(Ref, Cobj), 2672 jpl_class_to_type(Cobj, T), 2673 jpl_assert(jpl_iref_type_cache(Ref,T))
2674 ),
2675 Type = T.
2676
2677
2678jpl_object_type_to_super_type(T, Tx) :-
2679 ( ( T = class(_,_)
2680 ; T = array(_)
2681 )
2682 -> jpl_type_to_class(T, C),
2683 jpl_class_to_super_class(C, Cx),
2684 Cx \== @(null),
2685 jpl_class_to_type(Cx, Tx)
2686 ).
2687
2688
2696
2697jpl_primitive_buffer_to_array(T, Xc, Bp, I, Size, [Vc|Vcs]) :-
2698 jni_fetch_buffer_value(Bp, I, Vc, Xc),
2699 Ix is I+1,
2700 ( Ix < Size
2701 -> jpl_primitive_buffer_to_array(T, Xc, Bp, Ix, Size, Vcs)
2702 ; Vcs = []
2703 ).
2704
2705
2715
2716jpl_primitive_type(boolean).
2717jpl_primitive_type(char).
2718jpl_primitive_type(byte).
2719jpl_primitive_type(short).
2720jpl_primitive_type(int). 2721jpl_primitive_type(long).
2722jpl_primitive_type(float).
2723jpl_primitive_type(double).
2724
2725
2731
2732jpl_primitive_type_default_value(boolean, @(false)).
2733jpl_primitive_type_default_value(char, 0).
2734jpl_primitive_type_default_value(byte, 0).
2735jpl_primitive_type_default_value(short, 0).
2736jpl_primitive_type_default_value(int, 0).
2737jpl_primitive_type_default_value(long, 0).
2738jpl_primitive_type_default_value(float, 0.0).
2739jpl_primitive_type_default_value(double, 0.0).
2740
2741
2742jpl_primitive_type_super_type(T, Tx) :-
2743 ( jpl_type_fits_type_direct_prim(T, Tx)
2744 ; jpl_type_fits_type_direct_xtra(T, Tx)
2745 ).
2746
2747
2757
2758jpl_primitive_type_term_to_value(Type, Term, Val) :-
2759 once(jpl_primitive_type_term_to_value_1(Type, Term, Val)). 2760
2766
2767jpl_primitive_type_term_to_value_1(boolean, @(false), @(false)).
2768jpl_primitive_type_term_to_value_1(boolean, @(true), @(true)).
2769jpl_primitive_type_term_to_value_1(char, I, I) :-
2770 integer(I),
2771 I >= 0,
2772 I =< 65535. 2773jpl_primitive_type_term_to_value_1(byte, I, I) :-
2774 integer(I),
2775 I >= 128, 2776 I =< 127. 2777jpl_primitive_type_term_to_value_1(short, I, I) :-
2778 integer(I),
2779 I >= -32768, 2780 I =< 32767. 2781jpl_primitive_type_term_to_value_1(int, I, I) :-
2782 integer(I),
2783 I >= -2147483648, 2784 I =< 2147483647. 2785jpl_primitive_type_term_to_value_1(long, I, I) :-
2786 integer(I),
2787 I >= -9223372036854775808, 2788 I =< 9223372036854775807. 2789jpl_primitive_type_term_to_value_1(float, V, F) :-
2790 ( integer(V)
2791 -> F is float(V)
2792 ; float(V)
2793 -> F = V
2794 ).
2795jpl_primitive_type_term_to_value_1(double, V, F) :-
2796 ( integer(V)
2797 -> F is float(V)
2798 ; float(V)
2799 -> F = V
2800 ).
2801
2802
2803jpl_primitive_type_to_ancestor_types(T, Ts) :-
2804 ( jpl_primitive_type_super_type(T, Ta)
2805 -> Ts = [Ta|Tas],
2806 jpl_primitive_type_to_ancestor_types(Ta, Tas)
2807 ; Ts = []
2808 ).
2809
2810
2811jpl_primitive_type_to_super_type(T, Tx) :-
2812 jpl_primitive_type_super_type(T, Tx).
2813
2814
2820
2821jpl_ref_to_type(Ref, T) :-
2822 ( Ref == @(null)
2823 -> T = null
2824 ; Ref == @(void)
2825 -> T = void
2826 ; jpl_object_to_type(Ref, T)
2827 ).
2828
2829
2836
2837jpl_tag_to_type(Tag, Type) :-
2838 jni_tag_to_iref(Tag, Iref),
2839 ( jpl_iref_type_cache(Iref, T)
2840 -> true 2841 ; jpl_object_to_class(@(Tag), Cobj), 2842 jpl_class_to_type(Cobj, T), 2843 jpl_assert(jpl_iref_type_cache(Iref,T))
2844 ),
2845 Type = T.
2846
2847
2853
2854jpl_type_fits_type(Tx, Ty) :-
2855 once(jpl_type_fits_type_1(Tx, Ty)). 2856
2857
2861
2862jpl_type_fits_type_1(T, T).
2863jpl_type_fits_type_1(class(Ps1,Cs1), class(Ps2,Cs2)) :-
2864 jpl_type_to_class(class(Ps1,Cs1), C1),
2865 jpl_type_to_class(class(Ps2,Cs2), C2),
2866 jIsAssignableFrom(C1, C2).
2867jpl_type_fits_type_1(array(T1), class(Ps2,Cs2)) :-
2868 jpl_type_to_class(array(T1), C1),
2869 jpl_type_to_class(class(Ps2,Cs2), C2),
2870 jIsAssignableFrom(C1, C2).
2871jpl_type_fits_type_1(array(T1), array(T2)) :-
2872 jpl_type_to_class(array(T1), C1),
2873 jpl_type_to_class(array(T2), C2),
2874 jIsAssignableFrom(C1, C2).
2875jpl_type_fits_type_1(null, class(_,_)).
2876jpl_type_fits_type_1(null, array(_)).
2877jpl_type_fits_type_1(T1, T2) :-
2878 jpl_type_fits_type_xprim(T1, T2).
2879
2880
2881jpl_type_fits_type_direct_prim(float, double).
2882jpl_type_fits_type_direct_prim(long, float).
2883jpl_type_fits_type_direct_prim(int, long).
2884jpl_type_fits_type_direct_prim(char, int).
2885jpl_type_fits_type_direct_prim(short, int).
2886jpl_type_fits_type_direct_prim(byte, short).
2887
2888
2889jpl_type_fits_type_direct_xprim(Tp, Tq) :-
2890 jpl_type_fits_type_direct_prim(Tp, Tq).
2891jpl_type_fits_type_direct_xprim(Tp, Tq) :-
2892 jpl_type_fits_type_direct_xtra(Tp, Tq).
2893
2894
2899
2900jpl_type_fits_type_direct_xtra(char_int, int). 2901jpl_type_fits_type_direct_xtra(char_int, char). 2902jpl_type_fits_type_direct_xtra(char_short, short).
2903jpl_type_fits_type_direct_xtra(char_short, char).
2904jpl_type_fits_type_direct_xtra(char_byte, byte).
2905jpl_type_fits_type_direct_xtra(char_byte, char).
2906jpl_type_fits_type_direct_xtra(overlong, float). 2907
2908
2912
2913jpl_type_fits_type_xprim(Tp, T) :-
2914 jpl_type_fits_type_direct_xprim(Tp, Tq),
2915 ( Tq = T
2916 ; jpl_type_fits_type_xprim(Tq, T)
2917 ).
2918
2919
2924
2925jpl_type_to_ancestor_types(T, Tas) :-
2926 ( ( T = class(_,_)
2927 ; T = array(_)
2928 )
2929 -> jpl_type_to_class(T, C),
2930 jpl_class_to_ancestor_classes(C, Cas),
2931 jpl_classes_to_types(Cas, Tas)
2932 ; jpl_primitive_type_to_ancestor_types(T, Tas)
2933 -> true
2934 ).
2935
2936
2948
2949jpl_type_to_canonical_type(array(T), array(Tc)) :-
2950 !,
2951 jpl_type_to_canonical_type(T, Tc).
2952jpl_type_to_canonical_type(class([],[void]), void) :-
2953 !.
2954jpl_type_to_canonical_type(class([],[N]), N) :-
2955 jpl_primitive_type(N),
2956 !.
2957jpl_type_to_canonical_type(class(Ps,Cs), class(Ps,Cs)) :-
2958 !.
2959jpl_type_to_canonical_type(void, void) :-
2960 !.
2961jpl_type_to_canonical_type(P, P) :-
2962 jpl_primitive_type(P).
2963
2964
2972
2973jpl_type_to_class(Type, Class) :-
2974 (ground(Type)
2975 -> true
2976 ; throwme(jpl_type_to_class,arg1_is_var)), 2977 (jpl_class_tag_type_cache(RefB, Type)
2978 -> true
2979 ; ( jpl_type_to_java_findclass_descriptor(Type, FCN)
2980 -> jFindClass(FCN, RefB), 2981 jpl_cache_type_of_ref(class([java,lang],['Class']), RefB) 2982 ),
2983 jpl_assert(jpl_class_tag_type_cache(RefB,Type))
2984 ),
2985 Class = RefB.
2986
2987
2994
2995jpl_type_to_java_field_descriptor(T, FD) :-
2996 2997 phrase(jpl_field_descriptor(T,slashy), Cs), 2998 atom_codes(FD, Cs).
2999
3006
3007jpl_type_to_java_method_descriptor(T, MD) :-
3008 3009 phrase(jpl_method_descriptor(T), Cs),
3010 atom_codes(MD, Cs).
3011
3016
3017jpl_type_to_java_findclass_descriptor(T, FCD) :-
3018 3019 phrase(jpl_findclass_descriptor(T), Cs),
3020 atom_codes(FCD, Cs).
3021
3029
3030jpl_type_to_super_type(T, Tx) :-
3031 ( jpl_object_type_to_super_type(T, Tx)
3032 -> true
3033 ; jpl_primitive_type_to_super_type(T, Tx)
3034 -> true
3035 ).
3036
3037
3053
3054jpl_type_to_preferred_concrete_type(T, Tc) :-
3055 ( jpl_type_to_preferred_concrete_type_1(T, TcX)
3056 -> Tc = TcX
3057 ).
3058
3059
3060jpl_type_to_preferred_concrete_type_1(char_int, int).
3061jpl_type_to_preferred_concrete_type_1(char_short, short).
3062jpl_type_to_preferred_concrete_type_1(char_byte, byte).
3063jpl_type_to_preferred_concrete_type_1(array(T), array(Tc)) :-
3064 jpl_type_to_preferred_concrete_type_1(T, Tc).
3065jpl_type_to_preferred_concrete_type_1(T, T).
3066
3067
3073
3074jpl_types_fit_type([], _).
3075jpl_types_fit_type([T1|T1s], T2) :-
3076 jpl_type_fits_type(T1, T2),
3077 jpl_types_fit_type(T1s, T2).
3078
3079
3083
3084jpl_types_fit_types([], []).
3085jpl_types_fit_types([T1|T1s], [T2|T2s]) :-
3086 jpl_type_fits_type(T1, T2),
3087 jpl_types_fit_types(T1s, T2s).
3088
3089
3097
3098jpl_value_to_type(V, T) :-
3099 ground(V), 3100 ( jpl_value_to_type_1(V, Tv) 3101 -> T = Tv
3102 ).
3103
3104
3118
3119jpl_value_to_type_1(@(false), boolean) :- !.
3120jpl_value_to_type_1(@(true), boolean) :- !.
3121jpl_value_to_type_1(A, class([java,lang],['String'])) :- 3122 atom(A),
3123 !.
3124jpl_value_to_type_1(I, T) :-
3125 integer(I),
3126 !,
3127 ( I >= 0
3128 -> ( I < 128 -> T = char_byte
3129 ; I < 32768 -> T = char_short
3130 ; I < 65536 -> T = char_int
3131 ; I < 2147483648 -> T = int
3132 ; I =< 9223372036854775807 -> T = long
3133 ; T = overlong
3134 )
3135 ; I >= -128 -> T = byte
3136 ; I >= -32768 -> T = short
3137 ; I >= -2147483648 -> T = int
3138 ; I >= -9223372036854775808 -> T = long
3139 ; T = overlong
3140 ).
3141jpl_value_to_type_1(F, float) :-
3142 float(F).
3143
3144
3148
3149jpl_is_class(X) :-
3150 jpl_is_object(X),
3151 jpl_object_to_type(X, class([java,lang],['Class'])).
3152
3153
3157
3158jpl_is_false(X) :-
3159 X == @(false).
3160
3161
3171
3172jpl_is_fieldID(jfieldID(X)) :-
3173 integer(X).
3174
3175
3185
3186jpl_is_methodID(jmethodID(X)) :- 3187 integer(X).
3188
3189
3193
3194jpl_is_null(X) :-
3195 X == @(null).
3196
3197
3203
3204jpl_is_object(X) :-
3205 blob(X, jref).
3206
3207
3211
3212jpl_is_object_type(T) :-
3213 \+ var(T),
3214 jpl_non_var_is_object_type(T).
3215
3216
3222
3223jpl_is_ref(Term) :-
3224 ( jpl_is_object(Term)
3225 -> true
3226 ; jpl_is_null(Term)
3227 -> true
3228 ).
3229
3230
3235
3236jpl_is_true(X) :-
3237 X == @(true).
3238
3242
3243jpl_is_type(X) :-
3244 ground(X),
3245 jpl_ground_is_type(X).
3246
3255
3256jpl_is_void(X) :-
3257 X == @(void).
3258
3265
3266jpl_false(@(false)).
3267
3273
3274jpl_null(@(null)).
3275
3282
3283jpl_true(@(true)).
3284
3285
3292
3293jpl_void(@(void)).
3294
3295
3309
3310jpl_array_to_length(A, N) :-
3311 ( jpl_ref_to_type(A, array(_)) 3312 -> jGetArrayLength(A, N) 3313 ).
3314
3315
3334
3335jpl_array_to_list(A, Es) :-
3336 jpl_array_to_length(A, Len),
3337 ( Len > 0
3338 -> LoBound is 0,
3339 HiBound is Len-1,
3340 jpl_get(A, LoBound-HiBound, Es)
3341 ; Es = []
3342 ).
3343
3344
3356
3357jpl_datums_to_array(Ds, A) :-
3358 ground(Ds),
3359 jpl_datums_to_most_specific_common_ancestor_type(Ds, T), 3360 jpl_type_to_preferred_concrete_type(T, Tc), 3361 jpl_new(array(Tc), Ds, A).
3362
3363
3371
3372jpl_enumeration_element(En, E) :-
3373 ( jpl_call(En, hasMoreElements, [], @(true))
3374 -> jpl_call(En, nextElement, [], Ex),
3375 ( E = Ex
3376 ; jpl_enumeration_element(En, E)
3377 )
3378 ).
3379
3380
3398
3399jpl_enumeration_to_list(Enumeration, Es) :-
3400 ( jpl_call(Enumeration, hasMoreElements, [], @(true))
3401 -> jpl_call(Enumeration, nextElement, [], E),
3402 Es = [E|Es1],
3403 jpl_enumeration_to_list(Enumeration, Es1)
3404 ; Es = []
3405 ).
3406
3407
3416
3417jpl_hashtable_pair(HT, K-V) :-
3418 jpl_call(HT, keys, [], Ek),
3419 jpl_enumeration_to_list(Ek, Ks),
3420 member(K, Ks),
3421 jpl_call(HT, get, [K], V).
3422
3423
3440
3441jpl_iterator_element(I, E) :-
3442 ( jpl_call(I, hasNext, [], @(true))
3443 -> ( jpl_call(I, next, [], E)
3444 ; jpl_iterator_element(I, E)
3445 )
3446 ).
3447
3448
3458
3459jpl_list_to_array(Ds, A) :-
3460 jpl_datums_to_array(Ds, A).
3461
3462
3469
3470jpl_terms_to_array(Ts, A) :-
3471 jpl_terms_to_array_1(Ts, Ts2),
3472 jpl_new(array(class([org,jpl7],['Term'])), Ts2, A).
3473
3474
3475jpl_terms_to_array_1([], []).
3476jpl_terms_to_array_1([T|Ts], [{T}|Ts2]) :-
3477 jpl_terms_to_array_1(Ts, Ts2).
3478
3479
3485
3486jpl_array_to_terms(JRef, Terms) :-
3487 jpl_call('org.jpl7.Util', termArrayToList, [JRef], {Terms}).
3488
3489
3515
3516jpl_map_element(Map, K-V) :-
3517 jpl_call(Map, entrySet, [], ES),
3518 jpl_set_element(ES, E),
3519 jpl_call(E, getKey, [], K),
3520 jpl_call(E, getValue, [], V).
3521
3522
3536
3537jpl_set_element(S, E) :-
3538 jpl_call(S, iterator, [], I),
3539 jpl_iterator_element(I, E).
3540
3541
3550
3551jpl_servlet_byref(Config, Request, Response) :-
3552 jpl_call(Config, getServletContext, [], Context),
3553 jpl_call(Response, setStatus, [200], _),
3554 jpl_call(Response, setContentType, ['text/html'], _),
3555 jpl_call(Response, getWriter, [], W),
3556 jpl_call(W, println, ['<html><head></head><body><h2>jpl_servlet_byref/3 says:</h2><pre>'], _),
3557 jpl_call(W, println, ['\nservlet context stuff:'], _),
3558 jpl_call(Context, getInitParameterNames, [], ContextInitParameterNameEnum),
3559 jpl_enumeration_to_list(ContextInitParameterNameEnum, ContextInitParameterNames),
3560 length(ContextInitParameterNames, NContextInitParameterNames),
3561 atomic_list_concat(['\tContext.InitParameters = ',NContextInitParameterNames], NContextInitParameterNamesMsg),
3562 jpl_call(W, println, [NContextInitParameterNamesMsg], _),
3563 ( member(ContextInitParameterName, ContextInitParameterNames),
3564 jpl_call(Context, getInitParameter, [ContextInitParameterName], ContextInitParameter),
3565 atomic_list_concat(['\t\tContext.InitParameter[',ContextInitParameterName,'] = ',ContextInitParameter], ContextInitParameterMsg),
3566 jpl_call(W, println, [ContextInitParameterMsg], _),
3567 fail
3568 ; true
3569 ),
3570 jpl_call(Context, getMajorVersion, [], MajorVersion),
3571 atomic_list_concat(['\tContext.MajorVersion = ',MajorVersion], MajorVersionMsg),
3572 jpl_call(W, println, [MajorVersionMsg], _),
3573 jpl_call(Context, getMinorVersion, [], MinorVersion),
3574 atomic_list_concat(['\tContext.MinorVersion = ',MinorVersion], MinorVersionMsg),
3575 jpl_call(W, println, [MinorVersionMsg], _),
3576 jpl_call(Context, getServerInfo, [], ServerInfo),
3577 atomic_list_concat(['\tContext.ServerInfo = ',ServerInfo], ServerInfoMsg),
3578 jpl_call(W, println, [ServerInfoMsg], _),
3579 jpl_call(W, println, ['\nservlet config stuff:'], _),
3580 jpl_call(Config, getServletName, [], ServletName),
3581 ( ServletName == @(null)
3582 -> ServletNameAtom = null
3583 ; ServletNameAtom = ServletName
3584 ),
3585 atomic_list_concat(['\tConfig.ServletName = ',ServletNameAtom], ServletNameMsg),
3586 jpl_call(W, println, [ServletNameMsg], _),
3587 jpl_call(Config, getInitParameterNames, [], ConfigInitParameterNameEnum),
3588 jpl_enumeration_to_list(ConfigInitParameterNameEnum, ConfigInitParameterNames),
3589 length(ConfigInitParameterNames, NConfigInitParameterNames),
3590 atomic_list_concat(['\tConfig.InitParameters = ',NConfigInitParameterNames], NConfigInitParameterNamesMsg),
3591 jpl_call(W, println, [NConfigInitParameterNamesMsg], _),
3592 ( member(ConfigInitParameterName, ConfigInitParameterNames),
3593 jpl_call(Config, getInitParameter, [ConfigInitParameterName], ConfigInitParameter),
3594 atomic_list_concat(['\t\tConfig.InitParameter[',ConfigInitParameterName,'] = ',ConfigInitParameter], ConfigInitParameterMsg),
3595 jpl_call(W, println, [ConfigInitParameterMsg], _),
3596 fail
3597 ; true
3598 ),
3599 jpl_call(W, println, ['\nrequest stuff:'], _),
3600 jpl_call(Request, getAttributeNames, [], AttributeNameEnum),
3601 jpl_enumeration_to_list(AttributeNameEnum, AttributeNames),
3602 length(AttributeNames, NAttributeNames),
3603 atomic_list_concat(['\tRequest.Attributes = ',NAttributeNames], NAttributeNamesMsg),
3604 jpl_call(W, println, [NAttributeNamesMsg], _),
3605 ( member(AttributeName, AttributeNames),
3606 jpl_call(Request, getAttribute, [AttributeName], Attribute),
3607 jpl_call(Attribute, toString, [], AttributeString),
3608 atomic_list_concat(['\t\tRequest.Attribute[',AttributeName,'] = ',AttributeString], AttributeMsg),
3609 jpl_call(W, println, [AttributeMsg], _),
3610 fail
3611 ; true
3612 ),
3613 jpl_call(Request, getCharacterEncoding, [], CharacterEncoding),
3614 ( CharacterEncoding == @(null)
3615 -> CharacterEncodingAtom = ''
3616 ; CharacterEncodingAtom = CharacterEncoding
3617 ),
3618 atomic_list_concat(['\tRequest.CharacterEncoding',' = ',CharacterEncodingAtom], CharacterEncodingMsg),
3619 jpl_call(W, println, [CharacterEncodingMsg], _),
3620 jpl_call(Request, getContentLength, [], ContentLength),
3621 atomic_list_concat(['\tRequest.ContentLength',' = ',ContentLength], ContentLengthMsg),
3622 jpl_call(W, println, [ContentLengthMsg], _),
3623 jpl_call(Request, getContentType, [], ContentType),
3624 ( ContentType == @(null)
3625 -> ContentTypeAtom = ''
3626 ; ContentTypeAtom = ContentType
3627 ),
3628 atomic_list_concat(['\tRequest.ContentType',' = ',ContentTypeAtom], ContentTypeMsg),
3629 jpl_call(W, println, [ContentTypeMsg], _),
3630 jpl_call(Request, getParameterNames, [], ParameterNameEnum),
3631 jpl_enumeration_to_list(ParameterNameEnum, ParameterNames),
3632 length(ParameterNames, NParameterNames),
3633 atomic_list_concat(['\tRequest.Parameters = ',NParameterNames], NParameterNamesMsg),
3634 jpl_call(W, println, [NParameterNamesMsg], _),
3635 ( member(ParameterName, ParameterNames),
3636 jpl_call(Request, getParameter, [ParameterName], Parameter),
3637 atomic_list_concat(['\t\tRequest.Parameter[',ParameterName,'] = ',Parameter], ParameterMsg),
3638 jpl_call(W, println, [ParameterMsg], _),
3639 fail
3640 ; true
3641 ),
3642 jpl_call(Request, getProtocol, [], Protocol),
3643 atomic_list_concat(['\tRequest.Protocol',' = ',Protocol], ProtocolMsg),
3644 jpl_call(W, println, [ProtocolMsg], _),
3645 jpl_call(Request, getRemoteAddr, [], RemoteAddr),
3646 atomic_list_concat(['\tRequest.RemoteAddr',' = ',RemoteAddr], RemoteAddrMsg),
3647 jpl_call(W, println, [RemoteAddrMsg], _),
3648 jpl_call(Request, getRemoteHost, [], RemoteHost),
3649 atomic_list_concat(['\tRequest.RemoteHost',' = ',RemoteHost], RemoteHostMsg),
3650 jpl_call(W, println, [RemoteHostMsg], _),
3651 jpl_call(Request, getScheme, [], Scheme),
3652 atomic_list_concat(['\tRequest.Scheme',' = ',Scheme], SchemeMsg),
3653 jpl_call(W, println, [SchemeMsg], _),
3654 jpl_call(Request, getServerName, [], ServerName),
3655 atomic_list_concat(['\tRequest.ServerName',' = ',ServerName], ServerNameMsg),
3656 jpl_call(W, println, [ServerNameMsg], _),
3657 jpl_call(Request, getServerPort, [], ServerPort),
3658 atomic_list_concat(['\tRequest.ServerPort',' = ',ServerPort], ServerPortMsg),
3659 jpl_call(W, println, [ServerPortMsg], _),
3660 jpl_call(Request, isSecure, [], @(Secure)),
3661 atomic_list_concat(['\tRequest.Secure',' = ',Secure], SecureMsg),
3662 jpl_call(W, println, [SecureMsg], _),
3663 jpl_call(W, println, ['\nHTTP request stuff:'], _),
3664 jpl_call(Request, getAuthType, [], AuthType),
3665 ( AuthType == @(null)
3666 -> AuthTypeAtom = ''
3667 ; AuthTypeAtom = AuthType
3668 ),
3669 atomic_list_concat(['\tRequest.AuthType',' = ',AuthTypeAtom], AuthTypeMsg),
3670 jpl_call(W, println, [AuthTypeMsg], _),
3671 jpl_call(Request, getContextPath, [], ContextPath),
3672 ( ContextPath == @(null)
3673 -> ContextPathAtom = ''
3674 ; ContextPathAtom = ContextPath
3675 ),
3676 atomic_list_concat(['\tRequest.ContextPath',' = ',ContextPathAtom], ContextPathMsg),
3677 jpl_call(W, println, [ContextPathMsg], _),
3678 jpl_call(Request, getCookies, [], CookieArray),
3679 ( CookieArray == @(null)
3680 -> Cookies = []
3681 ; jpl_array_to_list(CookieArray, Cookies)
3682 ),
3683 length(Cookies, NCookies),
3684 atomic_list_concat(['\tRequest.Cookies',' = ',NCookies], NCookiesMsg),
3685 jpl_call(W, println, [NCookiesMsg], _),
3686 ( nth0(NCookie, Cookies, Cookie),
3687 atomic_list_concat(['\t\tRequest.Cookie[',NCookie,']'], CookieMsg),
3688 jpl_call(W, println, [CookieMsg], _),
3689 jpl_call(Cookie, getName, [], CookieName),
3690 atomic_list_concat(['\t\t\tRequest.Cookie.Name = ',CookieName], CookieNameMsg),
3691 jpl_call(W, println, [CookieNameMsg], _),
3692 jpl_call(Cookie, getValue, [], CookieValue),
3693 atomic_list_concat(['\t\t\tRequest.Cookie.Value = ',CookieValue], CookieValueMsg),
3694 jpl_call(W, println, [CookieValueMsg], _),
3695 jpl_call(Cookie, getPath, [], CookiePath),
3696 ( CookiePath == @(null)
3697 -> CookiePathAtom = ''
3698 ; CookiePathAtom = CookiePath
3699 ),
3700 atomic_list_concat(['\t\t\tRequest.Cookie.Path = ',CookiePathAtom], CookiePathMsg),
3701 jpl_call(W, println, [CookiePathMsg], _),
3702 jpl_call(Cookie, getComment, [], CookieComment),
3703 ( CookieComment == @(null)
3704 -> CookieCommentAtom = ''
3705 ; CookieCommentAtom = CookieComment
3706 ),
3707 atomic_list_concat(['\t\t\tRequest.Cookie.Comment = ',CookieCommentAtom], CookieCommentMsg),
3708 jpl_call(W, println, [CookieCommentMsg], _),
3709 jpl_call(Cookie, getDomain, [], CookieDomain),
3710 ( CookieDomain == @(null)
3711 -> CookieDomainAtom = ''
3712 ; CookieDomainAtom = CookieDomain
3713 ),
3714 atomic_list_concat(['\t\t\tRequest.Cookie.Domain = ',CookieDomainAtom], CookieDomainMsg),
3715 jpl_call(W, println, [CookieDomainMsg], _),
3716 jpl_call(Cookie, getMaxAge, [], CookieMaxAge),
3717 atomic_list_concat(['\t\t\tRequest.Cookie.MaxAge = ',CookieMaxAge], CookieMaxAgeMsg),
3718 jpl_call(W, println, [CookieMaxAgeMsg], _),
3719 jpl_call(Cookie, getVersion, [], CookieVersion),
3720 atomic_list_concat(['\t\t\tRequest.Cookie.Version = ',CookieVersion], CookieVersionMsg),
3721 jpl_call(W, println, [CookieVersionMsg], _),
3722 jpl_call(Cookie, getSecure, [], @(CookieSecure)),
3723 atomic_list_concat(['\t\t\tRequest.Cookie.Secure',' = ',CookieSecure], CookieSecureMsg),
3724 jpl_call(W, println, [CookieSecureMsg], _),
3725 fail
3726 ; true
3727 ),
3728 jpl_call(W, println, ['</pre></body></html>'], _),
3729 true.
3730
3731
3738
3739jpl_servlet_byval(MM, CT, Ba) :-
3740 CT = 'text/html',
3741 multimap_to_atom(MM, MMa),
3742 atomic_list_concat(['<html><head></head><body>','<h2>jpl_servlet_byval/3 says:</h2><pre>', MMa,'</pre></body></html>'], Ba).
3743
3744
3748
3749is_pair(Key-_Val) :-
3750 ground(Key).
3751
3752
3753is_pairs(List) :-
3754 is_list(List),
3755 maplist(is_pair, List).
3756
3757
3758multimap_to_atom(KVs, A) :-
3759 multimap_to_atom_1(KVs, '', Cz, []),
3760 flatten(Cz, Cs),
3761 atomic_list_concat(Cs, A).
3762
3763
3764multimap_to_atom_1([], _, Cs, Cs).
3765multimap_to_atom_1([K-V|KVs], T, Cs1, Cs0) :-
3766 Cs1 = [T,K,' = '|Cs2],
3767 ( is_list(V)
3768 -> ( is_pairs(V)
3769 -> V = V2
3770 ; findall(N-Ve, nth1(N, V, Ve), V2)
3771 ),
3772 T2 = [' ',T],
3773 Cs2 = ['\n'|Cs2a],
3774 multimap_to_atom_1(V2, T2, Cs2a, Cs3)
3775 ; to_atom(V, AV),
3776 Cs2 = [AV,'\n'|Cs3]
3777 ),
3778 multimap_to_atom_1(KVs, T, Cs3, Cs0).
3779
3780
3786
3787to_atom(Term, Atom) :-
3788 ( atom(Term)
3789 -> Atom = Term 3790 ; term_to_atom(Term, Atom)
3791 ).
3792
3797
3798jpl_pl_syntax(Syntax) :-
3799 ( [] == '[]'
3800 -> Syntax = traditional
3801 ; Syntax = modern
3802 ).
3803
3804 3807
3808:- multifile
3809 prolog:error_message/3. 3810
3811prolog:error_message(java_exception(Ex)) -->
3812 ( { jpl_call(Ex, toString, [], Msg)
3813 }
3814 -> [ 'Java exception: ~w'-[Msg] ]
3815 ; [ 'Java exception: ~w'-[Ex] ]
3816 ).
3817
3818
3819 3822
3823:- multifile user:file_search_path/2. 3824:- dynamic user:file_search_path/2. 3825
3826user:file_search_path(jar, swi(lib)).
3827
3828classpath(DirOrJar) :-
3829 getenv('CLASSPATH', ClassPath),
3830 current_prolog_flag(path_sep, Sep),
3831 atomic_list_concat(Elems, Sep, ClassPath),
3832 member(DirOrJar, Elems).
3833
3840
3841add_search_path(Path, Dir) :-
3842 ( getenv(Path, Old)
3843 -> current_prolog_flag(path_sep, Sep),
3844 ( atomic_list_concat(Current, Sep, Old),
3845 memberchk(Dir, Current)
3846 -> true 3847 ; atomic_list_concat([Old, Sep, Dir], New),
3848 ( debugging(jpl(path))
3849 -> env_var_separators(A,Z),
3850 debug(jpl(path), 'Set ~w~w~w to ~p', [A,Path,Z,New])
3851 ; true
3852 ),
3853 setenv(Path, New)
3854 )
3855 ; setenv(Path, Dir)
3856 ).
3857
3858env_var_separators('%','%') :-
3859 current_prolog_flag(windows, true),
3860 !.
3861env_var_separators($,'').
3862
3863
3864 3867
3883
3884check_java_environment :-
3885 current_prolog_flag(apple, true),
3886 !,
3887 print_message(error, jpl(run(jpl_config_dylib))).
3888check_java_environment :-
3889 check_lib(jvm).
3890
3891check_lib(Name) :-
3892 check_shared_object(Name, File, EnvVar, Absolute),
3893 ( Absolute == (-)
3894 -> env_var_separators(A, Z),
3895 format(string(Msg), 'Please add directory holding ~w to ~w~w~w',
3896 [ File, A, EnvVar, Z ]),
3897 throwme(check_lib,lib_not_found(Name,Msg))
3898 ; true
3899 ).
3900
3907
3908check_shared_object(Name, File, EnvVar, Absolute) :-
3909 libfile(Name, File),
3910 library_search_path(Path, EnvVar),
3911 ( member(Dir, Path),
3912 atomic_list_concat([Dir, File], /, Absolute),
3913 exists_file(Absolute)
3914 -> true
3915 ; Absolute = (-)
3916 ).
3917
3918libfile(Base, File) :-
3919 current_prolog_flag(unix, true),
3920 !,
3921 atom_concat(lib, Base, F0),
3922 current_prolog_flag(shared_object_extension, Ext),
3923 file_name_extension(F0, Ext, File).
3924libfile(Base, File) :-
3925 current_prolog_flag(windows, true),
3926 !,
3927 current_prolog_flag(shared_object_extension, Ext),
3928 file_name_extension(Base, Ext, File).
3929
3930
3935
3936library_search_path(Path, EnvVar) :-
3937 current_prolog_flag(shared_object_search_path, EnvVar),
3938 current_prolog_flag(path_sep, Sep),
3939 ( getenv(EnvVar, Env),
3940 atomic_list_concat(Path, Sep, Env)
3941 -> true
3942 ; Path = []
3943 ).
3944
3945
3956
3957add_jpl_to_classpath :-
3958 classpath(Jar),
3959 file_base_name(Jar, 'jpl.jar'),
3960 !.
3961add_jpl_to_classpath :-
3962 classpath(Dir),
3963 ( sub_atom(Dir, _, _, 0, /)
3964 -> atom_concat(Dir, 'jpl.jar', File)
3965 ; atom_concat(Dir, '/jpl.jar', File)
3966 ),
3967 access_file(File, read),
3968 !.
3969add_jpl_to_classpath :-
3970 absolute_file_name(jar('jpl.jar'), JplJAR,
3971 [ access(read)
3972 ]),
3973 !,
3974 ( getenv('CLASSPATH', Old)
3975 -> current_prolog_flag(path_sep, Separator),
3976 atomic_list_concat([JplJAR, Old], Separator, New)
3977 ; New = JplJAR
3978 ),
3979 setenv('CLASSPATH', New).
3980
3981
3992
3993libjpl(File) :-
3994 ( current_prolog_flag(unix, true)
3995 -> File = foreign(libjpl)
3996 ; File = foreign(jpl) 3997 ).
3998
4005
4006add_jpl_to_ldpath(JPL) :-
4007 absolute_file_name(JPL, File,
4008 [ file_type(executable),
4009 access(read),
4010 file_errors(fail)
4011 ]),
4012 !,
4013 file_directory_name(File, Dir),
4014 prolog_to_os_filename(Dir, OsDir),
4015 extend_java_library_path(OsDir),
4016 current_prolog_flag(shared_object_search_path, PathVar),
4017 add_search_path(PathVar, OsDir).
4018add_jpl_to_ldpath(_).
4019
4026
4027:- if(current_prolog_flag(windows,true)). 4028add_java_to_ldpath :-
4029 current_prolog_flag(windows, true),
4030 !,
4031 phrase(java_dirs, Extra),
4032 ( Extra \== []
4033 -> print_message(informational, extend_ld_path(Extra)),
4034 maplist(extend_dll_search_path, Extra)
4035 ; true
4036 ).
4037:- endif. 4038add_java_to_ldpath.
4039
4040
4046
4047:- if(current_prolog_flag(windows,true)). 4048:- use_module(library(shlib), [win_add_dll_directory/1]). 4049extend_dll_search_path(Dir) :-
4050 win_add_dll_directory(Dir),
4051 ( current_prolog_flag(wine_version, _)
4052 -> prolog_to_os_filename(Dir, OSDir),
4053 ( getenv('PATH', Path0)
4054 -> atomic_list_concat([Path0, OSDir], ';', Path),
4055 setenv('PATH', Path)
4056 ; setenv('PATH', OSDir)
4057 )
4058 ; true
4059 ).
4060:- endif. 4061
4066
4067extend_java_library_path(OsDir) :-
4068 jpl_get_default_jvm_opts(Opts0),
4069 ( select(PathOpt0, Opts0, Rest),
4070 sub_atom(PathOpt0, 0, _, _, '-Djava.library.path=')
4071 -> current_prolog_flag(path_sep, Separator),
4072 atomic_list_concat([PathOpt0, Separator, OsDir], PathOpt),
4073 NewOpts = [PathOpt|Rest]
4074 ; atom_concat('-Djava.library.path=', OsDir, PathOpt),
4075 NewOpts = [PathOpt|Opts0]
4076 ),
4077 debug(jpl(path), 'Setting Java options to ~p', [NewOpts]),
4078 jpl_set_default_jvm_opts(NewOpts).
4079
4084
4085java_dirs -->
4086 4087 java_dir(jvm, '/jre/bin/client'),
4088 java_dir(jvm, '/jre/bin/server'),
4089 java_dir(java, '/jre/bin'),
4090 4091 java_dir(jvm, '/bin/client'),
4092 java_dir(jvm, '/bin/server'),
4093 java_dir(java, '/bin').
4094
4095java_dir(DLL, _SubPath) -->
4096 { check_shared_object(DLL, _, _Var, Abs),
4097 Abs \== (-)
4098 },
4099 !.
4100java_dir(_DLL, SubPath) -->
4101 { java_home(JavaHome),
4102 atom_concat(JavaHome, SubPath, SubDir),
4103 exists_directory(SubDir)
4104 },
4105 !,
4106 [SubDir].
4107java_dir(_, _) --> [].
4108
4109
4115
4116java_home_win_key(
4117 jdk,
4118 'HKEY_LOCAL_MACHINE/Software/JavaSoft/JDK'). 4119java_home_win_key(
4120 jdk,
4121 'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Development Kit').
4122java_home_win_key(
4123 jre,
4124 'HKEY_LOCAL_MACHINE/Software/JavaSoft/JRE').
4125java_home_win_key(
4126 jre,
4127 'HKEY_LOCAL_MACHINE/Software/JavaSoft/Java Runtime Environment').
4128
4129java_home(Home) :-
4130 getenv('JAVA_HOME', Home),
4131 exists_directory(Home),
4132 !.
4133:- if(current_prolog_flag(windows, true)). 4134java_home(Home) :-
4135 java_home_win_key(_, Key0), 4136 catch(win_registry_get_value(Key0, 'CurrentVersion', Version), _, fail),
4137 atomic_list_concat([Key0, Version], /, Key),
4138 win_registry_get_value(Key, 'JavaHome', WinHome),
4139 prolog_to_os_filename(Home, WinHome),
4140 exists_directory(Home),
4141 !.
4142:- else. 4143java_home(Home) :-
4144 member(Home, [ '/usr/lib/java',
4145 '/usr/local/lib/java'
4146 ]),
4147 exists_directory(Home),
4148 !.
4149:- endif. 4150
4151:- dynamic
4152 jvm_ready/0. 4153:- volatile
4154 jvm_ready/0. 4155
4156setup_jvm :-
4157 jvm_ready,
4158 !.
4159setup_jvm :-
4160 add_jpl_to_classpath,
4161 add_java_to_ldpath,
4162 libjpl(JPL),
4163 catch(load_foreign_library(JPL), E, report_java_setup_problem(E)),
4164 add_jpl_to_ldpath(JPL),
4165 assert(jvm_ready).
4166
4167report_java_setup_problem(E) :-
4168 print_message(error, E),
4169 check_java_environment.
4170
4171 4174
4175:- multifile
4176 prolog:message//1. 4177
4178prolog:message(extend_ld_path(Dirs)) -->
4179 [ 'Extended DLL search path with'-[] ],
4180 dir_per_line(Dirs).
4181prolog:message(jpl(run(Command))) -->
4182 [ 'Could not find libjpl.dylib dependencies.'-[],
4183 'Please run `?- ~p.` to correct this'-[Command]
4184 ].
4185
4186dir_per_line([]) --> [].
4187dir_per_line([H|T]) -->
4188 [ nl, ' ~q'-[H] ],
4189 dir_per_line(T).
4190
4191 4194
4217
4270
4271jpl_entityname(class(Ps,Cs)) --> jpl_classname(class(Ps,Cs),dotty),!.
4272jpl_entityname(array(T)) --> jpl_array_type_descriptor(array(T),dotty),!.
4273jpl_entityname(void) --> "void",!.
4274jpl_entityname(P) --> jpl_primitive_entityname(P).
4275
4281
4282jpl_findclass_descriptor(array(T)) --> jpl_array_type_descriptor(array(T),slashy),!.
4283jpl_findclass_descriptor(class(Ps,Cs)) --> jpl_classname(class(Ps,Cs),slashy).
4284
4289
4290jpl_method_descriptor(method(Ts,T)) --> "(", jpl_method_descriptor_args(Ts), ")", jpl_method_descriptor_retval(T).
4291
4292jpl_method_descriptor_args([T|Ts]) --> jpl_field_descriptor(T,slashy), !, jpl_method_descriptor_args(Ts).
4293jpl_method_descriptor_args([]) --> [].
4294
4295jpl_method_descriptor_retval(void) --> "V".
4296jpl_method_descriptor_retval(T) --> jpl_field_descriptor(T,slashy).
4297
4309
4310jpl_classname(class(Ps,Cs),Mode) --> jpl_package_parts(Ps,Mode), jpl_class_parts(Cs).
4311
4324
4325jpl_package_parts([A|As],dotty) --> jpl_java_id(A), ".", !, jpl_package_parts(As,dotty).
4326jpl_package_parts([A|As],slashy) --> jpl_java_id(A), "/", !, jpl_package_parts(As,slashy).
4327jpl_package_parts([],_) --> [].
4328
4351
4352jpl_class_parts(Cs) --> { nonvar(Cs), ! }, 4353 { atomic_list_concat(Cs,'$',A) }, 4354 jpl_java_type_id(A). 4355
4356jpl_class_parts(Cs) --> { var(Cs), ! }, 4357 jpl_java_type_id(A), 4358 { messy_dollar_split(A,Cs) }. 4359
4360
4365
4366jpl_field_descriptor(class(Ps,Cs),Mode) --> jpl_reference_type_descriptor(class(Ps,Cs),Mode),!.
4367jpl_field_descriptor(array(T),Mode) --> jpl_array_type_descriptor(array(T),Mode),!.
4368jpl_field_descriptor(T,_) --> jpl_primitive_type_descriptor(T). 4369
4370jpl_reference_type_descriptor(class(Ps,Cs),Mode) --> "L", jpl_classname(class(Ps,Cs),Mode), ";".
4371
4372jpl_array_type_descriptor(array(T),Mode) --> "[", jpl_field_descriptor(T,Mode).
4373
4382
4383messy_dollar_split(A,Out) :-
4384 assertion(A \== ''),
4385 atom_chars(A,Chars),
4386 append([''|Chars],[''],GAChars), 4387 triple_process(GAChars,[],[],RunsOut),
4388 postprocess_messy_dollar_split_runs(RunsOut,Out).
4389
4390postprocess_messy_dollar_split_runs(Runs,Out) :-
4391 reverse(Runs,R1),
4392 maplist([Rin,Rout]>>reverse(Rin,Rout),R1,O1),
4393 maplist([Chars,Atom]>>atom_chars(Atom,Chars),O1,Out).
4394
4398
4399triple_process([P,'$',N|Rest],Run,Runs,Out) :-
4400 N \== '', P \== '$' , P \== '',!,
4401 triple_process(['',N|Rest],[],[Run|Runs],Out).
4402
4403triple_process(['','$',N|Rest],Run,Runs,Out) :-
4404 !,
4405 triple_process(['',N|Rest],['$'|Run],Runs,Out).
4406
4407triple_process([_,C,N|Rest],Run,Runs,Out) :-
4408 C \== '$',!,
4409 triple_process([C,N|Rest],[C|Run],Runs,Out).
4410
4411triple_process([_,C,''],Run,Runs,[[C|Run]|Runs]) :- !.
4412
4413triple_process([_,''],Run,Runs,[Run|Runs]).
4414
4418
4422
4423jpl_java_type_id(I) --> jpl_java_id(I), { \+memberchk(I,[var,yield]) }.
4424
4429
4430jpl_java_id(I) --> jpl_java_id_raw(I),
4431 { \+jpl_java_keyword(I),
4432 \+jpl_java_boolean_literal(I),
4433 \+jpl_java_null_literal(I) }.
4434
4438
4439jpl_java_id_raw(A) --> { atom(A),! }, 4440 { atom_codes(A,[C|Cs]) }, 4441 { jpl_java_id_start_char(C) },
4442 [C],
4443 jpl_java_id_part_chars(Cs).
4444
4446
4447jpl_java_id_raw(A) --> { var(A),! }, 4448 [C],
4449 { jpl_java_id_start_char(C) },
4450 jpl_java_id_part_chars(Cs),
4451 { atom_codes(A,[C|Cs]) }. 4452
4453jpl_java_id_part_chars([C|Cs]) --> [C], { jpl_java_id_part_char(C) } ,!, jpl_java_id_part_chars(Cs).
4454jpl_java_id_part_chars([]) --> [].
4455
4462
4463jpl_primitive_type_descriptor(boolean) --> "Z",!.
4464jpl_primitive_type_descriptor(byte) --> "B",!.
4465jpl_primitive_type_descriptor(char) --> "C",!.
4466jpl_primitive_type_descriptor(double) --> "D",!.
4467jpl_primitive_type_descriptor(float) --> "F",!.
4468jpl_primitive_type_descriptor(int) --> "I",!.
4469jpl_primitive_type_descriptor(long) --> "J",!.
4470jpl_primitive_type_descriptor(short) --> "S".
4471
4477
4478jpl_primitive_entityname(boolean) --> "boolean" ,!.
4479jpl_primitive_entityname(byte) --> "byte" ,!.
4480jpl_primitive_entityname(char) --> "char" ,!.
4481jpl_primitive_entityname(double) --> "double" ,!.
4482jpl_primitive_entityname(float) --> "float" ,!.
4483jpl_primitive_entityname(int) --> "int" ,!.
4484jpl_primitive_entityname(long) --> "long" ,!.
4485jpl_primitive_entityname(short) --> "short".
4486
4490
4491jpl_java_boolean_literal(true).
4492jpl_java_boolean_literal(false).
4493
4494jpl_java_null_literal(null).
4495
4496jpl_java_keyword('_').
4497jpl_java_keyword(abstract).
4498jpl_java_keyword(assert).
4499jpl_java_keyword(boolean).
4500jpl_java_keyword(break).
4501jpl_java_keyword(byte).
4502jpl_java_keyword(case).
4503jpl_java_keyword(catch).
4504jpl_java_keyword(char).
4505jpl_java_keyword(class).
4506jpl_java_keyword(const).
4507jpl_java_keyword(continue).
4508jpl_java_keyword(default).
4509jpl_java_keyword(do).
4510jpl_java_keyword(double).
4511jpl_java_keyword(else).
4512jpl_java_keyword(enum).
4513jpl_java_keyword(extends).
4514jpl_java_keyword(final).
4515jpl_java_keyword(finally).
4516jpl_java_keyword(float).
4517jpl_java_keyword(for).
4518jpl_java_keyword(goto).
4519jpl_java_keyword(if).
4520jpl_java_keyword(implements).
4521jpl_java_keyword(import).
4522jpl_java_keyword(instanceof).
4523jpl_java_keyword(int).
4524jpl_java_keyword(interface).
4525jpl_java_keyword(long).
4526jpl_java_keyword(native).
4527jpl_java_keyword(new).
4528jpl_java_keyword(package).
4529jpl_java_keyword(private).
4530jpl_java_keyword(protected).
4531jpl_java_keyword(public).
4532jpl_java_keyword(return).
4533jpl_java_keyword(short).
4534jpl_java_keyword(static).
4535jpl_java_keyword(strictfp).
4536jpl_java_keyword(super).
4537jpl_java_keyword(switch).
4538jpl_java_keyword(synchronized).
4539jpl_java_keyword(this).
4540jpl_java_keyword(throw).
4541jpl_java_keyword(throws).
4542jpl_java_keyword(transient).
4543jpl_java_keyword(try).
4544jpl_java_keyword(void).
4545jpl_java_keyword(volatile).
4546jpl_java_keyword(while).
4547
4581
4582jpl_java_id_start_char(C) :-
4583 assertion(integer(C)),
4584 java_id_start_char_ranges(Ranges), 4585 char_inside_range(C,Ranges). 4586
4587jpl_java_id_part_char(C) :-
4588 assertion(integer(C)),
4589 java_id_part_char_ranges(Ranges), 4590 char_inside_range(C,Ranges). 4591
4592char_inside_range(C,[[_Low,High]|Ranges]) :-
4593 High < C,!,char_inside_range(C,Ranges).
4594
4595char_inside_range(C,[[Low,High]|_]) :-
4596 Low =< C, C =< High.
4597
4605
4606java_id_start_char_ranges(
4607 [[36,36],[65,90],[95,95],[97,122],[162,165],[170,170],[181,181],[186,186],
4608 [192,214],[216,246],[248,705],[710,721],[736,740],[748,748],[750,750],
4609 [880,884],[886,887],[890,893],[895,895],[902,902],[904,906],[908,908],
4610 [910,929],[931,1013],[1015,1153],[1162,1327],[1329,1366],[1369,1369],
4611 [1376,1416],[1423,1423],[1488,1514],[1519,1522],[1547,1547],[1568,1610],
4612 [1646,1647],[1649,1747],[1749,1749],[1765,1766],[1774,1775],[1786,1788],
4613 [1791,1791],[1808,1808],[1810,1839],[1869,1957],[1969,1969],[1994,2026],
4614 [2036,2037],[2042,2042],[2046,2069],[2074,2074],[2084,2084],[2088,2088],
4615 [2112,2136],[2144,2154],[2208,2228],[2230,2237],[2308,2361],[2365,2365],
4616 [2384,2384],[2392,2401],[2417,2432],[2437,2444],[2447,2448],[2451,2472],
4617 [2474,2480],[2482,2482],[2486,2489],[2493,2493],[2510,2510],[2524,2525],
4618 [2527,2529],[2544,2547],[2555,2556],[2565,2570],[2575,2576],[2579,2600],
4619 [2602,2608],[2610,2611],[2613,2614],[2616,2617],[2649,2652],[2654,2654],
4620 [2674,2676],[2693,2701],[2703,2705],[2707,2728],[2730,2736],[2738,2739],
4621 [2741,2745],[2749,2749],[2768,2768],[2784,2785],[2801,2801],[2809,2809],
4622 [2821,2828],[2831,2832],[2835,2856],[2858,2864],[2866,2867],[2869,2873],
4623 [2877,2877],[2908,2909],[2911,2913],[2929,2929],[2947,2947],[2949,2954],
4624 [2958,2960],[2962,2965],[2969,2970],[2972,2972],[2974,2975],[2979,2980],
4625 [2984,2986],[2990,3001],[3024,3024],[3065,3065],[3077,3084],[3086,3088],
4626 [3090,3112],[3114,3129],[3133,3133],[3160,3162],[3168,3169],[3200,3200],
4627 [3205,3212],[3214,3216],[3218,3240],[3242,3251],[3253,3257],[3261,3261],
4628 [3294,3294],[3296,3297],[3313,3314],[3333,3340],[3342,3344],[3346,3386],
4629 [3389,3389],[3406,3406],[3412,3414],[3423,3425],[3450,3455],[3461,3478],
4630 [3482,3505],[3507,3515],[3517,3517],[3520,3526],[3585,3632],[3634,3635],
4631 [3647,3654],[3713,3714],[3716,3716],[3718,3722],[3724,3747],[3749,3749],
4632 [3751,3760],[3762,3763],[3773,3773],[3776,3780],[3782,3782],[3804,3807],
4633 [3840,3840],[3904,3911],[3913,3948],[3976,3980],[4096,4138],[4159,4159],
4634 [4176,4181],[4186,4189],[4193,4193],[4197,4198],[4206,4208],[4213,4225],
4635 [4238,4238],[4256,4293],[4295,4295],[4301,4301],[4304,4346],[4348,4680],
4636 [4682,4685],[4688,4694],[4696,4696],[4698,4701],[4704,4744],[4746,4749],
4637 [4752,4784],[4786,4789],[4792,4798],[4800,4800],[4802,4805],[4808,4822],
4638 [4824,4880],[4882,4885],[4888,4954],[4992,5007],[5024,5109],[5112,5117],
4639 [5121,5740],[5743,5759],[5761,5786],[5792,5866],[5870,5880],[5888,5900],
4640 [5902,5905],[5920,5937],[5952,5969],[5984,5996],[5998,6000],[6016,6067],
4641 [6103,6103],[6107,6108],[6176,6264],[6272,6276],[6279,6312],[6314,6314],
4642 [6320,6389],[6400,6430],[6480,6509],[6512,6516],[6528,6571],[6576,6601],
4643 [6656,6678],[6688,6740],[6823,6823],[6917,6963],[6981,6987],[7043,7072],
4644 [7086,7087],[7098,7141],[7168,7203],[7245,7247],[7258,7293],[7296,7304],
4645 [7312,7354],[7357,7359],[7401,7404],[7406,7411],[7413,7414],[7418,7418],
4646 [7424,7615],[7680,7957],[7960,7965],[7968,8005],[8008,8013],[8016,8023],
4647 [8025,8025],[8027,8027],[8029,8029],[8031,8061],[8064,8116],[8118,8124],
4648 [8126,8126],[8130,8132],[8134,8140],[8144,8147],[8150,8155],[8160,8172],
4649 [8178,8180],[8182,8188],[8255,8256],[8276,8276],[8305,8305],[8319,8319],
4650 [8336,8348],[8352,8383],[8450,8450],[8455,8455],[8458,8467],[8469,8469],
4651 [8473,8477],[8484,8484],[8486,8486],[8488,8488],[8490,8493],[8495,8505],
4652 [8508,8511],[8517,8521],[8526,8526],[8544,8584],[11264,11310],[11312,11358],
4653 [11360,11492],[11499,11502],[11506,11507],[11520,11557],[11559,11559],
4654 [11565,11565],[11568,11623],[11631,11631],[11648,11670],[11680,11686],
4655 [11688,11694],[11696,11702],[11704,11710],[11712,11718],[11720,11726],
4656 [11728,11734],[11736,11742],[11823,11823],[12293,12295],[12321,12329],
4657 [12337,12341],[12344,12348],[12353,12438],[12445,12447],[12449,12538],
4658 [12540,12543],[12549,12591],[12593,12686],[12704,12730],[12784,12799],
4659 [13312,19893],[19968,40943],[40960,42124],[42192,42237],[42240,42508],
4660 [42512,42527],[42538,42539],[42560,42606],[42623,42653],[42656,42735],
4661 [42775,42783],[42786,42888],[42891,42943],[42946,42950],[42999,43009],
4662 [43011,43013],[43015,43018],[43020,43042],[43064,43064],[43072,43123],
4663 [43138,43187],[43250,43255],[43259,43259],[43261,43262],[43274,43301],
4664 [43312,43334],[43360,43388],[43396,43442],[43471,43471],[43488,43492],
4665 [43494,43503],[43514,43518],[43520,43560],[43584,43586],[43588,43595],
4666 [43616,43638],[43642,43642],[43646,43695],[43697,43697],[43701,43702],
4667 [43705,43709],[43712,43712],[43714,43714],[43739,43741],[43744,43754],
4668 [43762,43764],[43777,43782],[43785,43790],[43793,43798],[43808,43814],
4669 [43816,43822],[43824,43866],[43868,43879],[43888,44002],[44032,55203],
4670 [55216,55238],[55243,55291],[63744,64109],[64112,64217],[64256,64262],
4671 [64275,64279],[64285,64285],[64287,64296],[64298,64310],[64312,64316],
4672 [64318,64318],[64320,64321],[64323,64324],[64326,64433],[64467,64829],
4673 [64848,64911],[64914,64967],[65008,65020],[65075,65076],[65101,65103],
4674 [65129,65129],[65136,65140],[65142,65276],[65284,65284],[65313,65338],
4675 [65343,65343],[65345,65370],[65382,65470],[65474,65479],[65482,65487],
4676 [65490,65495],[65498,65500],[65504,65505],[65509,65510]]).
4677
4678java_id_part_char_ranges(
4679 [[0,8],[14,27],[36,36],[48,57],[65,90],[95,95],[97,122],[127,159],[162,165],
4680 [170,170],[173,173],[181,181],[186,186],[192,214],[216,246],[248,705],
4681 [710,721],[736,740],[748,748],[750,750],[768,884],[886,887],[890,893],
4682 [895,895],[902,902],[904,906],[908,908],[910,929],[931,1013],[1015,1153],
4683 [1155,1159],[1162,1327],[1329,1366],[1369,1369],[1376,1416],[1423,1423],
4684 [1425,1469],[1471,1471],[1473,1474],[1476,1477],[1479,1479],[1488,1514],
4685 [1519,1522],[1536,1541],[1547,1547],[1552,1562],[1564,1564],[1568,1641],
4686 [1646,1747],[1749,1757],[1759,1768],[1770,1788],[1791,1791],[1807,1866],
4687 [1869,1969],[1984,2037],[2042,2042],[2045,2093],[2112,2139],[2144,2154],
4688 [2208,2228],[2230,2237],[2259,2403],[2406,2415],[2417,2435],[2437,2444],
4689 [2447,2448],[2451,2472],[2474,2480],[2482,2482],[2486,2489],[2492,2500],
4690 [2503,2504],[2507,2510],[2519,2519],[2524,2525],[2527,2531],[2534,2547],
4691 [2555,2556],[2558,2558],[2561,2563],[2565,2570],[2575,2576],[2579,2600],
4692 [2602,2608],[2610,2611],[2613,2614],[2616,2617],[2620,2620],[2622,2626],
4693 [2631,2632],[2635,2637],[2641,2641],[2649,2652],[2654,2654],[2662,2677],
4694 [2689,2691],[2693,2701],[2703,2705],[2707,2728],[2730,2736],[2738,2739],
4695 [2741,2745],[2748,2757],[2759,2761],[2763,2765],[2768,2768],[2784,2787],
4696 [2790,2799],[2801,2801],[2809,2815],[2817,2819],[2821,2828],[2831,2832],
4697 [2835,2856],[2858,2864],[2866,2867],[2869,2873],[2876,2884],[2887,2888],
4698 [2891,2893],[2902,2903],[2908,2909],[2911,2915],[2918,2927],[2929,2929],
4699 [2946,2947],[2949,2954],[2958,2960],[2962,2965],[2969,2970],[2972,2972],
4700 [2974,2975],[2979,2980],[2984,2986],[2990,3001],[3006,3010],[3014,3016],
4701 [3018,3021],[3024,3024],[3031,3031],[3046,3055],[3065,3065],[3072,3084],
4702 [3086,3088],[3090,3112],[3114,3129],[3133,3140],[3142,3144],[3146,3149],
4703 [3157,3158],[3160,3162],[3168,3171],[3174,3183],[3200,3203],[3205,3212],
4704 [3214,3216],[3218,3240],[3242,3251],[3253,3257],[3260,3268],[3270,3272],
4705 [3274,3277],[3285,3286],[3294,3294],[3296,3299],[3302,3311],[3313,3314],
4706 [3328,3331],[3333,3340],[3342,3344],[3346,3396],[3398,3400],[3402,3406],
4707 [3412,3415],[3423,3427],[3430,3439],[3450,3455],[3458,3459],[3461,3478],
4708 [3482,3505],[3507,3515],[3517,3517],[3520,3526],[3530,3530],[3535,3540],
4709 [3542,3542],[3544,3551],[3558,3567],[3570,3571],[3585,3642],[3647,3662],
4710 [3664,3673],[3713,3714],[3716,3716],[3718,3722],[3724,3747],[3749,3749],
4711 [3751,3773],[3776,3780],[3782,3782],[3784,3789],[3792,3801],[3804,3807],
4712 [3840,3840],[3864,3865],[3872,3881],[3893,3893],[3895,3895],[3897,3897],
4713 [3902,3911],[3913,3948],[3953,3972],[3974,3991],[3993,4028],[4038,4038],
4714 [4096,4169],[4176,4253],[4256,4293],[4295,4295],[4301,4301],[4304,4346],
4715 [4348,4680],[4682,4685],[4688,4694],[4696,4696],[4698,4701],[4704,4744],
4716 [4746,4749],[4752,4784],[4786,4789],[4792,4798],[4800,4800],[4802,4805],
4717 [4808,4822],[4824,4880],[4882,4885],[4888,4954],[4957,4959],[4992,5007],
4718 [5024,5109],[5112,5117],[5121,5740],[5743,5759],[5761,5786],[5792,5866],
4719 [5870,5880],[5888,5900],[5902,5908],[5920,5940],[5952,5971],[5984,5996],
4720 [5998,6000],[6002,6003],[6016,6099],[6103,6103],[6107,6109],[6112,6121],
4721 [6155,6158],[6160,6169],[6176,6264],[6272,6314],[6320,6389],[6400,6430],
4722 [6432,6443],[6448,6459],[6470,6509],[6512,6516],[6528,6571],[6576,6601],
4723 [6608,6617],[6656,6683],[6688,6750],[6752,6780],[6783,6793],[6800,6809],
4724 [6823,6823],[6832,6845],[6912,6987],[6992,7001],[7019,7027],[7040,7155],
4725 [7168,7223],[7232,7241],[7245,7293],[7296,7304],[7312,7354],[7357,7359],
4726 [7376,7378],[7380,7418],[7424,7673],[7675,7957],[7960,7965],[7968,8005],
4727 [8008,8013],[8016,8023],[8025,8025],[8027,8027],[8029,8029],[8031,8061],
4728 [8064,8116],[8118,8124],[8126,8126],[8130,8132],[8134,8140],[8144,8147],
4729 [8150,8155],[8160,8172],[8178,8180],[8182,8188],[8203,8207],[8234,8238],
4730 [8255,8256],[8276,8276],[8288,8292],[8294,8303],[8305,8305],[8319,8319],
4731 [8336,8348],[8352,8383],[8400,8412],[8417,8417],[8421,8432],[8450,8450],
4732 [8455,8455],[8458,8467],[8469,8469],[8473,8477],[8484,8484],[8486,8486],
4733 [8488,8488],[8490,8493],[8495,8505],[8508,8511],[8517,8521],[8526,8526],
4734 [8544,8584],[11264,11310],[11312,11358],[11360,11492],[11499,11507],
4735 [11520,11557],[11559,11559],[11565,11565],[11568,11623],[11631,11631],
4736 [11647,11670],[11680,11686],[11688,11694],[11696,11702],[11704,11710],
4737 [11712,11718],[11720,11726],[11728,11734],[11736,11742],[11744,11775],
4738 [11823,11823],[12293,12295],[12321,12335],[12337,12341],[12344,12348],
4739 [12353,12438],[12441,12442],[12445,12447],[12449,12538],[12540,12543],
4740 [12549,12591],[12593,12686],[12704,12730],[12784,12799],[13312,19893],
4741 [19968,40943],[40960,42124],[42192,42237],[42240,42508],[42512,42539],
4742 [42560,42607],[42612,42621],[42623,42737],[42775,42783],[42786,42888],
4743 [42891,42943],[42946,42950],[42999,43047],[43064,43064],[43072,43123],
4744 [43136,43205],[43216,43225],[43232,43255],[43259,43259],[43261,43309],
4745 [43312,43347],[43360,43388],[43392,43456],[43471,43481],[43488,43518],
4746 [43520,43574],[43584,43597],[43600,43609],[43616,43638],[43642,43714],
4747 [43739,43741],[43744,43759],[43762,43766],[43777,43782],[43785,43790],
4748 [43793,43798],[43808,43814],[43816,43822],[43824,43866],[43868,43879],
4749 [43888,44010],[44012,44013],[44016,44025],[44032,55203],[55216,55238],
4750 [55243,55291],[63744,64109],[64112,64217],[64256,64262],[64275,64279],
4751 [64285,64296],[64298,64310],[64312,64316],[64318,64318],[64320,64321],
4752 [64323,64324],[64326,64433],[64467,64829],[64848,64911],[64914,64967],
4753 [65008,65020],[65024,65039],[65056,65071],[65075,65076],[65101,65103],
4754 [65129,65129],[65136,65140],[65142,65276],[65279,65279],[65284,65284],
4755 [65296,65305],[65313,65338],[65343,65343],[65345,65370],[65382,65470],
4756 [65474,65479],[65482,65487],[65490,65495],[65498,65500],[65504,65505],
4757 [65509,65510],[65529,65531]]).
4758
4759
4760 4763
4783
4784throwme(LookupPred,LookupTerm) :-
4785 findall([Location,Formal,Msg],exc_desc(LookupPred,LookupTerm,Location,Formal,Msg),Bag),
4786 length(Bag,BagLength),
4787 throwme_help(BagLength,Bag,LookupPred,LookupTerm).
4788
4805
4806throwme_help(1,[[Location,Formal,Msg]],_,_) :-
4807 throw(error(Formal,context(Location,Msg))).
4808
4819
4820throwme_help(Count,_,LookupPred,LookupTerm) :-
4821 Count \== 1,
4822 with_output_to(
4823 atom(Msg),
4824 format("Instead of 1, found ~d exception descriptors for LookupPred = ~q, LookupTerm = ~q",
4825 [Count,LookupPred,LookupTerm])),
4826 throw(error(programming_error,context(_,Msg))).
4827
4878
4879safe_type_to_classname(Type,CN) :-
4880 catch(
4881 (jpl_type_to_classname(Type,CN)
4882 -> true
4883 ; with_output_to(atom(CN),format("~q",[Type]))),
4884 _DontCareCatcher,
4885 CN='???').
4886
4887exc_desc(jpl_new,x_is_var,
4888 jpl_new/3,
4889 instantiation_error,
4890 '1st arg must be bound to a classname, descriptor or object type').
4891
4892exc_desc(jpl_new,x_not_classname(X),
4893 jpl_new/3,
4894 domain_error(classname,X),
4895 'if 1st arg is an atom, it must be a classname or descriptor').
4896
4897exc_desc(jpl_new,x_not_instantiable(X),
4898 jpl_new/3,
4899 type_error(instantiable,X),
4900 '1st arg must be a classname, descriptor or object type').
4901
4902exc_desc(jpl_new,not_a_jpl_term(X),
4903 jpl_new/3,
4904 type_error(term,X),
4905 'result is not a org.jpl7.Term instance as required').
4906
4908
4909exc_desc(jpl_new_class,params_is_var,
4910 jpl_new/3,
4911 instantiation_error,
4912 '2nd arg must be a proper list of valid parameters for a constructor').
4913
4914exc_desc(jpl_new_class,params_is_not_list(Params),
4915 jpl_new/3,
4916 type_error(list,Params),
4917 '2nd arg must be a proper list of valid parameters for a constructor').
4918
4919exc_desc(jpl_new_class,class_is_interface(Type),
4920 jpl_new/3,
4921 type_error(concrete_class,CN),
4922 'cannot create instance of an interface') :- safe_type_to_classname(Type,CN).
4923
4924exc_desc(jpl_new_class,class_without_constructor(Type,Arity),
4925 jpl_new/3,
4926 existence_error(constructor,CN/Arity),
4927 'no constructor found with the corresponding quantity of parameters') :- safe_type_to_classname(Type,CN).
4928
4929exc_desc(jpl_new_class,acyclic(X,Msg),
4930 jpl_new/3,
4931 type_error(acyclic,X),
4932 Msg).
4933
4934exc_desc(jpl_new_class,bad_jpl_datum(Params),
4935 jpl_new/3,
4936 domain_error(list(jpl_datum),Params),
4937 'one or more of the actual parameters is not a valid representation of any Java value or object').
4938
4939exc_desc(jpl_new_class,single_constructor_mismatch(Co),
4940 jpl_new/3,
4941 existence_error(constructor,Co),
4942 'the actual parameters are not assignable to the formal parameter types of the only constructor which takes this qty of parameters').
4943
4944exc_desc(jpl_new_class,any_constructor_mismatch(Params),
4945 jpl_new/3,
4946 type_error(constructor_args,Params),
4947 'the actual parameters are not assignable to the formal parameter types of any of the constructors which take this qty of parameters').
4948
4949exc_desc(jpl_new_class,constructor_multimatch(Params),
4950 jpl_new/3,
4951 type_error(constructor_params,Params),
4952 'more than one most-specific matching constructor (shouldn''t happen)').
4953
4954exc_desc(jpl_new_class,class_is_abstract(Type),
4955 jpl_new/3,
4956 type_error(concrete_class,CN),
4957 'cannot create instance of an abstract class') :- safe_type_to_classname(Type,CN).
4958
4960
4961exc_desc(jpl_new_array,params_is_var,
4962 jpl_new/3,
4963 instantiation_error,
4964 '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').
4965
4966exc_desc(jpl_new_array,params_is_negative(Params),
4967 jpl_new/3,
4968 domain_error(array_length,Params),
4969 'when constructing a new array, if the 2nd arg is an integer (denoting the required array length) then it must be non-negative').
4970
4972
4973exc_desc(jpl_new_primitive,primitive_type_requested(T),
4974 jpl_new/3,
4975 domain_error(object_type,T),
4976 'cannot construct an instance of a primitive type').
4977
4979exc_desc(jpl_new_primitive,params_is_var,
4980 jpl_new/3,
4981 instantiation_error,
4982 'when constructing a new instance of a primitive type, 2nd arg must be bound (to a representation of a suitable value)').
4983
4985exc_desc(jpl_new_primitive,params_is_bad(Params),
4986 jpl_new/3,
4987 domain_error(constructor_args,Params),Msg) :-
4988 atomic_list_concat([
4989 'when constructing a new instance of a primitive type, 2nd arg must either be an ',
4990 'empty list (indicating that the default value of that type is required) or a ',
4991 'list containing exactly one representation of a suitable value'],Msg).
4992
4994
4995exc_desc(jpl_new_catchall,catchall(T),
4996 jpl_new/3,
4997 domain_error(jpl_type,T),
4998 '1st arg must denote a known or plausible type').
4999
5001
5002exc_desc(jpl_call,arg1_is_var,
5003 jpl_call/4,
5004 instantiation_error,
5005 '1st arg must be bound to an object, classname, descriptor or type').
5006
5007exc_desc(jpl_call,no_such_class(X),
5008 jpl_call/4,
5009 existence_error(class,X),
5010 'the named class cannot be found').
5011
5012exc_desc(jpl_call,arg1_is_bad(X),
5013 jpl_call/4,
5014 type_error(class_name_or_descriptor,X),
5015 '1st arg must be an object, classname, descriptor or type').
5016
5017exc_desc(jpl_call,arg1_is_array(X),
5018 jpl_call/4,
5019 type_error(object_or_class,X),
5020 'cannot call a static method of an array type, as none exists').
5021
5022exc_desc(jpl_call,arg1_is_bad_2(X),
5023 jpl_call/4,
5024 domain_error(object_or_class,X),
5025 '1st arg must be an object, classname, descriptor or type').
5026
5027exc_desc(jpl_call,mspec_is_var,
5028 jpl_call/4,
5029 instantiation_error,
5030 '2nd arg must be an atom naming a public method of the class or object').
5031
5032exc_desc(jpl_call,mspec_is_bad(Mspec),
5033 jpl_call/4,
5034 type_error(method_name,Mspec),
5035 '2nd arg must be an atom naming a public method of the class or object').
5036
5037exc_desc(jpl_call,acyclic(Te,Msg),
5038 jpl_call/4,
5039 type_error(acyclic,Te),
5040 Msg).
5041
5042exc_desc(jpl_call,nonconvertible_params(Params),
5043 jpl_call/4,
5044 type_error(method_params,Params),
5045 'not all actual parameters are convertible to Java values or references').
5046
5047exc_desc(jpl_call,arg3_is_var,
5048 jpl_call/4,
5049 instantiation_error,
5050 '3rd arg must be a proper list of actual parameters for the named method').
5051
5052exc_desc(jpl_call,arg3_is_bad(Params),
5053 jpl_call/4,
5054 type_error(method_params,Params),
5055 '3rd arg must be a proper list of actual parameters for the named method').
5056
5057exc_desc(jpl_call,not_a_jpl_term(X),
5058 jpl_call/4,
5059 type_error(jni_jref,X),
5060 'result is not a org.jpl7.Term instance as required').
5061
5063
5064exc_desc(jpl_call_instance,no_such_method(M),
5065 jpl_call/4,
5066 existence_error(method,M),
5067 'the class or object has no public methods with the given name and quantity of parameters').
5068
5069exc_desc(jpl_call_instance,param_not_assignable(P),
5070 jpl_call/4,
5071 type_error(method_params,P),
5072 'the actual parameters are not assignable to the formal parameters of any of the named methods').
5073
5074exc_desc(jpl_call_instance,multiple_most_specific(M),
5075 jpl_call/4,
5076 existence_error(most_specific_method,M),
5077 'more than one most-specific method is found for the actual parameters (this should not happen)').
5078
5080
5081exc_desc(jpl_call_static,no_such_method(M),
5082 jpl_call/4,
5083 existence_error(method,M),
5084 'the class has no public static methods with the given name and quantity of parameters').
5085
5086exc_desc(jpl_call_static,param_not_assignable(P),
5087 jpl_call/4,
5088 type_error(method_params,P),
5089 'the actual parameters are not assignable to the formal parameters of any of the named methods').
5090
5091exc_desc(jpl_call_static,multiple_most_specific(M),
5092 jpl_call/4,
5093 existence_error(most_specific_method,M),
5094 'more than one most-specific method is found for the actual parameters (this should not happen)').
5095
5097
5098exc_desc(jpl_get,arg1_is_var,
5099 jpl_get/3,
5100 instantiation_error,
5101 '1st arg must be bound to an object, classname, descriptor or type').
5102
5103exc_desc(jpl_get,named_class_not_found(Type),
5104 jpl_get/3,
5105 existence_error(class,CN),
5106 'the named class cannot be found') :- safe_type_to_classname(Type,CN).
5107
5108exc_desc(jpl_get,arg1_is_bad(X),
5109 jpl_get/3,
5110 type_error(class_name_or_descriptor,X),
5111 '1st arg must be an object, classname, descriptor or type').
5112
5113exc_desc(jpl_get,arg1_is_bad_2(X),
5114 jpl_get/3,
5115 domain_error(object_or_class,X),
5116 '1st arg must be an object, classname, descriptor or type').
5117
5118exc_desc(jpl_get,not_a_jpl_term(X),
5119 jpl_get/3,
5120 type_error(jni_ref,X),
5121 'result is not a org.jpl7.Term instance as required').
5122
5124
5125exc_desc(jpl_get_static,arg2_is_var,
5126 jpl_get/3,
5127 instantiation_error,
5128 '2nd arg must be bound to an atom naming a public field of the class').
5129
5130exc_desc(jpl_get_static,arg2_is_bad(F),
5131 jpl_get/3,
5132 type_error(field_name,F),
5133 '2nd arg must be an atom naming a public field of the class').
5134
5135exc_desc(jpl_get_static,no_such_field(F),
5136 jpl_get/3,
5137 existence_error(field,F),
5138 'the class or object has no public static field with the given name').
5139
5140exc_desc(jpl_get_static,multiple_fields(F),
5141 jpl_get/3,
5142 existence_error(unique_field,F),
5143 'more than one field is found with the given name').
5144
5146
5147exc_desc(jpl_get_instance,arg2_is_var,
5148 jpl_get/3,
5149 instantiation_error,
5150 '2nd arg must be bound to an atom naming a public field of the class or object').
5151
5152exc_desc(jpl_get_instance,arg2_is_bad(X),
5153 jpl_get/3,
5154 type_error(field_name,X),
5155 '2nd arg must be an atom naming a public field of the class or object').
5156
5157exc_desc(jpl_get_instance,no_such_field(Fname),
5158 jpl_get/3,
5159 existence_error(field,Fname),
5160 'the class or object has no public field with the given name').
5161
5162exc_desc(jpl_get_instance,multiple_fields(Fname),
5163 jpl_get/3,
5164 existence_error(unique_field,Fname),
5165 'more than one field is found with the given name').
5166
5168
5169exc_desc(jpl_get_instance_array,arg2_is_var,
5170 jpl_get/3,
5171 instantiation_error,
5172 'when 1st arg is an array, 2nd arg must be bound to an index, an index range, or ''length''').
5173
5174exc_desc(jpl_get_instance_array,arg2_is_bad(X),
5175 jpl_get/3,
5176 domain_error(array_index,X),
5177 'when 1st arg is an array, integral 2nd arg must be non-negative').
5178
5179exc_desc(jpl_get_instance_array,arg2_is_too_large(X),
5180 jpl_get/3,
5181 domain_error(array_index,X),
5182 'when 1st arg is an array, integral 2nd arg must not exceed upper bound of array').
5183
5184exc_desc(jpl_get_instance_array,bad_range_low(R),
5185 jpl_get/3,
5186 domain_error(array_index_range,R),
5187 'lower bound of array index range must not exceed upper bound of array').
5188
5189exc_desc(jpl_get_instance_array,bad_range_high(R),
5190 jpl_get/3,
5191 domain_error(array_index_range,R),
5192 'upper bound of array index range must not exceed upper bound of array').
5193
5194exc_desc(jpl_get_instance_array,bad_range_pair_values(R),
5195 jpl_get/3,
5196 domain_error(array_index_range,R),
5197 'array index range must be a non-decreasing pair of non-negative integers').
5198
5199exc_desc(jpl_get_instance_array,bad_range_pair_types(R),
5200 jpl_get/3,
5201 type_error(array_index_range,R),
5202 'array index range must be a non-decreasing pair of non-negative integers').
5203
5204exc_desc(jpl_get_instance_array,no_such_field(F),
5205 jpl_get/3,
5206 domain_error(array_field_name,F),
5207 'the array has no public field with the given name').
5208
5209exc_desc(jpl_get_instance_array,wrong_spec(F),
5210 jpl_get/3,
5211 type_error(array_lookup_spec,F),
5212 'when 1st arg is an array, 2nd arg must be an index, an index range, or ''length''').
5213
5215
5216exc_desc(jpl_set,arg1_is_var,
5217 jpl_set/3,
5218 instantiation_error,
5219 '1st arg must be an object, classname, descriptor or type').
5220
5221exc_desc(jpl_set,classname_does_not_resolve(X),
5222 jpl_set/3,
5223 existence_error(class,X),
5224 'the named class cannot be found').
5225
5226exc_desc(jpl_set,named_class_not_found(Type),
5227 jpl_set/3,
5228 existence_error(class,CN),
5229 'the named class cannot be found') :- safe_type_to_classname(Type,CN).
5230
5231exc_desc(jpl_set,acyclic(X,Msg),
5232 jpl_set/3,
5233 type_error(acyclic,X),
5234 Msg).
5235
5236exc_desc(jpl_set,arg1_is_bad(X),
5237 jpl_set/3,
5238 domain_error(object_or_class,X),
5239 '1st arg must be an object, classname, descriptor or type').
5240
5242
5243exc_desc(jpl_set_instance_class,arg2_is_var,
5244 jpl_set/3,
5245 instantiation_error,
5246 '2nd arg must be bound to the name of a public, non-final field').
5247
5248exc_desc(jpl_set_instance_class,arg2_is_bad(Fname),
5249 jpl_set/3,
5250 type_error(field_name,Fname),
5251 '2nd arg must be the name of a public, non-final field').
5252
5253exc_desc(jpl_set_instance_class,no_such_field(Fname),
5254 jpl_set/3,
5255 existence_error(field,Fname),
5256 'no public fields of the object have this name').
5257
5258exc_desc(jpl_set_instance_class,field_is_final(Fname),
5259 jpl_set/3,
5260 permission_error(modify,final_field,Fname),
5261 'cannot assign a value to a final field (actually you could but I''ve decided not to let you)').
5262
5263exc_desc(jpl_set_instance_class,incompatible_value(Type,V),
5264 jpl_set/3,
5265 type_error(CN,V),
5266 'the value is not assignable to the named field of the class') :- safe_type_to_classname(Type,CN).
5267
5268exc_desc(jpl_set_instance_class,arg3_is_bad(V),
5269 jpl_set/3,
5270 type_error(field_value,V),
5271 '3rd arg does not represent any Java value or object').
5272
5273exc_desc(jpl_set_instance_class,multiple_fields(Fname),
5274 jpl_set/3,
5275 existence_error(field,Fname),
5276 'more than one public field of the object has this name (this should not happen)').
5277
5279
5280exc_desc(jpl_set_instance_array,arg3_is_var,
5281 jpl_set/3,
5282 instantiation_error,
5283 'when 1st arg is an array, 3rd arg must be bound to a suitable element value or list of values').
5284
5285exc_desc(jpl_set_instance_array,arg2_is_var,
5286 jpl_set/3,
5287 instantiation_error,
5288 'when 1st arg is an array, 2nd arg must be bound to an index or index range').
5289
5290exc_desc(jpl_set_instance_array,arg2_is_bad(FSpec),
5291 jpl_set/3,
5292 domain_error(array_index,FSpec),
5293 'when 1st arg is an array, an integral 2nd arg must be a non-negative index').
5294
5295exc_desc(jpl_set_instance_array,no_values(Fspec,Vs),
5296 jpl_set/3,
5297 domain_error(array_element(Fspec),Vs),
5298 'no values for array element assignment: needs one').
5299
5300exc_desc(jpl_set_instance_array,more_than_one_value(Fspec,Vs),
5301 jpl_set/3,
5302 domain_error(array_element(Fspec),Vs),
5303 'too many values for array element assignment: needs one').
5304
5305exc_desc(jpl_set_instance_array,too_few_values(N-M,Vs),
5306 jpl_set/3,
5307 domain_error(array_elements(N-M),Vs),
5308 'too few values for array range assignment').
5309
5310exc_desc(jpl_set_instance_array,too_many_values(N-M,Vs),
5311 jpl_set/3,
5312 domain_error(array_elements(N-M),Vs),
5313 'too many values for array range assignment').
5314
5315exc_desc(jpl_set_instance_array,bad_range_pair_values(N-M),
5316 jpl_set/3,
5317 domain_error(array_index_range,N-M),
5318 'array index range must be a non-decreasing pair of non-negative integers').
5319
5320exc_desc(jpl_set_instance_array,bad_range_pair_types(N-M),
5321 jpl_set/3,
5322 type_error(array_index_range,N-M),
5323 'array index range must be a non-decreasing pair of non-negative integers').
5324
5325exc_desc(jpl_set_instance_array,cannot_assign_to_final_field,
5326 jpl_set/3,
5327 permission_error(modify,final_field,length),
5328 'cannot assign a value to a final field').
5329
5330exc_desc(jpl_set_instance_array,no_such_field(Fspec),
5331 jpl_set/3,
5332 existence_error(field,Fspec),
5333 'array has no field with that name').
5334
5335exc_desc(jpl_set_instance_array,arg2_is_bad_2(Fspec),
5336 jpl_set/3,
5337 domain_error(array_index,Fspec),
5338 'when 1st arg is an array object, 2nd arg must be a non-negative index or index range').
5339
5341
5342exc_desc(jpl_set_static,arg2_is_unbound,
5343 jpl_set/3,
5344 instantiation_error,
5345 'when 1st arg denotes a class, 2nd arg must be bound to the name of a public, static, non-final field').
5346
5347exc_desc(jpl_set_static,arg2_is_bad(Fname),
5348 jpl_set/3,
5349 type_error(field_name,Fname),
5350 'when 1st arg denotes a class, 2nd arg must be the name of a public, static, non-final field').
5351
5352exc_desc(jpl_set_static,no_such_public_static_field(field,Fname),
5353 jpl_set/3,
5354 existence_error(field,Fname),
5355 'class has no public static fields of this name').
5356
5357exc_desc(jpl_set_static,cannot_assign_final_field(Fname),
5358 jpl_set/3,
5359 permission_error(modify,final_field,Fname),
5360 'cannot assign a value to a final field').
5361
5362exc_desc(jpl_set_static,value_not_assignable(Type,V),
5363 jpl_set/3,
5364 type_error(CN,V),
5365 'the value is not assignable to the named field of the class') :- safe_type_to_classname(Type,CN).
5366
5367exc_desc(jpl_set_static,arg3_is_bad(field_value,V),
5368 jpl_set/3,
5369 type_error(field_value,V),
5370 '3rd arg does not represent any Java value or object').
5371
5372exc_desc(jpl_set_static,multiple_matches(field,Fname),
5373 jpl_set/3,
5374 existence_error(field,Fname),
5375 'more than one public static field of the class has this name (this should not happen)(?)').
5376
5378
5379exc_desc(jpl_set_array,not_all_values_assignable(T,Ds),
5380 jpl_set/3,
5381 type_error(array(T),Ds),
5382 'not all values are assignable to the array element type').
5383
5384exc_desc(jpl_set_array,not_all_values_convertible(T,Ds),
5385 jpl_set/3,
5386 type_error(array(T),Ds),
5387 'not all values are convertible to Java values or references').
5388
5389exc_desc(jpl_set_array,element_type_unknown(array_element_type,T),
5390 jpl_set/3,
5391 type_error(array_element_type,T),
5392 'array element type is unknown: neither a class, nor an array type, nor a primitive type').
5393
5395
5396exc_desc(jpl_datum_to_type,is_cyclic(Term),
5397 jpl_call/4, 5398 type_error(acyclic,Term),
5399 'must be acyclic').
5400
5402
5403exc_desc(jpl_type_to_class,arg1_is_var,
5404 jpl_type_to_class/2,
5405 instantiation_error,
5406 '1st arg must be bound to a JPL type').
5407
5409
5410exc_desc(check_lib,lib_not_found(Name,Msg),
5411 check_lib/2,
5412 existence_error(library,Name),
5413 Msg).
5414
5415
5416 5419
5420:- initialization(setup_jvm, now).