file_search_path
host_type git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@351 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
parent
a69a8e9a3f
commit
1f5af38ba8
@ -2066,6 +2066,12 @@ p_set_fpu_exceptions(void) {
|
||||
return(TRUE);
|
||||
}
|
||||
|
||||
static Int
|
||||
p_host_type(void) {
|
||||
Term out = MkAtomTerm(LookupAtom(HOST_ALIAS));
|
||||
return(unify(out,ARG1));
|
||||
}
|
||||
|
||||
/*
|
||||
* This is responsable for the initialization of all machine dependant
|
||||
* predicates
|
||||
@ -2114,6 +2120,7 @@ InitSysPreds(void)
|
||||
InitCPred ("$putenv", 2, p_putenv, SafePredFlag|SyncPredFlag);
|
||||
InitCPred ("$file_age", 2, p_file_age, SafePredFlag|SyncPredFlag);
|
||||
InitCPred ("$set_fpu_exceptions", 0, p_set_fpu_exceptions, SafePredFlag|SyncPredFlag);
|
||||
InitCPred ("$host_type", 1, p_host_type, SafePredFlag|SyncPredFlag);
|
||||
}
|
||||
|
||||
|
||||
@ -2182,3 +2189,4 @@ int WINAPI win_yap(HANDLE hinst, DWORD reason, LPVOID reserved)
|
||||
return 1;
|
||||
}
|
||||
#endif
|
||||
|
||||
|
@ -113,7 +113,7 @@ A contains the address of the variable that is to be trailed
|
||||
|
||||
#if SIZEOF_DOUBLE == 2*SIZEOF_LONG_INT
|
||||
|
||||
inline EXTERN void
|
||||
EXTERN inline void
|
||||
AlignGlobalForDouble(void)
|
||||
{
|
||||
/* Force Alignment for floats. Note that garbage collector may
|
||||
@ -380,7 +380,8 @@ Int unify(Term t0, Term t1)
|
||||
}
|
||||
}
|
||||
|
||||
EXTERN inline Int unify_constant(register Term a, register Term cons)
|
||||
EXTERN inline Int
|
||||
unify_constant(register Term a, register Term cons)
|
||||
{
|
||||
CELL *pt;
|
||||
deref_head(a,unify_cons_unk);
|
||||
|
33
docs/yap.tex
33
docs/yap.tex
@ -1612,6 +1612,34 @@ directories are the places where files specified in the form
|
||||
@code{consult/1}, @code{reconsult/1}, @code{use_module/1} or
|
||||
@code{ensure_loaded/1}.
|
||||
|
||||
@item file_search_path(+@var{NAME},-@var{DIRECTORY})
|
||||
@findex file_search_path/2
|
||||
@syindex file_search_path/2
|
||||
@cnindex file_search_path/2
|
||||
Allows writing file names as compound terms. The @var{NAME} and
|
||||
@var{DIRECTORY} must be atoms. The predicate may generate multiple
|
||||
solutions. The predicate is originally defined as follows:
|
||||
|
||||
@example
|
||||
file_search_path(library,A) :-
|
||||
library_directory(A).
|
||||
file_search_path(system,A) :-
|
||||
prolog_flag(host_type,A).
|
||||
@end example
|
||||
|
||||
Thus, [library(A)] will search for a file using
|
||||
@var{library_directory}/1 to obtain the prefix.
|
||||
|
||||
@item library_directory(+@var{D})
|
||||
@findex library_directory/1
|
||||
@snindex library_directory/1
|
||||
@cnindex library_directory/1
|
||||
Succeeds when @var{D} is a current library directory name. Library
|
||||
directories are the places where files specified in the form
|
||||
@code{library(@var{File})} are searched by the predicates
|
||||
@code{consult/1}, @code{reconsult/1}, @code{use_module/1} or
|
||||
@code{ensure_loaded/1}.
|
||||
|
||||
@item prolog_file_name(+@var{Name},-@var{FullPath})
|
||||
@findex prolog_file_name/2
|
||||
@syindex prolog_file_name/1
|
||||
@ -5998,6 +6026,11 @@ collection and stack shifts. Last, if @code{very_verbose} give detailed
|
||||
information on data-structures found during the garbage collection
|
||||
process, namely, on choice-points.
|
||||
|
||||
@item host_type
|
||||
@findex host_type (yap_flag/2 option)
|
||||
@* Return @code{configure} system information, including the machine-id
|
||||
for which Yap was compiled and Operating System information.
|
||||
|
||||
@item index
|
||||
@findex index (yap_flag/2 option)
|
||||
@*
|
||||
|
71
pl/boot.yap
71
pl/boot.yap
@ -884,8 +884,8 @@ break :- '$get_value'('$break',BL), NBL is BL+1,
|
||||
'$change_module'(M),
|
||||
'$consult'(X),
|
||||
'$change_module'(M0).
|
||||
'$consult'(X) :- atom(X), !,
|
||||
'$find_in_path'(X,Y),
|
||||
'$consult'(X) :-
|
||||
'$find_in_path'(X,Y,consult(X)),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$record_loaded'(Stream),
|
||||
'$consult'(X,Stream),
|
||||
@ -893,22 +893,6 @@ break :- '$get_value'('$break',BL), NBL is BL+1,
|
||||
;
|
||||
throw(error(permission_error(input,stream,Y),consult(X)))
|
||||
).
|
||||
'$consult'(M:X) :- !,
|
||||
% set the type-in module
|
||||
'$current_module'(Mod),
|
||||
module(M),
|
||||
'$consult'(X),
|
||||
'$current_module'(Mod).
|
||||
'$consult'(library(X)) :- !,
|
||||
'$find_in_path'(library(X),Y),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$record_loaded'(Stream),
|
||||
'$consult'(library(X),Stream), '$close'(Stream)
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),consult(library(X))))
|
||||
).
|
||||
'$consult'(V) :-
|
||||
throw(error(type_error(atom,V),consult(V))).
|
||||
|
||||
|
||||
'$consult'(F,Stream) :-
|
||||
@ -1012,10 +996,6 @@ break :- '$get_value'('$break',BL), NBL is BL+1,
|
||||
|
||||
/* General purpose predicates */
|
||||
|
||||
'$append'([], L, L) .
|
||||
'$append'([H|T], L, [H|R]) :-
|
||||
'$append'(T, L, R).
|
||||
|
||||
'$head_and_body'((H:-B),H,B) :- !.
|
||||
'$head_and_body'(H,H,true).
|
||||
|
||||
@ -1042,37 +1022,26 @@ break :- '$get_value'('$break',BL), NBL is BL+1,
|
||||
'$set_value'(fileerrors,V), fail).
|
||||
|
||||
|
||||
'$find_in_path'(user,user_input) :- !.
|
||||
'$find_in_path'(user_input,user_input) :- !.
|
||||
'$find_in_path'(library(File),NewFile) :- !,
|
||||
'$find_library_in_path'(File, NewFile).
|
||||
'$find_in_path'(File,File) :- '$exists'(File,'$csult'), !.
|
||||
'$find_in_path'(File,NewFile) :- name(File,FileStr),
|
||||
'$search_in_path'(FileStr,NewFile),!.
|
||||
'$find_in_path'(File,File).
|
||||
|
||||
'$find_library_in_path'(File, NewFile) :-
|
||||
user:library_directory(Dir),
|
||||
atom_codes(File,FileS),
|
||||
atom_codes(Dir,DirS),
|
||||
'$dir_separator'(A),
|
||||
'$append'(DirS,[A|FileS],NewS),
|
||||
atom_codes(NewFile,NewS),
|
||||
'$exists'(NewFile,'$csult'), !.
|
||||
'$find_library_in_path'(File, NewFile) :-
|
||||
'$getenv'('YAPSHAREDIR', LibDir),
|
||||
'$dir_separator'(A),
|
||||
atom_codes(File,FileS),
|
||||
atom_codes(LibDir,Dir1S),
|
||||
'$append'(Dir1S,[A|"library"],DirS),
|
||||
'$append'(DirS,[A|FileS],NewS),
|
||||
atom_codes(NewFile,NewS),
|
||||
'$exists'(NewFile,'$csult'), !.
|
||||
'$find_library_in_path'(File, File).
|
||||
'$find_in_path'(user,user_input, _) :- !.
|
||||
'$find_in_path'(user_input,user_input, _) :- !.
|
||||
'$find_in_path'(S,NewFile, _) :-
|
||||
S =.. [Name,File], !,
|
||||
user:file_search_path(Name, Dir),
|
||||
'$dir_separator'(D),
|
||||
atom_codes(A,[D]),
|
||||
atom_concat([Dir,A,File],NFile),
|
||||
'$search_in_path'(NFile, NewFile).
|
||||
'$find_in_path'(File,NewFile,_) :- atom(File), !,
|
||||
'$search_in_path'(File,NewFile),!.
|
||||
'$find_in_path'(File,_,Call) :-
|
||||
throw(error(domain_error(source_sink,File),G)).
|
||||
|
||||
'$search_in_path'(New,New) :-
|
||||
'$exists'(New,'$csult'), !.
|
||||
'$search_in_path'(File,New) :-
|
||||
'$recorded'('$path',Path,_), '$append'(Path,File,NewStr),
|
||||
name(New,NewStr),'$exists'(New,'$csult').
|
||||
'$recorded'('$path',Path,_),
|
||||
atom_concat([Path,File],New),
|
||||
'$exists'(New,'$csult').
|
||||
|
||||
path(Path) :- findall(X,'$in_path'(X),Path).
|
||||
|
||||
|
@ -29,8 +29,8 @@ ensure_loaded(V) :-
|
||||
'$change_module'(M),
|
||||
'$ensure_loaded'(X),
|
||||
'$change_module'(M0).
|
||||
'$ensure_loaded'(X) :- atom(X), !,
|
||||
'$find_in_path'(X,Y),
|
||||
'$ensure_loaded'(X) :-
|
||||
'$find_in_path'(X,Y,ensure_loaded(X)),
|
||||
( '$open'(Y, '$csult', Stream, 0), !,
|
||||
( '$loaded'(Stream) ->
|
||||
( '$consulting_file_name'(Stream,TFN),
|
||||
@ -48,26 +48,6 @@ ensure_loaded(V) :-
|
||||
|
||||
throw(error(permission_error(input,stream,X),ensure_loaded(X)))
|
||||
).
|
||||
'$ensure_loaded'(library(X)) :- !,
|
||||
'$find_in_path'(library(X),Y),
|
||||
( '$open'(Y,'$csult',Stream, 0), !,
|
||||
( '$loaded'(Stream) ->
|
||||
( '$consulting_file_name'(Stream,TFN),
|
||||
'$recorded'('$module','$module'(TFN,M,P),_) ->
|
||||
'$current_module'(T), '$import'(P,M,T)
|
||||
;
|
||||
true
|
||||
)
|
||||
;
|
||||
'$record_loaded'(Stream),
|
||||
'$reconsult'(Y,Stream)
|
||||
),
|
||||
'$close'(Stream)
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),ensure_loaded(library(X))))
|
||||
).
|
||||
'$ensure_loaded'(V) :-
|
||||
throw(error(type_error(atom,V),ensure_loaded(V))).
|
||||
|
||||
|
||||
compile(P) :-
|
||||
@ -105,24 +85,14 @@ reconsult(Fs) :-
|
||||
'$reconsult'([F|Fs]) :- !,
|
||||
'$reconsult'(F),
|
||||
'$reconsult'(Fs).
|
||||
'$reconsult'(X) :- atom(X), !,
|
||||
'$find_in_path'(X,Y),
|
||||
'$reconsult'(X) :-
|
||||
'$find_in_path'(X,Y,reconsult(X)),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$record_loaded'(Stream),
|
||||
'$reconsult'(X,Stream), '$close'(Stream)
|
||||
;
|
||||
throw(error(permission_error(input,stream,X),reconsult(X)))
|
||||
).
|
||||
'$reconsult'(library(X)) :- !,
|
||||
'$find_in_path'(library(X),Y),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$record_loaded'(Stream),
|
||||
'$reconsult'(library(X),Stream), '$close'(Stream)
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),reconsult(library(X))))
|
||||
).
|
||||
'$reconsult'(V) :-
|
||||
throw(error(type_error(atom,V),reconsult(V))).
|
||||
|
||||
'$reconsult'(F,Stream) :-
|
||||
'$getcwd'(OldD),
|
||||
@ -158,7 +128,7 @@ reconsult(Fs) :-
|
||||
'$format'('''EMACS_RECONSULT''(~w).~n',[File0]),
|
||||
'$getcwd'(OldD),
|
||||
'$open'(F,'$csult',Stream,0),
|
||||
'$find_in_path'(File0,File),
|
||||
'$find_in_path'(File0,File,emacs(F)),
|
||||
'$open'(File,'$csult',Stream0,0),
|
||||
'$get_value'('$consulting_file',OldF),
|
||||
'$set_consulting_file'(Stream0),
|
||||
@ -203,8 +173,8 @@ reconsult(Fs) :-
|
||||
'$include'([F|Fs], Status) :- !,
|
||||
'$include'(F, Status),
|
||||
'$include'(Fs, Status).
|
||||
'$include'(X, Status) :- atom(X), !,
|
||||
'$find_in_path'(X,Y),
|
||||
'$include'(X, Status) :-
|
||||
'$find_in_path'(X,Y,include(X)),
|
||||
'$values'('$included_file',OY,Y),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$loop'(Stream,Status), '$close'(Stream)
|
||||
@ -212,8 +182,6 @@ reconsult(Fs) :-
|
||||
throw(error(permission_error(input,stream,Y),include(X)))
|
||||
),
|
||||
'$set_value'('$included_file',OY).
|
||||
'$include'(V, _) :-
|
||||
throw(error(type_error(atom,V),include(V))).
|
||||
|
||||
'$do_startup_reconsult'(X) :-
|
||||
( '$access_yap_flags'(15, 0) ->
|
||||
@ -221,7 +189,7 @@ reconsult(Fs) :-
|
||||
;
|
||||
'$set_value'('$verbose',off)
|
||||
),
|
||||
'$find_in_path'(X,Y),
|
||||
'$find_in_path'(X,Y,reconsult(X)),
|
||||
( '$open'(Y,'$csult',Stream,0), !,
|
||||
'$record_loaded'(Stream),
|
||||
( '$access_yap_flags'(15, 0) -> true ; '$skip_unix_comments'(Stream) ),
|
||||
|
16
pl/init.yap
16
pl/init.yap
@ -119,9 +119,6 @@ system_mode(verbose,off) :- '$set_value'('$verbose',off).
|
||||
|
||||
:- module(user).
|
||||
|
||||
:- multifile library_directory/1.
|
||||
|
||||
:- dynamic_predicate(library_directory/1, logical).
|
||||
|
||||
:- multifile goal_expansion/3.
|
||||
|
||||
@ -131,5 +128,18 @@ system_mode(verbose,off) :- '$set_value'('$verbose',off).
|
||||
|
||||
:- dynamic_predicate(term_expansion/2, logical).
|
||||
|
||||
:- multifile file_search_path/2.
|
||||
|
||||
:- dynamic_predicate(file_search_path/2, logical).
|
||||
|
||||
file_search_path(library, Dir) :-
|
||||
library_directory(Dir).
|
||||
file_search_path(system, Dir) :-
|
||||
prolog_flag(host_type, Dir).
|
||||
|
||||
:- multifile library_directory/1.
|
||||
|
||||
:- dynamic_predicate(library_directory/1, logical).
|
||||
|
||||
:- get_value(system_library_directory,D), assert(library_directory(D)).
|
||||
|
||||
|
@ -34,7 +34,7 @@ use_module(M) :-
|
||||
'$use_module'(F),
|
||||
'$change_module'(M0).
|
||||
'$use_module'(File) :-
|
||||
'$find_in_path'(File,X),
|
||||
'$find_in_path'(File,X,use_module(File)),
|
||||
( '$recorded'('$module','$module'(_,X,Publics),_) ->
|
||||
'$use_module'(File,Publics)
|
||||
;
|
||||
@ -54,9 +54,8 @@ use_module(M,I) :-
|
||||
'$use_module'(F, Imports),
|
||||
'$change_module'(M0).
|
||||
'$use_module'(File,Imports) :-
|
||||
atom(File), !,
|
||||
'$current_module'(M),
|
||||
'$find_in_path'(File,X),
|
||||
'$find_in_path'(File,X,use_module(File,Imports)),
|
||||
( '$open'(X,'$csult',Stream,0), !,
|
||||
'$consulting_file_name'(Stream,TrueFileName),
|
||||
( '$loaded'(Stream) -> true
|
||||
@ -77,31 +76,6 @@ use_module(M,I) :-
|
||||
;
|
||||
throw(error(permission_error(input,stream,X),use_module(X,Imports)))
|
||||
).
|
||||
'$use_module'(library(File),Imports) :- !,
|
||||
'$current_module'(M),
|
||||
'$find_in_path'(library(File),X),
|
||||
( '$open'(X,'$csult',Stream,0), !,
|
||||
'$consulting_file_name'(Stream,TrueFileName),
|
||||
( '$loaded'(Stream) -> true
|
||||
;
|
||||
'$record_loaded'(Stream),
|
||||
% the following avoids import of all public predicates
|
||||
'$recorda'('$importing','$importing'(TrueFileName),R),
|
||||
'$reconsult'(library(File),Stream)
|
||||
),
|
||||
'$close'(Stream),
|
||||
( var(R) -> true; erased(R) -> true; erase(R)),
|
||||
( '$recorded'('$module','$module'(TrueFileName,Mod,Publics),_) ->
|
||||
'$use_preds'(Imports,Publics,Mod,M)
|
||||
;
|
||||
'$format'(user_error,"[ use_module/2 can not find a module in file ~w]~n",[File]),
|
||||
fail
|
||||
)
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),use_module(library(X),Imports)))
|
||||
).
|
||||
'$use_module'(V,Decls) :-
|
||||
throw(error(type_error(atom,V),use_module(V,Decls))).
|
||||
|
||||
use_module(Mod,F,I) :-
|
||||
'$use_module'(Mod,F,I).
|
||||
@ -114,7 +88,7 @@ use_module(Mod,F,I) :-
|
||||
'$change_module'(M0).
|
||||
'$use_module'(Module,File,Imports) :-
|
||||
'$current_module'(M),
|
||||
'$find_in_path'(File,X),
|
||||
'$find_in_path'(File,X,use_module(Module,File,Imports)),
|
||||
( '$open'(X,'$csult',Stream,0), !,
|
||||
'$consulting_file_name'(Stream,TrueFileName),
|
||||
( '$loaded'(Stream) -> true
|
||||
@ -135,30 +109,6 @@ use_module(Mod,F,I) :-
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),use_module(Module,File,Imports)))
|
||||
).
|
||||
'$use_module'(Module,File,Imports,M) :-
|
||||
'$find_in_path'(File,X),
|
||||
( '$open'(X,'$csult',Stream,0), !,
|
||||
'$consulting_file_name'(Stream,TrueFileName),
|
||||
( '$loaded'(Stream) -> true
|
||||
;
|
||||
'$record_loaded'(Stream),
|
||||
% the following avoids import of all public predicates
|
||||
'$recorda'('$importing','$importing'(TrueFileName),R),
|
||||
'$reconsult'(File,Stream)
|
||||
),
|
||||
'$close'(Stream),
|
||||
( var(R) -> true; erased(R) -> true; erase(R)),
|
||||
( '$recorded'('$module','$module'(TrueFileName,Module,Publics),_) ->
|
||||
'$use_preds'(Imports,Publics,Module,M)
|
||||
;
|
||||
'$format'(user_error,"[ use_module/2 can not find module ~w in file ~w]~n",[Module,File]),
|
||||
fail
|
||||
)
|
||||
;
|
||||
throw(error(permission_error(input,stream,library(X)),use_module(Module,File,Imports)))
|
||||
).
|
||||
'$use_module'(Module,V,Decls) :-
|
||||
throw(error(type_error(atom,V),use_module(Module,V,Decls))).
|
||||
|
||||
'$consulting_file_name'(Stream,F) :-
|
||||
'$file_name'(Stream, F).
|
||||
|
@ -808,3 +808,7 @@ user_defined_directive(Dir,Action) :-
|
||||
raise_exception(Ball) :- throw(Ball).
|
||||
on_exception(Pat, G, H) :- catch(G, Pat, H).
|
||||
|
||||
'$append'([], L, L) .
|
||||
'$append'([H|T], L, [H|R]) :-
|
||||
'$append'(T, L, R).
|
||||
|
||||
|
@ -871,7 +871,7 @@ absolute_file_name(V,Out) :- var(V), !,
|
||||
throw(error(instantiation_error, absolute_file_name(V, Out))).
|
||||
absolute_file_name(user,user) :- !.
|
||||
absolute_file_name(RelFile,AbsFile) :-
|
||||
'$find_in_path'(RelFile,PathFile),
|
||||
'$find_in_path'(RelFile,PathFile,absolute_file_name(RelFile,AbsFile)),
|
||||
'$exists'(PathFile,'$csult', AbsFile), !.
|
||||
absolute_file_name(RelFile, AbsFile) :-
|
||||
'$file_expansion'(RelFile, AbsFile).
|
||||
|
Reference in New Issue
Block a user