2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
% redefines stuff in prolog module.
|
2005-03-13 06:26:13 +00:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
:- module(swi, []).
|
|
|
|
|
|
|
|
:- ensure_loaded(library(atts)).
|
2005-03-13 06:26:13 +00:00
|
|
|
|
2005-03-15 18:29:25 +00:00
|
|
|
:- use_module(library(charsio),[write_to_chars/2,read_from_chars/2]).
|
|
|
|
|
|
|
|
:- use_module(library(lists),[nth/3]).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
:- use_module(library(terms),[term_variables/2,
|
|
|
|
term_variables/3]).
|
|
|
|
|
|
|
|
:- multifile
|
|
|
|
prolog:message/3.
|
|
|
|
|
|
|
|
:- multifile
|
|
|
|
user:file_search_path/2.
|
2005-03-13 06:26:13 +00:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
:- dynamic
|
|
|
|
user:file_search_path/2.
|
2005-03-13 06:26:13 +00:00
|
|
|
|
|
|
|
user:file_search_path(swi, Home) :-
|
|
|
|
current_prolog_flag(home, Home).
|
|
|
|
user:file_search_path(foreign, swi(ArchLib)) :-
|
|
|
|
current_prolog_flag(arch, Arch),
|
|
|
|
atom_concat('lib/', Arch, ArchLib).
|
|
|
|
user:file_search_path(foreign, swi(lib)).
|
|
|
|
|
|
|
|
%
|
|
|
|
% maybe a good idea to eventually support this in YAP.
|
|
|
|
% but for now just ignore it.
|
|
|
|
%
|
2005-10-18 18:04:43 +01:00
|
|
|
:- meta_predicate prolog:volatile(:).
|
2005-03-13 06:26:13 +00:00
|
|
|
|
|
|
|
:- op(1150, fx, 'volatile').
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:volatile(P) :- var(P),
|
2005-03-13 06:26:13 +00:00
|
|
|
throw(error(instantiation_error,volatile(P))).
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:volatile(M:P) :-
|
2005-03-13 06:26:13 +00:00
|
|
|
do_volatile(P,M).
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:volatile((G1,G2)) :-
|
|
|
|
prolog:volatile(G1),
|
|
|
|
prolog:volatile(G2).
|
|
|
|
prolog:volatile(P) :-
|
2005-03-13 06:26:13 +00:00
|
|
|
do_volatile(P,_).
|
|
|
|
|
|
|
|
do_volatile(_,_).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
:- meta_predicate prolog:forall(+,:).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
|
|
|
:- load_foreign_files([yap2swi], [], swi_install).
|
|
|
|
|
|
|
|
:- use_module(library(lists)).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:absolute_file_name(jar(File), _Opts, Path) :- !,
|
2004-09-07 18:10:43 +01:00
|
|
|
absolute_file_name(library(File), Path).
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:absolute_file_name(library(File), _Opts, Path) :- !,
|
2004-09-07 18:10:43 +01:00
|
|
|
absolute_file_name(library(File), Path).
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:absolute_file_name(File, _Opts, Path) :-
|
2004-09-07 18:10:43 +01:00
|
|
|
absolute_file_name(File, Path).
|
|
|
|
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:term_to_atom(Term,Atom) :-
|
2005-03-15 18:29:25 +00:00
|
|
|
nonvar(Atom), !,
|
|
|
|
atom_codes(Atom,S),
|
|
|
|
read_from_chars(S,Term).
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:term_to_atom(Term,Atom) :-
|
2005-03-15 18:29:25 +00:00
|
|
|
write_to_chars(Term,S),
|
|
|
|
atom_codes(Atom,S).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:concat_atom(List, Separator, New) :-
|
2004-09-07 18:10:43 +01:00
|
|
|
add_separator_to_list(List, Separator, NewList),
|
|
|
|
atomic_concat(NewList, New).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:concat_atom(List, New) :-
|
2004-09-07 18:10:43 +01:00
|
|
|
atomic_concat(List, New).
|
|
|
|
|
|
|
|
add_separator_to_list([], _, []).
|
|
|
|
add_separator_to_list([T], _, [T]) :- !.
|
|
|
|
add_separator_to_list([H|T], Separator, [H,Separator|NT]) :-
|
|
|
|
add_separator_to_list(T, Separator, NT).
|
|
|
|
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:setenv(X,Y) :- unix(putenv(X,Y)).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:nth1(I,L,A) :- nth(I,L,A).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:forall(X,Y) :-
|
2004-09-07 18:10:43 +01:00
|
|
|
catch(do_forall(X,Y), fail_forall, fail).
|
|
|
|
|
|
|
|
do_forall(X,Y) :-
|
|
|
|
call(X),
|
|
|
|
do_for_forall(Y).
|
|
|
|
do_forall(_,_).
|
|
|
|
|
|
|
|
do_for_forall(Y) :- call(Y), !, fail.
|
2005-04-10 05:01:15 +01:00
|
|
|
do_for_forall(_) :- throw(fail_forall).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:between(I,_,I).
|
|
|
|
prolog:between(I0,I,J) :- I0 < I,
|
2004-09-07 18:10:43 +01:00
|
|
|
I1 is I0+1,
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:between(I1,I,J).
|
2004-09-07 18:10:43 +01:00
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:b_getval(GlobalVariable,Value) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
array_element(GlobalVariable,0,Value).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:b_setval(GlobalVariable,Value) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
array(GlobalVariable,1),
|
|
|
|
update_array(GlobalVariable,0,Value).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:nb_getval(GlobalVariable,Value) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
array_element(GlobalVariable,0,Value).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:nb_setval(GlobalVariable,Value) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
static_array(GlobalVariable,1,term),
|
|
|
|
update_array(GlobalVariable,0,Value).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:nb_delete(GlobalVariable) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
close_static_array(GlobalVariable).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
prolog:nb_current(GlobalVariable,Val) :-
|
2005-09-22 04:26:13 +01:00
|
|
|
static_array_properties(GlobalVariable,1,term),
|
|
|
|
array_element(GlobalVariable,0,Val).
|
|
|
|
|
2005-10-18 18:04:43 +01:00
|
|
|
% SWI has a dynamic attribute scheme
|
|
|
|
|
|
|
|
prolog:get_attr(Var, Mod, Att) :-
|
|
|
|
AttTerm =.. [Mod,_,Att],
|
|
|
|
attributes:get_module_atts(Var, AttTerm).
|
|
|
|
|
|
|
|
prolog:put_attr(Var, Mod, Att) :-
|
|
|
|
AttTerm =.. [Mod,_,Att],
|
|
|
|
attributes:put_module_atts(Var, AttTerm).
|
|
|
|
|
|
|
|
prolog:del_attr(Var, Mod) :-
|
|
|
|
AttTerm =.. [Mod,_,_],
|
|
|
|
attributes:del_all_module_atts(Var, AttTerm).
|
|
|
|
|
|
|
|
prolog:get_attrs(Var, SWIAtts) :-
|
|
|
|
get_all_swi_atts(AttVar,SWIAtts).
|
|
|
|
|
|
|
|
prolog:put_attrs(_, []).
|
|
|
|
prolog:put_attrs(V, att(Mod,Att,Atts)) :-
|
|
|
|
prolog:put_attr(V,Mod,Att),
|
|
|
|
prolog:put_attrs(V, Atts).
|
|
|
|
|
|
|
|
bindings_message(V) -->
|
|
|
|
{ cvt_bindings(V, Bindings) },
|
|
|
|
prolog:message(query(YesNo,Bindings)), !.
|
|
|
|
|
|
|
|
cvt_bindings([],[]).
|
|
|
|
cvt_bindings([[Name|Value]|L],[AName=Value|Bindings]) :-
|
|
|
|
atom_codes(AName, Name),
|
|
|
|
cvt_bindings(L,Bindings).
|
|
|
|
|
|
|
|
'$messages':prolog_message(_,L,L).
|
|
|
|
|
|
|
|
prolog:append([],L,L).
|
|
|
|
prolog:append([X|L0],L,[X|Lf]) :-
|
|
|
|
prolog:append(L0,L,Lf).
|
|
|
|
|
|
|
|
tv(Term,List) :- term_variables(Term,List).
|
|
|
|
|
|
|
|
prolog:term_variables(Term,List) :- tv(Term,List).
|
|
|
|
|
|
|
|
tv(Term,List,Tail) :- term_variables(Term,List,Tail).
|
|
|
|
|
|
|
|
prolog:term_variables(Term,List,Tail) :- tv(Term,List,Tail).
|
|
|
|
|