This commit is contained in:
Vitor Santos Costa
2019-01-21 01:11:42 +00:00
parent 8e2864c0cf
commit 86decdddde
35 changed files with 1041 additions and 957 deletions

View File

@@ -1,11 +1,9 @@
set (LIBRARY_PL
INDEX.pl
apply.yap
apply_macros.yap
arg.yap
assoc.yap
atts.yap
autoloader.yap
avl.yap
bhash.yap
charsio.yap

View File

@@ -1,406 +0,0 @@
index(foreach,2,aggretate,library(aggregate)).
index(aggregate,3,aggretate,library(aggregate)).
index(aggregate,4,aggretate,library(aggregate)).
index(aggregate_all,3,aggretate,library(aggregate)).
index(aggregate_all,4,aggretate,library(aggregate)).
index(free_variables,4,aggretate,library(aggregate)).
index(genarg,3,arg,library(arg)).
index(arg0,3,arg,library(arg)).
index(genarg0,3,arg,library(arg)).
index(args,3,arg,library(arg)).
index(args0,3,arg,library(arg)).
index(path_arg,3,arg,library(arg)).
index(empty_assoc,1,assoc,library(assoc)).
index(assoc_to_list,2,assoc,library(assoc)).
index(is_assoc,1,assoc,library(assoc)).
index(min_assoc,3,assoc,library(assoc)).
index(max_assoc,3,assoc,library(assoc)).
index(gen_assoc,3,assoc,library(assoc)).
index(get_assoc,3,assoc,library(assoc)).
index(get_assoc,5,assoc,library(assoc)).
index(get_next_assoc,4,assoc,library(assoc)).
index(get_prev_assoc,4,assoc,library(assoc)).
index(list_to_assoc,2,assoc,library(assoc)).
index(ord_list_to_assoc,2,assoc,library(assoc)).
index(map_assoc,2,assoc,library(assoc)).
index(map_assoc,3,assoc,library(assoc)).
index(put_assoc,4,assoc,library(assoc)).
index(del_assoc,4,assoc,library(assoc)).
index(assoc_to_keys,2,assoc,library(assoc)).
index(del_min_assoc,4,assoc,library(assoc)).
index(del_max_assoc,4,assoc,library(assoc)).
index(avl_new,1,avl,library(avl)).
index(avl_insert,4,avl,library(avl)).
index(avl_lookup,3,avl,library(avl)).
index(b_hash_new,1,b_hash,library(bhash)).
index(b_hash_new,2,b_hash,library(bhash)).
index(b_hash_new,4,b_hash,library(bhash)).
index(b_hash_lookup,3,b_hash,library(bhash)).
index(b_hash_update,3,b_hash,library(bhash)).
index(b_hash_update,4,b_hash,library(bhash)).
index(b_hash_insert_new,4,b_hash,library(bhash)).
index(b_hash_insert,4,b_hash,library(bhash)).
index(format_to_chars,3,charsio,library(charsio)).
index(format_to_chars,4,charsio,library(charsio)).
index(write_to_chars,3,charsio,library(charsio)).
index(write_to_chars,2,charsio,library(charsio)).
index(atom_to_chars,3,charsio,library(charsio)).
index(atom_to_chars,2,charsio,library(charsio)).
index(number_to_chars,3,charsio,library(charsio)).
index(number_to_chars,2,charsio,library(charsio)).
index(read_from_chars,2,charsio,library(charsio)).
index(open_chars_stream,2,charsio,library(charsio)).
index(with_output_to_chars,2,charsio,library(charsio)).
index(with_output_to_chars,3,charsio,library(charsio)).
index(with_output_to_chars,4,charsio,library(charsio)).
index(term_to_atom,2,charsio,library(charsio)).
index(chr_show_store,1,chr,library(chr)).
index(find_chr_constraint,1,chr,library(chr)).
index(chr_trace,0,chr,library(chr)).
index(chr_notrace,0,chr,library(chr)).
index(chr_leash,1,chr,library(chr)).
index(#>,2,clpfd,library(clpfd)).
index(#<,2,clpfd,library(clpfd)).
index(#>=,2,clpfd,library(clpfd)).
index(#=<,2,clpfd,library(clpfd)).
index(#=,2,clpfd,library(clpfd)).
index(#\=,2,clpfd,library(clpfd)).
index(#\,1,clpfd,library(clpfd)).
index(#<==>,2,clpfd,library(clpfd)).
index(#==>,2,clpfd,library(clpfd)).
index(#<==,2,clpfd,library(clpfd)).
index(#\/,2,clpfd,library(clpfd)).
index(#/\,2,clpfd,library(clpfd)).
index(in,2,clpfd,library(clpfd)).
index(ins,2,clpfd,library(clpfd)).
index(all_different,1,clpfd,library(clpfd)).
index(all_distinct,1,clpfd,library(clpfd)).
index(sum,3,clpfd,library(clpfd)).
index(scalar_product,4,clpfd,library(clpfd)).
index(tuples_in,2,clpfd,library(clpfd)).
index(labeling,2,clpfd,library(clpfd)).
index(label,1,clpfd,library(clpfd)).
index(indomain,1,clpfd,library(clpfd)).
index(lex_chain,1,clpfd,library(clpfd)).
index(serialized,2,clpfd,library(clpfd)).
index(global_cardinality,2,clpfd,library(clpfd)).
index(global_cardinality,3,clpfd,library(clpfd)).
index(circuit,1,clpfd,library(clpfd)).
index(element,3,clpfd,library(clpfd)).
index(automaton,3,clpfd,library(clpfd)).
index(automaton,8,clpfd,library(clpfd)).
index(transpose,2,clpfd,library(clpfd)).
index(zcompare,3,clpfd,library(clpfd)).
index(chain,2,clpfd,library(clpfd)).
index(fd_var,1,clpfd,library(clpfd)).
index(fd_inf,2,clpfd,library(clpfd)).
index(fd_sup,2,clpfd,library(clpfd)).
index(fd_size,2,clpfd,library(clpfd)).
index(fd_dom,2,clpfd,library(clpfd)).
index({},1,clpr,library(clpr)).
index(maximize,1,clpr,library(clpr)).
index(minimize,1,clpr,library(clpr)).
index(inf,2,clpr,library(clpr)).
index(inf,4,clpr,library(clpr)).
index(sup,2,clpr,library(clpr)).
index(sup,4,clpr,library(clpr)).
index(bb_inf,3,clpr,library(clpr)).
index(bb_inf,5,clpr,library(clpr)).
index(ordering,1,clpr,library(clpr)).
index(entailed,1,clpr,library(clpr)).
index(clp_type,2,clpr,library(clpr)).
index(dump,3,clpr,library(clpr)).
index(gensym,2,gensym,library(gensym)).
index(reset_gensym,1,gensym,library(gensym)).
index(reset_gensym,0,gensym,library(gensym)).
index(add_to_heap,4,heaps,library(heaps)).
index(get_from_heap,4,heaps,library(heaps)).
index(empty_heap,1,heaps,library(heaps)).
index(heap_size,2,heaps,library(heaps)).
index(heap_to_list,2,heaps,library(heaps)).
index(list_to_heap,2,heaps,library(heaps)).
index(min_of_heap,3,heaps,library(heaps)).
index(min_of_heap,5,heaps,library(heaps)).
index(jpl_get_default_jvm_opts,1,jpl,library(jpl)).
index(jpl_set_default_jvm_opts,1,jpl,library(jpl)).
index(jpl_get_actual_jvm_opts,1,jpl,library(jpl)).
index(jpl_pl_lib_version,1,jpl,library(jpl)).
index(jpl_c_lib_version,1,jpl,library(jpl)).
index(jpl_new,3,jpl,library(jpl)).
index(jpl_call,4,jpl,library(jpl)).
index(jpl_get,3,jpl,library(jpl)).
index(jpl_set,3,jpl,library(jpl)).
index(jpl_servlet_byref,3,jpl,library(jpl)).
index(jpl_servlet_byval,3,jpl,library(jpl)).
index(jpl_class_to_classname,2,jpl,library(jpl)).
index(jpl_class_to_type,2,jpl,library(jpl)).
index(jpl_classname_to_class,2,jpl,library(jpl)).
index(jpl_classname_to_type,2,jpl,library(jpl)).
index(jpl_datum_to_type,2,jpl,library(jpl)).
index(jpl_false,1,jpl,library(jpl)).
index(jpl_is_class,1,jpl,library(jpl)).
index(jpl_is_false,1,jpl,library(jpl)).
index(jpl_is_null,1,jpl,library(jpl)).
index(jpl_is_object,1,jpl,library(jpl)).
index(jpl_is_object_type,1,jpl,library(jpl)).
index(jpl_is_ref,1,jpl,library(jpl)).
index(jpl_is_true,1,jpl,library(jpl)).
index(jpl_is_type,1,jpl,library(jpl)).
index(jpl_is_void,1,jpl,library(jpl)).
index(jpl_null,1,jpl,library(jpl)).
index(jpl_object_to_class,2,jpl,library(jpl)).
index(jpl_object_to_type,2,jpl,library(jpl)).
index(jpl_primitive_type,1,jpl,library(jpl)).
index(jpl_ref_to_type,2,jpl,library(jpl)).
index(jpl_true,1,jpl,library(jpl)).
index(jpl_type_to_class,2,jpl,library(jpl)).
index(jpl_type_to_classname,2,jpl,library(jpl)).
index(jpl_void,1,jpl,library(jpl)).
index(jpl_array_to_length,2,jpl,library(jpl)).
index(jpl_array_to_list,2,jpl,library(jpl)).
index(jpl_datums_to_array,2,jpl,library(jpl)).
index(jpl_enumeration_element,2,jpl,library(jpl)).
index(jpl_enumeration_to_list,2,jpl,library(jpl)).
index(jpl_hashtable_pair,2,jpl,library(jpl)).
index(jpl_iterator_element,2,jpl,library(jpl)).
index(jpl_list_to_array,2,jpl,library(jpl)).
index(jpl_list_to_array,3,jpl,library(jpl)).
index(jpl_terms_to_array,2,jpl,library(jpl)).
index(jpl_map_element,2,jpl,library(jpl)).
index(jpl_set_element,2,jpl,library(jpl)).
index(append,3,lists,library(lists)).
index(append,2,lists,library(lists)).
index(delete,3,lists,library(lists)).
index(intersection,3,lists,library(lists)).
index(flatten,2,lists,library(lists)).
index(last,2,lists,library(lists)).
index(list_concat,2,lists,library(lists)).
index(max_list,2,lists,library(lists)).
index(member,2,lists,library(lists)).
index(memberchk,2,lists,library(lists)).
index(min_list,2,lists,library(lists)).
index(nextto,3,lists,library(lists)).
index(nth,3,lists,library(lists)).
index(nth,4,lists,library(lists)).
index(nth0,3,lists,library(lists)).
index(nth0,4,lists,library(lists)).
index(nth1,3,lists,library(lists)).
index(nth1,4,lists,library(lists)).
index(numlist,3,lists,library(lists)).
index(permutation,2,lists,library(lists)).
index(prefix,2,lists,library(lists)).
index(remove_duplicates,2,lists,library(lists)).
index(reverse,2,lists,library(lists)).
index(same_length,2,lists,library(lists)).
index(select,3,lists,library(lists)).
index(selectchk,3,lists,library(lists)).
index(sublist,2,lists,library(lists)).
index(substitute,4,lists,library(lists)).
index(subtract,3,lists,library(lists)).
index(suffix,2,lists,library(lists)).
index(sum_list,2,lists,library(lists)).
index(sum_list,3,lists,library(lists)).
index(sumlist,2,lists,library(lists)).
index(nb_queue,1,nb,library(nb)).
index(nb_queue,2,nb,library(nb)).
index(nb_queue_close,3,nb,library(nb)).
index(nb_queue_enqueue,2,nb,library(nb)).
index(nb_queue_dequeue,2,nb,library(nb)).
index(nb_queue_peek,2,nb,library(nb)).
index(nb_queue_empty,1,nb,library(nb)).
index(nb_queue_size,2,nb,library(nb)).
index(nb_heap,2,nb,library(nb)).
index(nb_heap_close,1,nb,library(nb)).
index(nb_heap_add,3,nb,library(nb)).
index(nb_heap_del,3,nb,library(nb)).
index(nb_heap_peek,3,nb,library(nb)).
index(nb_heap_empty,1,nb,library(nb)).
index(nb_heap_size,2,nb,library(nb)).
index(nb_beam,2,nb,library(nb)).
index(nb_beam_close,1,nb,library(nb)).
index(nb_beam_add,3,nb,library(nb)).
index(nb_beam_del,3,nb,library(nb)).
index(nb_beam_peek,3,nb,library(nb)).
index(nb_beam_empty,1,nb,library(nb)).
index(nb_beam_size,2,nb,library(nb)).
index(contains_term,2,occurs,library(occurs)).
index(contains_var,2,occurs,library(occurs)).
index(free_of_term,2,occurs,library(occurs)).
index(free_of_var,2,occurs,library(occurs)).
index(occurrences_of_term,3,occurs,library(occurs)).
index(occurrences_of_var,3,occurs,library(occurs)).
index(sub_term,2,occurs,library(occurs)).
index(sub_var,2,occurs,library(occurs)).
index(option,2,swi_option,library(option)).
index(option,3,swi_option,library(option)).
index(select_option,3,swi_option,library(option)).
index(select_option,4,swi_option,library(option)).
index(merge_options,3,swi_option,library(option)).
index(meta_options,3,swi_option,library(option)).
index(list_to_ord_set,2,ordsets,library(ordsets)).
index(merge,3,ordsets,library(ordsets)).
index(ord_add_element,3,ordsets,library(ordsets)).
index(ord_del_element,3,ordsets,library(ordsets)).
index(ord_disjoint,2,ordsets,library(ordsets)).
index(ord_insert,3,ordsets,library(ordsets)).
index(ord_member,2,ordsets,library(ordsets)).
index(ord_intersect,2,ordsets,library(ordsets)).
index(ord_intersect,3,ordsets,library(ordsets)).
index(ord_intersection,3,ordsets,library(ordsets)).
index(ord_intersection,4,ordsets,library(ordsets)).
index(ord_seteq,2,ordsets,library(ordsets)).
index(ord_setproduct,3,ordsets,library(ordsets)).
index(ord_subset,2,ordsets,library(ordsets)).
index(ord_subtract,3,ordsets,library(ordsets)).
index(ord_symdiff,3,ordsets,library(ordsets)).
index(ord_union,2,ordsets,library(ordsets)).
index(ord_union,3,ordsets,library(ordsets)).
index(ord_union,4,ordsets,library(ordsets)).
index(ord_empty,1,ordsets,library(ordsets)).
index(ord_memberchk,2,ordsets,library(ordsets)).
index(pairs_keys_values,3,pairs,library(pairs)).
index(pairs_values,2,pairs,library(pairs)).
index(pairs_keys,2,pairs,library(pairs)).
index(group_pairs_by_key,2,pairs,library(pairs)).
index(transpose_pairs,2,pairs,library(pairs)).
index(map_list_to_pairs,3,pairs,library(pairs)).
index(xref_source,1,prolog_xref,library(prolog_xref)).
index(xref_called,3,prolog_xref,library(prolog_xref)).
index(xref_defined,3,prolog_xref,library(prolog_xref)).
index(xref_definition_line,2,prolog_xref,library(prolog_xref)).
index(xref_exported,2,prolog_xref,library(prolog_xref)).
index(xref_module,2,prolog_xref,library(prolog_xref)).
index(xref_op,2,prolog_xref,library(prolog_xref)).
index(xref_clean,1,prolog_xref,library(prolog_xref)).
index(xref_current_source,1,prolog_xref,library(prolog_xref)).
index(xref_done,2,prolog_xref,library(prolog_xref)).
index(xref_built_in,1,prolog_xref,library(prolog_xref)).
index(xref_expand,2,prolog_xref,library(prolog_xref)).
index(xref_source_file,3,prolog_xref,library(prolog_xref)).
index(xref_source_file,4,prolog_xref,library(prolog_xref)).
index(xref_public_list,4,prolog_xref,library(prolog_xref)).
index(xref_meta,2,prolog_xref,library(prolog_xref)).
index(xref_hook,1,prolog_xref,library(prolog_xref)).
index(xref_used_class,2,prolog_xref,library(prolog_xref)).
index(xref_defined_class,3,prolog_xref,library(prolog_xref)).
index(set_test_options,1,plunit,library(plunit)).
index(begin_tests,1,plunit,library(plunit)).
index(begin_tests,2,plunit,library(plunit)).
index(end_tests,1,plunit,library(plunit)).
index(run_tests,0,plunit,library(plunit)).
index(run_tests,1,plunit,library(plunit)).
index(load_test_files,1,plunit,library(plunit)).
index(running_tests,0,plunit,library(plunit)).
index(test_report,1,plunit,library(plunit)).
index(make_queue,1,queues,library(queues)).
index(join_queue,3,queues,library(queues)).
index(list_join_queue,3,queues,library(queues)).
index(jump_queue,3,queues,library(queues)).
index(list_jump_queue,3,queues,library(queues)).
index(head_queue,2,queues,library(queues)).
index(serve_queue,3,queues,library(queues)).
index(length_queue,2,queues,library(queues)).
index(empty_queue,1,queues,library(queues)).
index(list_to_queue,2,queues,library(queues)).
index(queue_to_list,2,queues,library(queues)).
index(random,1,random,library(random)).
index(random,3,random,library(random)).
index(randseq,3,random,library(random)).
index(randset,3,random,library(random)).
index(getrand,1,random,library(random)).
index(setrand,1,random,library(random)).
index(rb_new,1,rbtrees,library(rbtrees)).
index(rb_empty,1,rbtrees,library(rbtrees)).
index(rb_lookup,3,rbtrees,library(rbtrees)).
index(rb_update,4,rbtrees,library(rbtrees)).
index(rb_update,5,rbtrees,library(rbtrees)).
index(rb_apply,4,rbtrees,library(rbtrees)).
index(rb_lookupall,3,rbtrees,library(rbtrees)).
index(rb_insert,4,rbtrees,library(rbtrees)).
index(rb_insert_new,4,rbtrees,library(rbtrees)).
index(rb_delete,3,rbtrees,library(rbtrees)).
index(rb_delete,4,rbtrees,library(rbtrees)).
index(rb_visit,2,rbtrees,library(rbtrees)).
index(rb_visit,3,rbtrees,library(rbtrees)).
index(rb_keys,2,rbtrees,library(rbtrees)).
index(rb_keys,3,rbtrees,library(rbtrees)).
index(rb_map,2,rbtrees,library(rbtrees)).
index(rb_map,3,rbtrees,library(rbtrees)).
index(rb_partial_map,4,rbtrees,library(rbtrees)).
index(rb_clone,3,rbtrees,library(rbtrees)).
index(rb_clone,4,rbtrees,library(rbtrees)).
index(rb_min,3,rbtrees,library(rbtrees)).
index(rb_max,3,rbtrees,library(rbtrees)).
index(rb_del_min,4,rbtrees,library(rbtrees)).
index(rb_del_max,4,rbtrees,library(rbtrees)).
index(rb_next,4,rbtrees,library(rbtrees)).
index(rb_previous,4,rbtrees,library(rbtrees)).
index(list_to_rbtree,2,rbtrees,library(rbtrees)).
index(ord_list_to_rbtree,2,rbtrees,library(rbtrees)).
index(is_rbtree,1,rbtrees,library(rbtrees)).
index(rb_size,2,rbtrees,library(rbtrees)).
index(rb_in,3,rbtrees,library(rbtrees)).
index(read_line_to_codes,2,read_util,library(readutil)).
index(read_line_to_codes,3,read_util,library(readutil)).
index(read_stream_to_codes,2,read_util,library(readutil)).
index(read_stream_to_codes,3,read_util,library(readutil)).
index(read_file_to_codes,3,read_util,library(readutil)).
index(read_file_to_terms,3,read_util,library(readutil)).
index(regexp,3,regexp,library(regexp)).
index(regexp,4,regexp,library(regexp)).
index(load_foreign_library,1,shlib,library(shlib)).
index(load_foreign_library,2,shlib,library(shlib)).
index(unload_foreign_library,1,shlib,library(shlib)).
index(unload_foreign_library,2,shlib,library(shlib)).
index(current_foreign_library,2,shlib,library(shlib)).
index(reload_foreign_libraries,0,shlib,library(shlib)).
index(use_foreign_library,1,shlib,library(shlib)).
index(use_foreign_library,2,shlib,library(shlib)).
index(datime,1,operating_system_support,library(system)).
index(delete_file,1,operating_system_support,library(system)).
index(delete_file,2,operating_system_support,library(system)).
index(directory_files,2,operating_system_support,library(system)).
index(environ,2,operating_system_support,library(system)).
index(exec,3,operating_system_support,library(system)).
index(file_exists,1,operating_system_support,library(system)).
index(file_exists,2,operating_system_support,library(system)).
index(file_property,2,operating_system_support,library(system)).
index(host_id,1,operating_system_support,library(system)).
index(host_name,1,operating_system_support,library(system)).
index(pid,1,operating_system_support,library(system)).
index(kill,2,operating_system_support,library(system)).
index(mktemp,2,operating_system_support,library(system)).
index(make_directory,1,operating_system_support,library(system)).
index(popen,3,operating_system_support,library(system)).
index(rename_file,2,operating_system_support,library(system)).
index(shell,0,operating_system_support,library(system)).
index(shell,1,operating_system_support,library(system)).
index(shell,2,operating_system_support,library(system)).
index(sleep,1,operating_system_support,library(system)).
index(system,0,operating_system_support,library(system)).
index(system,1,operating_system_support,library(system)).
index(system,2,operating_system_support,library(system)).
index(mktime,2,operating_system_support,library(system)).
index(tmpnam,1,operating_system_support,library(system)).
index(tmp_file,2,operating_system_support,library(system)).
index(tmpdir,1,operating_system_support,library(system)).
index(wait,2,operating_system_support,library(system)).
index(working_directory,2,operating_system_support,library(system)).
index(term_hash,2,terms,library(terms)).
index(term_hash,4,terms,library(terms)).
index(instantiated_term_hash,4,terms,library(terms)).
index(variant,2,terms,library(terms)).
index(unifiable,3,terms,library(terms)).
index(subsumes,2,terms,library(terms)).
index(subsumes_chk,2,terms,library(terms)).
index(cyclic_term,1,terms,library(terms)).
index(variable_in_term,2,terms,library(terms)).
index(variables_within_term,3,terms,library(terms)).
index(new_variables_in_term,3,terms,library(terms)).
index(time_out,3,timeout,library(timeout)).
index(get_label,3,trees,library(trees)).
index(list_to_tree,2,trees,library(trees)).
index(map_tree,3,trees,library(trees)).
index(put_label,4,trees,library(trees)).
index(tree_size,2,trees,library(trees)).
index(tree_to_list,2,trees,library(trees)).

View File

@@ -120,10 +120,7 @@ find_predicate(G,ExportingModI) :-
var(G),
index(Name,Arity,ExportingModI,File),
functor(G, Name, Arity),
ensure_file_loaded(File).
ensure_loaded(File).
:- ensure_loaded('INDEX').
ensure_file_loaded(File) :-
loaded(File), !.
ensure_file_loaded(File) :-
load_files(autoloader:File,[silent(true),if(not_loaded)]),
assert(loaded(File)).

View File

@@ -705,7 +705,7 @@ scanl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V, [VH|VT]) :-
goal_expansion(checklist(Meta, List), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -726,7 +726,7 @@ goal_expansion(checklist(Meta, List), Mod:Goal) :-
goal_expansion(maplist(Meta, List), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -747,7 +747,7 @@ goal_expansion(maplist(Meta, List), Mod:Goal) :-
goal_expansion(maplist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -768,7 +768,7 @@ goal_expansion(maplist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion(maplist(Meta, L1, L2, L3), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -789,7 +789,7 @@ goal_expansion(maplist(Meta, L1, L2, L3), Mod:Goal) :-
goal_expansion(maplist(Meta, L1, L2, L3, L4), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -810,7 +810,7 @@ goal_expansion(maplist(Meta, L1, L2, L3, L4), Mod:Goal) :-
goal_expansion(maplist(Meta, L1, L2, L3, L4, L5), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -831,7 +831,7 @@ goal_expansion(maplist(Meta, L1, L2, L3, L4, L5), Mod:Goal) :-
goal_expansion(selectlist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -854,7 +854,7 @@ goal_expansion(selectlist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion(selectlist(Meta, ListIn, ListIn1, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -877,7 +877,7 @@ goal_expansion(selectlist(Meta, ListIn, ListIn1, ListOut), Mod:Goal) :-
goal_expansion(selectlists(Meta, ListIn, ListIn1, ListOut, ListOut1), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -901,7 +901,7 @@ goal_expansion(selectlists(Meta, ListIn, ListIn1, ListOut, ListOut1), Mod:Goal)
% same as selectlist
goal_expansion(include(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -924,7 +924,7 @@ goal_expansion(include(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion(exclude(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -947,7 +947,7 @@ goal_expansion(exclude(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion(partition(Meta, ListIn, List1, List2), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -970,7 +970,7 @@ goal_expansion(partition(Meta, ListIn, List1, List2), Mod:Goal) :-
goal_expansion(partition(Meta, ListIn, List1, List2, List3), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1010,7 +1010,7 @@ goal_expansion(partition(Meta, ListIn, List1, List2, List3), Mod:Goal) :-
goal_expansion(convlist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1033,7 +1033,7 @@ goal_expansion(convlist(Meta, ListIn, ListOut), Mod:Goal) :-
goal_expansion(convlist(Meta, ListIn, ListExtra, ListOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1056,7 +1056,7 @@ goal_expansion(convlist(Meta, ListIn, ListExtra, ListOut), Mod:Goal) :-
goal_expansion(sumlist(Meta, List, AccIn, AccOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1077,7 +1077,7 @@ goal_expansion(sumlist(Meta, List, AccIn, AccOut), Mod:Goal) :-
goal_expansion(foldl(Meta, List, AccIn, AccOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1098,7 +1098,7 @@ goal_expansion(foldl(Meta, List, AccIn, AccOut), Mod:Goal) :-
goal_expansion(foldl(Meta, List1, List2, AccIn, AccOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1119,7 +1119,7 @@ goal_expansion(foldl(Meta, List1, List2, AccIn, AccOut), Mod:Goal) :-
goal_expansion(foldl(Meta, List1, List2, List3, AccIn, AccOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1140,7 +1140,7 @@ goal_expansion(foldl(Meta, List1, List2, List3, AccIn, AccOut), Mod:Goal) :-
goal_expansion(foldl2(Meta, List, AccIn, AccOut, W0, W), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1161,7 +1161,7 @@ goal_expansion(foldl2(Meta, List, AccIn, AccOut, W0, W), Mod:Goal) :-
goal_expansion(foldl2(Meta, List1, List2, AccIn, AccOut, W0, W), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1182,7 +1182,7 @@ goal_expansion(foldl2(Meta, List1, List2, AccIn, AccOut, W0, W), Mod:Goal) :-
goal_expansion(foldl2(Meta, List1, List2, List3, AccIn, AccOut, W0, W), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1203,7 +1203,7 @@ goal_expansion(foldl2(Meta, List1, List2, List3, AccIn, AccOut, W0, W), Mod:Goal
goal_expansion(foldl3(Meta, List, AccIn, AccOut, W0, W, X0, X), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1224,7 +1224,7 @@ goal_expansion(foldl3(Meta, List, AccIn, AccOut, W0, W, X0, X), Mod:Goal) :-
goal_expansion(foldl4(Meta, List, AccIn, AccOut, W0, W, X0, X, Y0, Y), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1245,7 +1245,7 @@ goal_expansion(foldl4(Meta, List, AccIn, AccOut, W0, W, X0, X, Y0, Y), Mod:Goal)
goal_expansion(mapnodes(Meta, InTerm, OutTerm), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1277,7 +1277,7 @@ goal_expansion(mapnodes(Meta, InTerm, OutTerm), Mod:Goal) :-
goal_expansion(checknodes(Meta, Term), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,
@@ -1307,7 +1307,7 @@ goal_expansion(checknodes(Meta, Term), Mod:Goal) :-
goal_expansion(sumnodes(Meta, Term, AccIn, AccOut), Mod:Goal) :-
goal_expansion_allowed,
callable(Meta),
is_callable(Meta),
prolog_load_context(module, Mod),
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
!,

View File

@@ -5,7 +5,7 @@
/* Define to 1 if you have the <openssl/ripemd.h> header file. */
#ifndef HAVE_APR_1_APR_MD5_H
#define HAVE_APR_1_APR_MD5_H 1
/* #undef HAVE_APR_1_APR_MD5_H */
#endif