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