upgrade JPL

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@1936 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
vsc
2007-09-27 15:25:34 +00:00
parent 5f9555baa4
commit 31ff28d3ee
70 changed files with 12020 additions and 9030 deletions

View File

@@ -917,53 +917,18 @@ bootstrap(F) :-
% Path predicates
access_file(F,Mode) :-
'$exists'(F,Mode).
'$exists'(_,none) :- !.
'$exists'(F,exists) :-
'$access'(F), !.
'$exists'(F,Mode) :-
get_value(fileerrors,V),
set_value(fileerrors,0),
( '$open'(F,Mode,S,0,1) -> '$close'(S), set_value(fileerrors,V) ; set_value(fileerrors,V), fail).
% This sequence must be followed:
% user and user_input are special;
% library(F) must check library_directories
% T(F) must check file_search_path
% all must try search in path
'$find_in_path'(user,user_input, _) :- !.
'$find_in_path'(user_input,user_input, _) :- !.
'$find_in_path'(library(File),NewFile, _) :-
'$dir_separator'(D),
atom_codes(A,[D]),
user:library_directory(Dir),
'$extend_path'(Dir, A, File, NFile, compile(library(File))),
'$search_in_path'(NFile, NewFile), !.
'$find_in_path'(S,NewFile, _) :-
S =.. [Name,File], !,
'$dir_separator'(D),
atom_codes(A,[D]),
user:file_search_path(Name, Dir),
'$extend_path'(Dir, A, File, NFile, compile(S)),
'$search_in_path'(NFile, NewFile), !.
'$find_in_path'(File,NewFile,_) :- atom(File), !,
'$search_in_path'(File,NewFile),!.
'$find_in_path'(File,_,Call) :-
'$do_error'(domain_error(source_sink,File),Call).
'$search_in_path'(New,New) :-
'$exists'(New,'$csult'), !.
'$search_in_path'(File,New) :-
recorded('$path',Path,_),
atom_concat([Path,File],New),
'$exists'(New,'$csult').
'$extend_path'(Dir, A, File, NFile, _) :-
atom(Dir), !,
atom_concat([Dir,A,File],NFile).
'$extend_path'(Name, A, File, NFile, Goal) :-
nonvar(Name),
Name =.. [_,_],
'$find_in_path'(Name, Path, Goal),
'$extend_path'(Path, A, File, NFile, Goal).
% term expansion
%
% return two arguments: Expanded0 is the term after "USER" expansion.

View File

