This repository has been archived on 2023-08-20. You can view files and clone it, but cannot push or open issues or pull requests.
yap-6.3/library/dialect/swi.yap

264 lines
6.2 KiB
Plaintext
Raw Normal View History

2009-07-21 04:56:54 +01:00
% SWI emulation.
% written in an on-demand basis.
2010-05-23 18:39:46 +01:00
:- module(system, [concat_atom/2,
2010-04-22 16:27:32 +01:00
concat_atom/3,
setenv/2,
read_clause/1,
string/1,
chdir/1,
compile_aux_clauses/1,
convert_time/2,
'$set_source_module'/2,
'$declare_module'/5,
'$set_predicate_attribute'/3,
2010-07-19 14:52:26 +01:00
stamp_date_time/3,
date_time_stamp/2,
format_time/3,
format_time/4,
2010-04-22 16:27:32 +01:00
time_file/2,
flag/3,
2010-07-28 23:25:12 +01:00
require/1,
2010-08-03 21:07:58 +01:00
normalize_space/2,
2010-04-22 16:27:32 +01:00
current_flag/1
]).
:- reexport(library(charsio),[
write_to_chars/2,
read_from_chars/2
]).
:- reexport(library(lists),[append/2,
append/3,
delete/3,
member/2,
flatten/2,
intersection/3,
last/2,
memberchk/2,
max_list/2,
min_list/2,
nextto/3,
permutation/2,
reverse/2,
select/3,
selectchk/3,
sublist/2,
sumlist/2,
nth1/3,
nth0/3]).
:- reexport(library(apply),[maplist/2,
maplist/3,
maplist/4,
maplist/5,
include/3,
exclude/3,
partition/4,
partition/5
]).
:- reexport(library(system),
2009-03-06 10:59:02 +00:00
[datime/1,
mktime/2,
file_property/2,
delete_file/1,
2009-03-06 10:59:02 +00:00
sleep/1]).
:- reexport(library(arg),
2009-03-06 10:59:02 +00:00
[genarg/3]).
:- reexport(library(apply_macros),
[]).
:- reexport(library(terms),
2009-03-06 10:59:02 +00:00
[subsumes/2,
subsumes_chk/2,
2009-03-06 10:59:02 +00:00
term_hash/2,
unifiable/3,
cyclic_term/1,
2009-03-06 10:59:02 +00:00
variant/2]).
2010-07-28 23:25:12 +01:00
:- use_module(library(error),[must_be/2]).
:- source.
:- style_check(all).
:- yap_flag(unknown,error).
:- yap_flag(open_expands_filename,false).
:- yap_flag(autoload,true).
:- set_prolog_flag(user_flags,silent).
% Time is given as a float in SWI-Prolog.
swi_get_time(FSecs) :- datime(Datime), mktime(Datime, Secs), FSecs is Secs*1.0.
goal_expansion(atom_concat(A,B),atomic_concat(A,B)).
goal_expansion(atom_concat(A,B,C),atomic_concat(A,B,C)).
%goal_expansion(arg(A,_,_),_) :- nonvar(A), !, fail.
goal_expansion(arg(A,B,C),genarg(A,B,C)).
goal_expansion(time_file(A,B),system:swi_time_file(A,B)).
2010-07-19 14:52:26 +01:00
goal_expansion(stamp_date_time(A,B,C),system:swi_stamp_date_time(A,B,C)).
goal_expansion(date_time_stamp(A,B),system:swi_date_time_stamp(A,B)).
goal_expansion(format_time(A,B,C),system:swi_format_time(A,B,C)).
goal_expansion(format_time(A,B,C,D),system:swi_format_time(A,B,C,D)).
goal_expansion(get_time(A),system:swi_get_time(A)).
goal_expansion(time_file(A,B),system:swi_time_file(A,B)).
goal_expansion(expand_file_name(A,B),system:swi_expand_file_name(A,B)).
goal_expansion(wildcard_match(A,B),system:swi_wilcard_match(A,B)).
goal_expansion(directory_files(A,B),system:swi_directory_files(A,B)).
goal_expansion(exists_file(A), system:swi_exists_file(A)).
goal_expansion(exists_directory(A), system:swi_exists_directory(A)).
2009-03-06 10:59:02 +00:00
% make sure we also use
:- user:library_directory(X),
atom(X),
atom_concat([X,'/dialect/swi'],SwiDir),
2009-03-06 10:59:02 +00:00
\+ user:library_directory(SwiDir),
asserta(user:library_directory(SwiDir)),
fail
;
true.
:- multifile
user:file_search_path/2.
:- dynamic
user:file_search_path/2.
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)).
concat_atom([A|List], Separator, New) :- var(List), !,
2009-03-06 10:59:02 +00:00
atom_codes(Separator,[C]),
atom_codes(New, NewChars),
split_atom_by_chars(NewChars,C,L,L,A,List).
concat_atom(List, Separator, New) :-
2009-03-06 10:59:02 +00:00
add_separator_to_list(List, Separator, NewList),
atomic_concat(NewList, New).
split_atom_by_chars([],_,[],L,A,[]):-
atom_codes(A,L).
split_atom_by_chars([C|NewChars],C,[],L,A,[NA|Atoms]) :- !,
atom_codes(A,L),
split_atom_by_chars(NewChars,C,NL,NL,NA,Atoms).
split_atom_by_chars([C1|NewChars],C,[C1|LF],LAtom,Atom,Atoms) :-
split_atom_by_chars(NewChars,C,LF,LAtom,Atom,Atoms).
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).
concat_atom(List, New) :-
atomic_concat(List, New).
2009-03-06 10:59:02 +00:00
setenv(X,Y) :- unix(putenv(X,Y)).
2009-03-06 10:59:02 +00:00
read_clause(X,Y) :-
2009-03-06 10:59:02 +00:00
read_term(X,Y,[singetons(warning)]).
string(_) :- fail.
2009-03-06 10:59:02 +00:00
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).
chdir(X) :- cd(X).
2009-03-06 10:59:02 +00:00
% Time is received as int, and converted to "..."
% ctime is a built-in.
convert_time(X,Y) :- swi:ctime(X,Y).
2009-03-06 10:59:02 +00:00
compile_aux_clauses([]).
compile_aux_clauses([(:- G)|Cls]) :-
2009-03-06 10:59:02 +00:00
prolog_load_context(module, M),
once(M:G),
compile_aux_clauses(Cls).
compile_aux_clauses([Cl|Cls]) :-
2009-03-06 10:59:02 +00:00
prolog_load_context(module, M),
assert_static(M:Cl),
compile_aux_clauses(Cls).
'$set_source_module'(Source0, SourceF) :-
prolog_load_context(module, Source0), !,
module(SourceF).
'$set_source_module'(Source0, SourceF) :-
current_module(Source0, SourceF).
2010-06-18 00:28:42 +01:00
/** '$declare_module'(+Module, +Super, +File, +Line, +Redefine) is det.
Start a new (source-)module
@param Module is the name of the module to declare
@param File is the canonical name of the file from which the module
is loaded
@param Line is the line-number of the :- module/2 directive.
@param Redefine If =true=, allow associating the module to a new file
*/
'$declare_module'(Name, Context, _, _, _) :-
add_import_module(Name, Context, start).
'$set_predicate_attribute'(_, _, _).
flag(Key, Old, New) :-
recorded(Key, Old, R), !,
(
Old \== New
->
erase(R),
recorda(Key, New, _)
;
true
).
flag(Key, 0, New) :-
functor(Key, N, Ar),
functor(K, N, Ar),
assert(flag(K)),
recorda(K, New, _).
current_flag(Key) :-
swi:flag(Key).
2010-07-28 23:25:12 +01:00
require(F) :-
must_be(list, F),
% notice that this must be used as a declaration.
prolog_load_context(module, Mod),
required_predicates(F, Mod).
required_predicates([], _).
required_predicates(F.Fs, M) :-
required_predicate(F, M),
required_predicates(Fs, M).
required_predicate(Na/Ar, M) :-
functor(G, Na, Ar),
(
predicate_property(M:G, _) ->
true
;
autoloader:find_predicate(G, _)
).