fix use of pathconf

This commit is contained in:
Vitor Santos Costa 2016-08-02 18:25:39 -05:00
parent 8050747db7
commit 0dd5da91ca
3 changed files with 8 additions and 16 deletions

View File

@ -289,6 +289,10 @@ private(_).
'$sort'(L, S). '$sort'(L, S).
'$bootstrap_predicate'(print_message(Context, Msg), _M, _) :- !, '$bootstrap_predicate'(print_message(Context, Msg), _M, _) :- !,
'$early_print_message'(Context, Msg). '$early_print_message'(Context, Msg).
'$bootstrap_predicate'(print_message(Context, Msg), _M, _) :- !,
'$early_print_message'(Context, Msg).
'$bootstrap_predicate'(prolog_file_type(A,B), _, prolog_file_type(A,prolog)) :- !.
'$bootstrap_predicate'(file_search_path(_A,B), _, _ ) :- !, fail.
'$bootstrap_predicate'(meta_predicate(G), M, _) :- !, '$bootstrap_predicate'(meta_predicate(G), M, _) :- !,
strip_module(M:G, M1, G1), strip_module(M:G, M1, G1),
'$meta_predicate'(M1:G1). '$meta_predicate'(M1:G1).
@ -367,20 +371,10 @@ true :- true.
-> ->
prolog_flag(verbose, OldV, silent), prolog_flag(verbose, OldV, silent),
prolog_flag(resource_database, RootPath), prolog_flag(resource_database, RootPath),
file_directory_name( RootPath, Dir ), file_directory_name( RootPath, Dir ),
atom_concat( Dir, '/init.yap' , Init), atom_concat( Dir, '/init.yap' , Init),
( bootstrap(Init),
% is lib_dir set? % set_prolog_flag(verbose, OldV),
system_library( LibDir )
->
true
;
% get it from boot.yap
atom_concat( LibDir, '/pl' , Dir),
system_library(LibDir)
),
bootstrap(Init),
set_prolog_flag(verbose, OldV),
module( user ), module( user ),
'$make_saved_state' '$make_saved_state'
; ;
@ -1333,7 +1327,7 @@ not(G) :- \+ '$execute'(G).
bootstrap(F) :- bootstrap(F) :-
% '$open'(F, '$csult', Stream, 0, 0, F), % '$open'(F, '$csult', Stream, 0, 0, F),
% '$file_name'(Stream,File), % '$file_name'(Stream,File),
yap_flag(verbose_load, Old, silent), % yap_flag(verbose_load, Old, silent),
open(F, read, Stream), open(F, read, Stream),
stream_property(Stream, [file_name(File)]), stream_property(Stream, [file_name(File)]),
'$start_consult'(consult, File, LC), '$start_consult'(consult, File, LC),

View File

@ -126,7 +126,6 @@ otherwise.
:- bootstrap('directives.yap'). :- bootstrap('directives.yap').
:- bootstrap('absf.yap'). :- bootstrap('absf.yap').
:- dynamic prolog:'$parent_module'/2. :- dynamic prolog:'$parent_module'/2.
:- [ :- [

View File

@ -169,6 +169,5 @@ file_search_path(path, C) :-
lists:member(C, B) lists:member(C, B)
). ).
:- module(prolog).
%% @} %% @}