@@ -19,7 +19,7 @@
% SWI options
% autoload(true,false)
% derived_from(File) -> make
% encoding(Enconding)
% encoding(Encoding)
% expand({true,false)
% if(changed,true,not_loaded)
% imports(all,List)
@@ -544,6 +544,208 @@ remove_from_path(New) :- '$check_path'(New,Path),
).
absolute_file_name(V,Out) :- var(V), !,
'$do_error'(instantiation_error, absolute_file_name(V, Out)).
absolute_file_name(user,user) :- !.
absolute_file_name(File0,File) :-
'$absolute_file_name'(File0,[access(read),file_type(source),file_errors(fail),solutions(first)],File,absolute_file_name(File0,File)).
'$find_in_path'(F0,F,G) :-
'$absolute_file_name'(F0,[access(read),file_type(source),file_errors(fail),solutions(first)],F,G).
absolute_file_name(File,TrueFileName,Opts) :-
var(TrueFileName), !,
absolute_file_name(File,Opts,TrueFileName).
absolute_file_name(File,Opts,TrueFileName) :-
'$absolute_file_name'(File,Opts,TrueFileName,absolute_file_name(File,Opts,TrueFileName)).
'$absolute_file_name'(File,Opts,TrueFileName,G) :- var(File), !,
'$do_error'(instantiation_error, G).
'$absolute_file_name'(File,Opts,TrueFileName, G) :-
'$process_fn_opts'(Opts,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G),
FoundOne = a(false),
(
'$find_in_path'(File,opts(Extensions,RelTo,Type,Access,FErrors,Expand,Debug),TrueFileName,G),
(Solutions = first -> ! ; true),
nb_setarg(1, FoundOne, true)
;
FErrors = error, FoundOne = a(false) ->
'$do_error'(existence_error(file,File),G)
).
'$process_fn_opts'(V,_,_,_,_,_,_,_,_,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$process_fn_opts'([],[],CWD,source,read,error,first,false,false,_) :- !,
getcwd(CWD).
'$process_fn_opts'([Opt|Opts],Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$process_fn_opt'(Opt,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions0,RelTo0,Type0,Access0,FErrors0,Solutions0,Expand0,Debug0,G),
'$process_fn_opts'(Opts,Extensions0,RelTo0,Type0,Access0,FErrors0,Solutions0,Expand0,Debug0,G).
'$process_fn_opts'(Opts,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$do_error'(type_error(list,T),G).
'$process_fn_opt'(Opt,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G) :- var(Opt), !,
'$do_error'(instantiation_error, G).
'$process_fn_opt'(extensions(Extensions),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,_,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$check_fn_extensions'(L,G).
'$process_fn_opt'(relative_to(RelTo),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,_,Type,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$check_atom'(RelTo,G).
'$process_fn_opt'(access(Access),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,_,FErrors,Solutions,Expand,Debug,G) :- !,
'$check_atom'(Access,G).
'$process_fn_opt'(file_type(Type),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,_,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$check_fn_type'(Type,G).
'$process_fn_opt'(file_errors(FErrors),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,_,Solutions,Expand,Debug,G) :- !,
'$check_fn_errors'(FErrors,G).
'$process_fn_opt'(solutions(Solutions),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,FErrors,_,Expand,Debug,G) :- !,
'$check_fn_solutions'(Solutions,G).
'$process_fn_opt'(expand(Expand),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,FErrors,Solutions,_,Debug,G) :- !,
'$check_true_false'(Expand,G).
'$process_fn_opt'(verbose_file_search(Debug),Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,_,G) :- !,
'$check_true_false'(Debug,G).
'$process_fn_opt'(Opt,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,Extensions,RelTo,Type,Access,FErrors,Solutions,Expand,Debug,G) :- !,
'$do_error'(domain_error(file_name_option,T),G).
'$check_fn_extensions'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_fn_extensions'([],_) :- !.
'$check_fn_extensions'([A|L],G) :- !,
'$check_atom'(A,G),
'$check_fn_extensions'(L,G).
'$check_fn_extensions'(T,G) :- !,
'$do_error'(type_error(list,T),G).
'$check_atom'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_atom'(A,G) :- atom(A), !.
'$check_atom'(T,G) :- !,
'$do_error'(type_error(atom,T),G).
'$check_fn_type'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_fn_type'(txt,_) :- !.
'$check_fn_type'(prolog,_) :- !.
'$check_fn_type'(source,_) :- !.
'$check_fn_type'(executable,_) :- !.
'$check_fn_type'(qlf,_) :- !.
'$check_fn_type'(directory,_) :- !.
'$check_fn_type'(T,G) :- atom(T), !,
'$do_error'(domain_error(file_type,T),G).
'$check_fn_type'(T,G) :- !,
'$do_error'(type_error(atom,T),G).
'$check_fn_errors'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_fn_errors'(fail,_) :- !.
'$check_fn_errors'(error,_) :- !.
'$check_fn_errors'(T,G) :- atom(T), !,
'$do_error'(domain_error(file_errors,T),G).
'$check_fn_errors'(T,G) :- !,
'$do_error'(type_error(atom,T),G).
'$check_fn_solutions'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_fn_solutions'(first,_) :- !.
'$check_fn_solutions'(all,_) :- !.
'$check_fn_solutions'(T,G) :- atom(T), !,
'$do_error'(domain_error(solutions,T),G).
'$check_fn_solutions'(T,G) :- !,
'$do_error'(type_error(atom,T),G).
'$check_true_false'(V,G) :- var(V), !,
'$do_error'(instantiation_error, G).
'$check_true_false'(true,_) :- !.
'$check_true_false'(false,_) :- !.
'$check_true_false'(T,G) :- atom(T), !,
'$do_error'(domain_error(boolean,T),G).
'$check_true_false'(T,G) :- !,
'$do_error'(type_error(atom,T),G).
% This sequence must be followed:
% user and user_input are special;
% library(F) must check library_directories
% T(F) must check file_search_path
% all must try search in path
'$find_in_path'(user,_,user_input, _) :- !.
'$find_in_path'(user_input,_,user_input, _) :- !.
'$find_in_path'(library(File),Opts,NewFile, Call) :- !,
'$dir_separator'(D),
atom_codes(A,[D]),
'$extend_path_directory'(Name, A, File, Opts, NewFile, Call).
'$find_in_path'(S, Opts, NewFile, Call) :-
S =.. [Name,File], !,
'$dir_separator'(D),
atom_codes(A,[D]),
'$extend_path_directory'(Name, A, File, Opts, NewFile, Call).
'$find_in_path'(File,Opts,NewFile,_) :-
atom(File), !,
'$add_path'(File,PFile),
'$get_abs_file'(PFile,Opts,AbsFile),
'$search_in_path'(AbsFile,Opts,NewFile).
'$find_in_path'(File,_,_,Call) :-
'$do_error'(domain_error(source_sink,File),Call).
'$get_abs_file'(File,opts(_,D0,_,_,_,_,_),AbsFile) :-
'$dir_separator'(D),
atom_codes(A,[D]),
atom_concat([D0,A,File],File1),
system:true_file_name(File1,AbsFile).
'$search_in_path'(File,opts(Extensions,_,_,Access,_,_,_),F) :-
'$add_extensions'(Extensions,File,F),
access_file(F,Access).
'$search_in_path'(File,opts(_,_,Type,Access,_,_,_),F) :-
'$add_type_extensions'(Type,File,F),
access_file(F,Access).
'$add_extensions'([Ext|_],File,F) :-
'$mk_sure_true_ext'(Ext,NExt),
atom_concat([File,NExt],F).
'$add_extensions'([_|Extensions],File,F) :-
'$add_extensions'(Extensions,File,F).
'$mk_sure_true_ext'(Ext,NExt) :-
atom_codes(Ext,[C|L]),
C \= 0'.,
!,
atom_codes(NExt,[0'.,C|L]).
'$mk_sure_true_ext'(Ext,Ext).
'$add_type_extensions'(Type,File,F) :-
'$type_extension'(Type,Ext),
atom_concat([File,Ext],F).
'$type_extension'(txt,'').
'$type_extension'(prolog,'.yap').
'$type_extension'(prolog,'.pl').
'$type_extension'(prolog,'').
'$type_extension'(source,'.yap').
'$type_extension'(source,'.pl').
'$type_extension'(source,'').
'$type_extension'(executable,'.so').
'$type_extension'(executable,'').
'$type_extension'(qlf,'.qlf').
'$type_extension'(qlf,'').
'$type_extension'(directory,'').
'$add_path'(File,File).
'$add_path'(File,PFile) :-
recorded('$path',Path,_),
atom_concat([Path,File],PFile).
'$extend_path_directory'(Name, D, File, Opts, NewFile, Call) :-
user:file_search_path(Name, Dir),
'$extend_pathd'(Dir, D, File, Opts, NewFile, Call).
'$extend_pathd'(Dir, A, File, Opts, NFile, Call) :-
atom(Dir), !,
atom_concat([Dir,A,File],NFile),
'$search_in_path'(NFile, Opts, NewFile), !.
'$extend_pathd'(Name, A, File, Opts, OFile, Goal) :-
nonvar(Name),
Name =.. [N,P0],
atom_concat([P0,A,File],NFile),
NewName =.. [N,NFile],
'$find_in_path'(NewName, Opts, OFile, Goal).

View File

@@ -193,15 +193,17 @@ yap_flag(enhanced,off) :- set_value('$enhanced',[]).
%
% SWI compatibility flag
%
yap_flag(generate_debug_info,X) :-
yap_flag(generate_debugging_info,X) :-
var(X), !,
'$access_yap_flags'(18,Options),
(Options =:= 0 -> X = false ; X = true ).
yap_flag(generate_debug_info,true) :- !,
'$set_yap_flags'(18,1).
yap_flag(generate_debug_info,false) :- !,
'$set_yap_flags'(18,0).
yap_flag(generate_debug_info,X) :-
yap_flag(generate_debugging_info,true) :- !,
'$set_yap_flags'(18,1),
source.
yap_flag(generate_debugging_info,false) :- !,
'$set_yap_flags'(18,0),
no_source.
yap_flag(generate_debugging_info,X) :-
'$do_error'(domain_error(flag_value,generate_debugging_info+X),yap_flag(generate_debugging_info,X)).
%
@@ -557,6 +559,17 @@ yap_flag(toplevel_hook,X) :-
yap_flag(toplevel_hook,G) :- !,
'$set_toplevel_hook'(G).
yap_flag(unix,true) :-
'$unix', !.
yap_flag(unix,false).
yap_flag(windows,true) :-
'$win32', !.
yap_flag(windows,false).
yap_flag(shared_object_search_path,P) :-
'$ld_path'(P).
yap_flag(typein_module,X) :-
var(X), !,
'$current_module'(X).
@@ -691,7 +704,7 @@ yap_flag(max_threads,X) :-
V = gc ;
V = gc_margin ;
V = gc_trace ;
V = generate_debug_info ;
V = generate_debugging_info ;
% V = hide ;
V = home ;
V = host_type ;
@@ -703,11 +716,13 @@ yap_flag(max_threads,X) :-
V = max_arity ;
V = max_integer ;
V = max_tagged_integer ;
V = max_threads ;
V = min_integer ;
V = min_tagged_integer ;
V = n_of_integer_keys_in_db ;
V = profiling ;
V = redefine_warnings ;
V = shared_object_search_path ;
V = single_var_warnings ;
V = stack_dump_on_error ;
V = strict_iso ;
@@ -717,6 +732,7 @@ yap_flag(max_threads,X) :-
V = toplevel_hook ;
V = toplevel_print_options ;
V = typein_module ;
V = unix ;
V = unknown ;
V = update_semantics ;
V = user_error ;
@@ -724,8 +740,8 @@ yap_flag(max_threads,X) :-
V = user_output ;
V = verbose_auto_load ;
V = version ;
V = write_strings;
V = max_threads
V = windows ;
V = write_strings
),
yap_flag(V, Out).

View File

@@ -11,8 +11,13 @@
* File: errors.yap *
* comments: error messages for YAP *
* *
* Last rev: $Date: 2007-01-24 14:20:04 $,$Author: vsc $ *
* Last rev: $Date: 2007-09-27 15:25:34 $,$Author: vsc $ *
* $Log: not supported by cvs2svn $
* Revision 1.80 2007/01/24 14:20:04 vsc
* Fix typos across code
* Change debugger to backtrack more alike byrd model
* Fix typo in debugger option f
*
* Revision 1.79 2006/12/13 16:10:26 vsc
* several debugger and CLP(BN) improvements.
*
@@ -631,8 +636,8 @@ print_message(Level, Mss) :-
'$output_error_message'(existence_error(array,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open array ~w~n',
[W,F]).
'$output_error_message'(existence_error(mutex,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open mutex ~w~n',
'$output_error_message'(existence_error(file,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open file ~w~n',
[W,F]).
'$output_error_message'(existence_error(library,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open library ~w~n',
@@ -640,6 +645,9 @@ print_message(Level, Mss) :-
'$output_error_message'(existence_error(message_queue,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open message queue ~w~n',
[W,F]).
'$output_error_message'(existence_error(mutex,F), W) :-
format(user_error,'% EXISTENCE ERROR- ~w could not open mutex ~w~n',
[W,F]).
'$output_error_message'(existence_error(procedure,P), context(Call,Parent)) :-
format(user_error,'% EXISTENCE ERROR- procedure ~w is undefined, called from context ~w~n% Goal was ~w~n',
[P,Parent,Call]).

View File

@@ -99,8 +99,14 @@ yap_hacks:cut_by(CP) :- '$$cut_by'(CP).
:- dynamic user:library_directory/1.
user:library_directory(D) :-
prolog:'$system_library_directories'(D).
:- (
prolog:'$system_library_directories'(D),
write(D),nl,
assert(user:library_directory(D)),
fail
;
true
).
%
% cleanup ensure loaded and recover some data-base space.
@@ -135,8 +141,12 @@ user:library_directory(D) :-
:- dynamic file_search_path/2.
file_search_path(library, Dir) :-
library_directory(Dir).
library_directory(Dir).
file_search_path(swi, Home) :-
current_prolog_flag(home, Home).
file_search_path(yap, Home) :-
current_prolog_flag(home, Home).
file_search_path(system, Dir) :-
prolog_flag(host_type, Dir).
prolog_flag(host_type, Dir).
file_search_path(foreign, yap('lib/Yap')).

View File

@@ -965,15 +965,6 @@ at_end_of_line(S) :-
consult_depth(LV) :- '$show_consult_level'(LV).
absolute_file_name(V,Out) :- var(V), !,
'$do_error'(instantiation_error, absolute_file_name(V, Out)).
absolute_file_name(user,user) :- !.
absolute_file_name(RelFile,AbsFile) :-
'$find_in_path'(RelFile,PathFile,absolute_file_name(RelFile,AbsFile)),
'$exists'(PathFile,'$csult', AbsFile), !.
absolute_file_name(RelFile, AbsFile) :-
'$file_expansion'(RelFile, AbsFile).
'$exists'(F,Mode,AbsFile) :-
get_value(fileerrors,V),
set_value(fileerrors,0),
@@ -1053,3 +1044,5 @@ current_stream(File, Opts, Stream) :-
throw(Exception).
write_depth(T,L) :- write_depth(T,L,_).