fix to thread support.
This commit is contained in:
@@ -26,6 +26,7 @@ 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)).
|
||||
@@ -52,6 +53,7 @@ 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)).
|
||||
@@ -169,9 +171,14 @@ 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)).
|
||||
@@ -179,6 +186,7 @@ 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)).
|
||||
@@ -188,16 +196,11 @@ 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(suffix,2,lists,library(lists)).
|
||||
index(sumlist,2,lists,library(lists)).
|
||||
index(list_concat,2,lists,library(lists)).
|
||||
index(flatten,2,lists,library(lists)).
|
||||
index(max_list,2,lists,library(lists)).
|
||||
index(min_list,2,lists,library(lists)).
|
||||
index(numlist,3,lists,library(lists)).
|
||||
index(intersection,3,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)).
|
||||
@@ -232,6 +235,8 @@ 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)).
|
||||
@@ -335,14 +340,12 @@ 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,readutil,library(readutil)).
|
||||
index(read_line_to_codes,3,readutil,library(readutil)).
|
||||
index(read_stream_to_codes,2,readutil,library(readutil)).
|
||||
index(read_stream_to_codes,3,readutil,library(readutil)).
|
||||
index(read_file_to_codes,2,readutil,library(readutil)).
|
||||
index(read_file_to_codes,3,readutil,library(readutil)).
|
||||
index(read_file_to_terms,2,readutil,library(readutil)).
|
||||
index(read_file_to_terms,3,readutil,library(readutil)).
|
||||
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)).
|
||||
@@ -380,6 +383,7 @@ 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)).
|
||||
@@ -390,7 +394,6 @@ 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(acyclic_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)).
|
||||
|
@@ -96,9 +96,7 @@ DIALECT_PROGRAMS= \
|
||||
|
||||
DIALECT_SWI= \
|
||||
$(srcdir)/dialect/swi/INDEX.pl \
|
||||
$(srcdir)/dialect/swi/listing.pl \
|
||||
$(srcdir)/dialect/swi/readutil.pl
|
||||
|
||||
$(srcdir)/dialect/swi/listing.pl
|
||||
|
||||
install: $(PROGRAMS) install_myddas
|
||||
mkdir -p $(DESTDIR)$(SHAREDIR)/Yap
|
||||
|
@@ -64,8 +64,7 @@
|
||||
[datime/1,
|
||||
mktime/2,
|
||||
file_property/2,
|
||||
delete_file/1,
|
||||
sleep/1]).
|
||||
delete_file/1]).
|
||||
|
||||
:- reexport(library(arg),
|
||||
[genarg/3]).
|
||||
@@ -104,19 +103,6 @@ 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)).
|
||||
|
||||
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)).
|
||||
|
||||
% make sure we also use
|
||||
:- user:library_directory(X),
|
||||
|
@@ -30,7 +30,7 @@ index(partition,5,system,library(dialect/swi)).
|
||||
index(datime,1,system,library(dialect/swi)).
|
||||
index(mktime,2,system,library(dialect/swi)).
|
||||
index(file_property,2,system,library(dialect/swi)).
|
||||
index(sleep,1,system,library(dialect/swi)).
|
||||
index(delete_file,1,system,library(dialect/swi)).
|
||||
index(genarg,3,system,library(dialect/swi)).
|
||||
index(subsumes,2,system,library(dialect/swi)).
|
||||
index(subsumes_chk,2,system,library(dialect/swi)).
|
||||
@@ -41,17 +41,20 @@ index(variant,2,system,library(dialect/swi)).
|
||||
index(concat_atom,2,system,library(dialect/swi)).
|
||||
index(concat_atom,3,system,library(dialect/swi)).
|
||||
index(setenv,2,system,library(dialect/swi)).
|
||||
index(prolog_to_os_filename,2,system,library(dialect/swi)).
|
||||
index(is_absolute_file_name,1,system,library(dialect/swi)).
|
||||
index(read_clause,1,system,library(dialect/swi)).
|
||||
index(string,1,system,library(dialect/swi)).
|
||||
index(working_directory,2,system,library(dialect/swi)).
|
||||
index(chdir,1,system,library(dialect/swi)).
|
||||
index(compile_aux_clauses,1,system,library(dialect/swi)).
|
||||
index(convert_time,2,system,library(dialect/swi)).
|
||||
index('$set_source_module',2,system,library(dialect/swi)).
|
||||
index('$declare_module',5,system,library(dialect/swi)).
|
||||
index('$set_predicate_attribute',3,system,library(dialect/swi)).
|
||||
index(stamp_date_time,3,system,library(dialect/swi)).
|
||||
index(date_time_stamp,2,system,library(dialect/swi)).
|
||||
index(format_time,3,system,library(dialect/swi)).
|
||||
index(format_time,4,system,library(dialect/swi)).
|
||||
index(time_file,2,system,library(dialect/swi)).
|
||||
index(flag,3,system,library(dialect/swi)).
|
||||
index(require,1,system,library(dialect/swi)).
|
||||
index(normalize_space,2,system,library(dialect/swi)).
|
||||
index(current_flag,1,system,library(dialect/swi)).
|
||||
|
@@ -98,6 +98,9 @@ PL_unify_blob(term_t t, void *blob, size_t len, PL_blob_t *type)
|
||||
if (!ae) {
|
||||
return FALSE;
|
||||
}
|
||||
if (type->acquire) {
|
||||
type->acquire(AtomToSWIAtom(AbsAtom(ae)));
|
||||
}
|
||||
return Yap_unify(Yap_GetFromSlot(t PASS_REGS), MkAtomTerm(AbsAtom(ae)));
|
||||
}
|
||||
|
||||
|
@@ -1360,38 +1360,6 @@ X_API int PL_unify_wchars(term_t t, int type, size_t len, const pl_wchar_t *char
|
||||
return YAP_Unify(Yap_GetFromSlot(t PASS_REGS), chterm);
|
||||
}
|
||||
|
||||
/* SWI: int PL_unify_wchars(term_t ?t, int type, size_t len,, const pl_wchar_t *s)
|
||||
*/
|
||||
X_API int PL_unify_wchars_diff(term_t t, term_t tail, int type, size_t len, const pl_wchar_t *chars)
|
||||
{
|
||||
CACHE_REGS
|
||||
YAP_Term chterm;
|
||||
|
||||
if (tail == 0)
|
||||
return PL_unify_wchars(t, type, len, chars);
|
||||
if (Unsigned(H) > Unsigned(ASP)-CreepFlag) {
|
||||
if (!Yap_gc(0, ENV, CP)) {
|
||||
return FALSE;
|
||||
}
|
||||
}
|
||||
if (len == (size_t)-1)
|
||||
len = wcslen(chars);
|
||||
|
||||
switch (type) {
|
||||
case PL_CODE_LIST:
|
||||
chterm = YAP_NWideBufferToDiffList(chars, Yap_GetFromSlot(tail PASS_REGS), len);
|
||||
break;
|
||||
case PL_CHAR_LIST:
|
||||
chterm = YAP_NWideBufferToAtomDiffList(chars, Yap_GetFromSlot(tail PASS_REGS), len);
|
||||
break;
|
||||
default:
|
||||
fprintf(stderr,"NOT GOOD option %d PL_unify_chars_wdiff\n",type);
|
||||
/* should give error?? */
|
||||
return FALSE;
|
||||
}
|
||||
return YAP_Unify(Yap_GetFromSlot(t PASS_REGS), chterm);
|
||||
}
|
||||
|
||||
typedef struct {
|
||||
int type;
|
||||
union {
|
||||
@@ -2528,7 +2496,7 @@ X_API int
|
||||
PL_destroy_engine(PL_engine_t e)
|
||||
{
|
||||
#if THREADS
|
||||
return YAP_ThreadDestroyEngine((struct worker_local *)e-Yap_WLocal);
|
||||
return YAP_ThreadDestroyEngine(((struct worker_local *)e)->thread_handle.current_yaam_regs->worker_id_);
|
||||
#else
|
||||
return FALSE;
|
||||
#endif
|
||||
@@ -2542,7 +2510,7 @@ PL_set_engine(PL_engine_t engine, PL_engine_t *old)
|
||||
int cwid = PL_thread_self(), nwid;
|
||||
|
||||
if (cwid >= 0) {
|
||||
if (old) *old = (PL_engine_t)(Yap_WLocal+cwid);
|
||||
if (old) *old = (PL_engine_t)(Yap_WLocal[cwid]);
|
||||
}
|
||||
if (!engine) {
|
||||
if (cwid < 0)
|
||||
@@ -2561,7 +2529,7 @@ PL_set_engine(PL_engine_t engine, PL_engine_t *old)
|
||||
}
|
||||
return PL_ENGINE_SET;
|
||||
} else {
|
||||
nwid = (struct worker_local *)engine-Yap_WLocal;
|
||||
nwid = ((struct worker_local *)engine)->thread_handle.current_yaam_regs->worker_id_;
|
||||
}
|
||||
|
||||
pthread_mutex_lock(&(FOREIGN_ThreadHandle(nwid).tlock));
|
||||
@@ -2779,6 +2747,8 @@ PL_query(int query)
|
||||
return (intptr_t)Yap_argv;
|
||||
case PL_QUERY_USER_CPU:
|
||||
return (intptr_t)Yap_cputime();
|
||||
case PL_QUERY_VERSION:
|
||||
return (intptr_t)600301;
|
||||
default:
|
||||
fprintf(stderr,"Unimplemented PL_query %d\n",query);
|
||||
return (intptr_t)0;
|
||||
@@ -3002,6 +2972,10 @@ term_t Yap_CvtTerm(term_t ts)
|
||||
default:
|
||||
return ts;
|
||||
}
|
||||
} else if (f == FunctorDBRef) {
|
||||
Term ta[0];
|
||||
ta[0] = MkIntegerTerm(DBRefOfTerm(t));
|
||||
return Yap_InitSlot(Yap_MkApplTerm(FunctorDBREF, 1, ta) PASS_REGS);
|
||||
}
|
||||
}
|
||||
}
|
||||
|
@@ -1,242 +0,0 @@
|
||||
/* $Id$
|
||||
|
||||
Part of SWI-Prolog
|
||||
|
||||
Author: Jan Wielemaker
|
||||
E-mail: jan@swi.psy.uva.nl
|
||||
WWW: http://www.swi-prolog.org
|
||||
Copyright (C): 1985-2002, University of Amsterdam
|
||||
|
||||
This program is free software; you can redistribute it and/or
|
||||
modify it under the terms of the GNU General Public License
|
||||
as published by the Free Software Foundation; either version 2
|
||||
of the License, or (at your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful,
|
||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
GNU General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU Lesser General Public
|
||||
License along with this library; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
|
||||
As a special exception, if you link this library with other files,
|
||||
compiled with a Free Software compiler, to produce an executable, this
|
||||
library does not by itself cause the resulting executable to be covered
|
||||
by the GNU General Public License. This exception does not however
|
||||
invalidate any other reasons why the executable file might be covered by
|
||||
the GNU General Public License.
|
||||
*/
|
||||
|
||||
:- module(read_util,
|
||||
[ read_line_to_codes/2, % +Fd, -Codes (without trailing \n)
|
||||
read_line_to_codes/3, % +Fd, -Codes, ?Tail
|
||||
read_stream_to_codes/2, % +Fd, -Codes
|
||||
read_stream_to_codes/3, % +Fd, -Codes, ?Tail
|
||||
read_file_to_codes/3, % +File, -Codes, +Options
|
||||
read_file_to_terms/3 % +File, -Terms, +Options
|
||||
]).
|
||||
:- use_module(library(shlib)).
|
||||
:- use_module(library(lists), [select/3]).
|
||||
:- use_module(library(error)).
|
||||
|
||||
/** <module> Read utilities
|
||||
|
||||
This library provides some commonly used reading predicates. As these
|
||||
predicates have proven to be time-critical in some applications we moved
|
||||
them to C. For compatibility as well as to reduce system dependency, we
|
||||
link the foreign code at runtime and fallback to the Prolog
|
||||
implementation if the shared object cannot be found.
|
||||
*/
|
||||
|
||||
:- volatile
|
||||
read_line_to_codes/2,
|
||||
read_line_to_codes/3,
|
||||
read_stream_to_codes/2,
|
||||
read_stream_to_codes/3.
|
||||
|
||||
link_foreign :-
|
||||
catch(load_foreign_library(foreign(readutil)), _, fail), !.
|
||||
link_foreign :-
|
||||
assertz((read_line_to_codes(Stream, Line) :-
|
||||
pl_read_line_to_codes(Stream, Line))),
|
||||
assertz((read_line_to_codes(Stream, Line, Tail) :-
|
||||
pl_read_line_to_codes(Stream, Line, Tail))),
|
||||
assertz((read_stream_to_codes(Stream, Content) :-
|
||||
pl_read_stream_to_codes(Stream, Content))),
|
||||
assertz((read_stream_to_codes(Stream, Content, Tail) :-
|
||||
pl_read_stream_to_codes(Stream, Content, Tail))),
|
||||
compile_predicates([ read_line_to_codes/2,
|
||||
read_line_to_codes/3,
|
||||
read_stream_to_codes/2,
|
||||
read_stream_to_codes/3
|
||||
]).
|
||||
|
||||
:- initialization(link_foreign, now).
|
||||
|
||||
|
||||
/*******************************
|
||||
* LINES *
|
||||
*******************************/
|
||||
|
||||
%% read_line_to_codes(+In:stream, -Line:codes) is det.
|
||||
%
|
||||
% Read a line of input from In into a list of character codes.
|
||||
% Trailing newline and or return are deleted. Upon reaching
|
||||
% end-of-file Line is unified to the atom =end_of_file=.
|
||||
|
||||
pl_read_line_to_codes(Fd, Codes) :-
|
||||
get_code(Fd, C0),
|
||||
( C0 == -1
|
||||
-> Codes = end_of_file
|
||||
; read_1line_to_codes(C0, Fd, Codes0)
|
||||
),
|
||||
Codes = Codes0.
|
||||
|
||||
read_1line_to_codes(-1, _, []) :- !.
|
||||
read_1line_to_codes(10, _, []) :- !.
|
||||
read_1line_to_codes(13, Fd, L) :- !,
|
||||
get_code(Fd, C2),
|
||||
read_1line_to_codes(C2, Fd, L).
|
||||
read_1line_to_codes(C, Fd, [C|T]) :-
|
||||
get_code(Fd, C2),
|
||||
read_1line_to_codes(C2, Fd, T).
|
||||
|
||||
%% read_line_to_codes(+Fd, -Line, ?Tail) is det.
|
||||
%
|
||||
% Read a line of input as a difference list. This should be used
|
||||
% to read multiple lines efficiently. On reaching end-of-file,
|
||||
% Tail is bound to the empty list.
|
||||
|
||||
pl_read_line_to_codes(Fd, Codes, Tail) :-
|
||||
get_code(Fd, C0),
|
||||
read_line_to_codes(C0, Fd, Codes0, Tail),
|
||||
Codes = Codes0.
|
||||
|
||||
read_line_to_codes(-1, _, Tail, Tail) :- !,
|
||||
Tail = [].
|
||||
read_line_to_codes(10, _, [10|Tail], Tail) :- !.
|
||||
read_line_to_codes(C, Fd, [C|T], Tail) :-
|
||||
get_code(Fd, C2),
|
||||
read_line_to_codes(C2, Fd, T, Tail).
|
||||
|
||||
|
||||
/*******************************
|
||||
* STREAM (ENTIRE INPUT) *
|
||||
*******************************/
|
||||
|
||||
%% read_stream_to_codes(+Stream, -Codes) is det.
|
||||
%% read_stream_to_codes(+Stream, -Codes, ?Tail) is det.
|
||||
%
|
||||
% Read input from Stream to a list of character codes. The version
|
||||
% read_stream_to_codes/3 creates a difference-list.
|
||||
|
||||
pl_read_stream_to_codes(Fd, Codes) :-
|
||||
pl_read_stream_to_codes(Fd, Codes, []).
|
||||
pl_read_stream_to_codes(Fd, Codes, Tail) :-
|
||||
get_code(Fd, C0),
|
||||
read_stream_to_codes(C0, Fd, Codes0, Tail),
|
||||
Codes = Codes0.
|
||||
|
||||
read_stream_to_codes(-1, _, Tail, Tail) :- !.
|
||||
read_stream_to_codes(C, Fd, [C|T], Tail) :-
|
||||
get_code(Fd, C2),
|
||||
read_stream_to_codes(C2, Fd, T, Tail).
|
||||
|
||||
|
||||
%% read_stream_to_terms(+Stream, -Terms, ?Tail, +Options) is det.
|
||||
|
||||
read_stream_to_terms(Fd, Terms, Tail, Options) :-
|
||||
read_term(Fd, C0, Options),
|
||||
read_stream_to_terms(C0, Fd, Terms0, Tail, Options),
|
||||
Terms = Terms0.
|
||||
|
||||
read_stream_to_terms(end_of_file, _, Tail, Tail, _) :- !.
|
||||
read_stream_to_terms(C, Fd, [C|T], Tail, Options) :-
|
||||
read_term(Fd, C2, Options),
|
||||
read_stream_to_terms(C2, Fd, T, Tail, Options).
|
||||
|
||||
|
||||
/*******************************
|
||||
* FILE (ENTIRE INPUT) *
|
||||
*******************************/
|
||||
|
||||
%% read_file_to_codes(+Spec, -Codes, +Options) is det.
|
||||
%
|
||||
% Read the file Spec into a list of Codes. Options is split into
|
||||
% options for absolute_file_name/3 and open/4.
|
||||
|
||||
read_file_to_codes(Spec, Codes, Options) :-
|
||||
must_be(proper_list, Options),
|
||||
( select(tail(Tail), Options, Options1)
|
||||
-> true
|
||||
; Tail = [],
|
||||
Options1 = Options
|
||||
),
|
||||
split_options(Options1, file_option, FileOptions, OpenOptions),
|
||||
absolute_file_name(Spec,
|
||||
[ access(read)
|
||||
| FileOptions
|
||||
],
|
||||
Path),
|
||||
open(Path, read, Fd, OpenOptions),
|
||||
call_cleanup(read_stream_to_codes(Fd, Codes0, Tail),
|
||||
close(Fd)),
|
||||
Codes = Codes0.
|
||||
|
||||
|
||||
%% read_file_to_terms(+Spec, -Terms, +Options) is det.
|
||||
%
|
||||
% Read the file Spec into a list of terms. Options is split over
|
||||
% absolute_file_name/3, open/4 and read_term/3.
|
||||
|
||||
read_file_to_terms(Spec, Terms, Options) :-
|
||||
must_be(proper_list, Options),
|
||||
( select(tail(Tail), Options, Options1)
|
||||
-> true
|
||||
; Tail = [],
|
||||
Options1 = Options
|
||||
),
|
||||
split_options(Options1, file_option, FileOptions, Options2),
|
||||
split_options(Options2, read_option, ReadOptions, OpenOptions),
|
||||
absolute_file_name(Spec,
|
||||
[ access(read)
|
||||
| FileOptions
|
||||
],
|
||||
Path),
|
||||
open(Path, read, Fd, OpenOptions),
|
||||
call_cleanup(read_stream_to_terms(Fd, Terms0, Tail, ReadOptions),
|
||||
close(Fd)),
|
||||
Terms = Terms0.
|
||||
|
||||
split_options([], _, [], []).
|
||||
split_options([H|T], G, File, Open) :-
|
||||
( call(G, H)
|
||||
-> File = [H|FT],
|
||||
OT = Open
|
||||
; Open = [H|OT],
|
||||
FT = File
|
||||
),
|
||||
split_options(T, G, FT, OT).
|
||||
|
||||
|
||||
read_option(module(_)).
|
||||
read_option(syntax_errors(_)).
|
||||
read_option(character_escapes(_)).
|
||||
read_option(double_quotes(_)).
|
||||
read_option(backquoted_string(_)).
|
||||
|
||||
file_option(extensions(_)).
|
||||
file_option(file_type(_)).
|
||||
file_option(file_errors(_)).
|
||||
file_option(relative_to(_)).
|
||||
file_option(expand(_)).
|
||||
|
||||
/*******************************
|
||||
* XREF *
|
||||
*******************************/
|
||||
|
||||
:- multifile prolog:meta_goal/2.
|
||||
:- dynamic prolog:meta_goal/2.
|
||||
prolog:meta_goal(split_options(_,G,_,_), [G+1]).
|
@@ -88,79 +88,6 @@ check_int(I, Inp) :-
|
||||
|
||||
% file operations
|
||||
|
||||
delete_file(IFile) :-
|
||||
true_file_name(IFile, File),
|
||||
delete_file(File, off, on, off).
|
||||
|
||||
delete_file(IFile, Opts) :-
|
||||
true_file_name(IFile, File),
|
||||
process_delete_file_opts(Opts, Dir, Recurse, Ignore, delete_file(File,Opts)),
|
||||
delete_file(File, Dir, Recurse, Ignore).
|
||||
|
||||
process_delete_file_opts(V, _, _, _, T) :- var(V), !,
|
||||
throw(error(instantiation_error,T)).
|
||||
process_delete_file_opts([], off, off, off, _) :- !.
|
||||
process_delete_file_opts([V|_], _, _, _, T) :- var(V), !,
|
||||
throw(error(instantiation_error,T)).
|
||||
process_delete_file_opts([directory|Opts], on, Recurse, Ignore, T) :- !,
|
||||
process_delete_file_opts(Opts, _, Recurse, Ignore, T).
|
||||
process_delete_file_opts([recursive|Opts], Dir, on, Ignore, T) :- !,
|
||||
process_delete_file_opts(Opts, Dir, _, Ignore, T).
|
||||
process_delete_file_opts([ignore|Opts], Dir, Recurse, on, T) :- !,
|
||||
process_delete_file_opts(Opts, Dir, Recurse, _, T).
|
||||
process_delete_file_opts(Opts, _, _, _, T) :-
|
||||
throw(error(domain_error(delete_file_option,Opts),T)).
|
||||
|
||||
delete_file(IFile, Dir, Recurse, Ignore) :-
|
||||
true_file_name(IFile, File),
|
||||
file_property(File, Type, _, _, _Permissions, _, Ignore),
|
||||
delete_file(Type, File, Dir, Recurse, Ignore).
|
||||
|
||||
delete_file(N, File, _Dir, _Recurse, Ignore) :- number(N), !, % error.
|
||||
handle_system_error(N, Ignore, delete_file(File)).
|
||||
delete_file(directory, File, Dir, Recurse, Ignore) :-
|
||||
delete_directory(Dir, File, Recurse, Ignore).
|
||||
delete_file(_, File, _Dir, _Recurse, Ignore) :-
|
||||
unlink_file(File, Ignore).
|
||||
|
||||
unlink_file(IFile, Ignore) :-
|
||||
true_file_name(IFile, File),
|
||||
unlink(File, N),
|
||||
handle_system_error(N, Ignore, delete_file(File)).
|
||||
|
||||
delete_directory(on, File, _Recurse, Ignore) :-
|
||||
rm_directory(File, Ignore).
|
||||
delete_directory(off, File, Recurse, Ignore) :-
|
||||
delete_directory(Recurse, File, Ignore).
|
||||
|
||||
rm_directory(File, Ignore) :-
|
||||
rmdir(File, Error),
|
||||
handle_system_error(Error, Ignore, delete_file(File)).
|
||||
|
||||
delete_directory(on, File, Ignore) :-
|
||||
directory_files(File, FileList, Ignore),
|
||||
path_separator(D),
|
||||
atom_concat(File, D, FileP),
|
||||
delete_dirfiles(FileList, FileP, Ignore),
|
||||
rmdir(File, Ignore).
|
||||
|
||||
delete_dirfiles([], _, _).
|
||||
delete_dirfiles(['.'|Fs], File, Ignore) :- !,
|
||||
delete_dirfiles(Fs, File, Ignore).
|
||||
delete_dirfiles(['..'|Fs], File, Ignore) :- !,
|
||||
delete_dirfiles(Fs, File, Ignore).
|
||||
delete_dirfiles([F|Fs], File, Ignore) :-
|
||||
atom_concat(File,F,TrueF),
|
||||
delete_file(TrueF, off, on, Ignore),
|
||||
delete_dirfiles(Fs, File, Ignore).
|
||||
|
||||
directory_files(IFile, FileList) :-
|
||||
true_file_name(IFile, File),
|
||||
directory_files(File, FileList, off).
|
||||
|
||||
directory_files(File, FileList, Ignore) :-
|
||||
list_directory(File, FileList, Error),
|
||||
handle_system_error(Error, Ignore, directory_files(File, FileList)).
|
||||
|
||||
handle_system_error(Error, _Ignore, _G) :- var(Error), !.
|
||||
handle_system_error(Error, off, G) :- atom(Error), !,
|
||||
@@ -216,29 +143,6 @@ file_exists(IFile, Permissions) :-
|
||||
|
||||
process_permissions(Number, Number) :- integer(Number).
|
||||
|
||||
make_directory(Dir) :-
|
||||
var(Dir), !,
|
||||
throw(error(instantiation_error,mkdir(Dir))).
|
||||
make_directory(IDir) :-
|
||||
atom(IDir), !,
|
||||
true_file_name(IDir, Dir),
|
||||
mkdir(Dir,Error),
|
||||
handle_system_error(Error, off, mkdir(IDir)).
|
||||
make_directory(Dir) :-
|
||||
throw(error(type_error(atom,Dir),make_directory(Dir))).
|
||||
|
||||
rename_file(IOld, New) :-
|
||||
atom(IOld), atom(New), !,
|
||||
true_file_name(IOld,Old),
|
||||
rename_file(Old, New, Error),
|
||||
handle_system_error(Error, off, rename_file(Old, New)).
|
||||
rename_file(X,Y) :- (var(X) ; var(Y)), !,
|
||||
throw(error(instantiation_error,rename_file(X,Y))).
|
||||
rename_file(X,Y) :- atom(X), !,
|
||||
throw(error(type_error(atom,Y),rename_file(X,Y))).
|
||||
rename_file(X,Y) :-
|
||||
throw(error(type_error(atom,X),rename_file(X,Y))).
|
||||
|
||||
%
|
||||
% environment manipulation.
|
||||
%
|
||||
@@ -413,18 +317,6 @@ system(Command, Status) :-
|
||||
Status = 0,
|
||||
handle_system_error(Error, off, G).
|
||||
|
||||
sleep(Interval) :- var(Interval), !,
|
||||
throw(error(instantiation_error,sleep(Interval))).
|
||||
sleep(Interval) :- number(Interval), !,
|
||||
( Interval =< 0 ->
|
||||
throw(error(domain_error(not_less_than_zero,Interval),
|
||||
sleep(Interval)))
|
||||
;
|
||||
sleep(Interval, _Remainder)
|
||||
).
|
||||
sleep(Interval) :-
|
||||
throw(error(type_error(number,Interval),sleep(Interval))).
|
||||
|
||||
wait(PID,STATUS) :- var(PID), !,
|
||||
throw(error(instantiation_error,wait(PID,STATUS))).
|
||||
wait(PID,STATUS) :- integer(PID), !,
|
||||
@@ -474,28 +366,6 @@ tmpnam(X) :-
|
||||
tmpnam(X, Error),
|
||||
handle_system_error(Error, off, tmpnam(X)).
|
||||
|
||||
tmp_file(Base,X) :-
|
||||
var(Base), !,
|
||||
throw(error(instantiation_error,tmp_file(Base,X))).
|
||||
tmp_file(Base,X) :-
|
||||
atom(Base), !,
|
||||
tmpdir(Dir),
|
||||
handle_system_error(Error, off, tmp_file(Base,X)),
|
||||
pid(PID, Error),
|
||||
handle_system_error(Error, off, tmp_file(Base,X)),
|
||||
tmp_file_sequence(I),
|
||||
% path_separator(D),
|
||||
atomic_concat([Dir,yap_,Base,'_',PID,'_',I],X).
|
||||
tmp_file(Base,X) :-
|
||||
throw(error(type_error(atom,Base),tmp_file(Base,X))).
|
||||
|
||||
tmp_file_sequence(X) :-
|
||||
retract(tmp_file_sequence_counter(X)),
|
||||
X1 is X+1,
|
||||
assert(tmp_file_sequence_counter(X1)).
|
||||
tmp_file_sequence(0) :-
|
||||
assert(tmp_file_sequence_counter(1)).
|
||||
|
||||
%%% Added from Theo, path_seperator is used to replace the c predicate dir_separator which is not OS aware
|
||||
|
||||
tmpdir(TmpDir):-
|
||||
|
Reference in New Issue
Block a user