few extra good built-ins.

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@11 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
vsc 2001-04-19 17:12:18 +00:00
parent c5c775f933
commit f80b0b1d32
8 changed files with 89 additions and 11 deletions

View File

@ -6,6 +6,10 @@
<H2 ALIGN=CENTER>Yap-4.3.19:</H2>
<UL>
<LI> FIXED: extra clause for module/1.
<LI> NEW: module/3: SICStus options plus ciao options.
<LI> FIXED: mode/1 should not be defined if we do not know what
to do about it.
<LI> NEW: prolog_flag(version,X).
<LI> FIXED: understand 0'\ escape sequences.
<LI> NEW: atom_concat/2 (idea from ciao).

View File

@ -1698,6 +1698,31 @@ accessed if the module name is prefixed to the file name through the
The built-in @code{module/1} sets the current source module:
@table @code
@item module(+@var{M},+@var{L}, +@var{Options})
@findex module/3 (directive)
@syindex module/3 (directive)
@cnindex module/3 (directive)
Similar to @code{module/2}, this predicate defines the file where it
appears as a module file; it must be the first declaration in the file.
@var{M} must be an atom specifying the module name; @var{L} must be a
list containing the module's public predicates specification, in the
form @code{[predicate_name/arity,...]}.
The last argument @var{Options} must be a list of options, which can be:
@table @code
@item filename
the filename for a module to import into the current module.
@table @code
@item library(file)
a library file to import into the current module.
@item hide(@var{Opt})
if @var{Opt} is @code{false}, keep source code for current module, if
@code{true}, disable.
@end table
@item module(+@var{M})
@findex module/1
@syindex module/1

View File

@ -1243,6 +1243,13 @@ throw(G) :-
'$recorded'('$blocking_code',_,R),
erase(R),
fail.
% system goals must be performed first
'$exec_initialisation_goals' :-
'$recorded'('$system_initialisation',G,R),
erase(R),
G \= '$',
call(G),
fail.
'$exec_initialisation_goals' :-
'$recorded'('$initialisation',G,R),
erase(R),

View File

@ -45,8 +45,8 @@
( open(Y,'$csult',Stream), !,
( '$loaded'(Stream) ->
( '$consulting_file_name'(Stream,TFN),
'$recorded'($module,$module(TFN,M,P),_) ->
$current_module(T,T), $import(P,M,T)
'$recorded'('$module','$module'(TFN,M,P),_) ->
'$current_module'(T,T), $import(P,M,T)
;
true
)

View File

@ -20,6 +20,7 @@
'$directive'(initialization(_)).
'$directive'(include(_)).
'$directive'(module(_,_)).
'$directive'(module(_,_,_)).
'$directive'(meta_predicate(_)).
'$directive'(public(_)).
'$directive'(dynamic(_)).
@ -56,6 +57,8 @@
'$include'(F, Status).
'$exec_directive'(module(N,P), Status) :-
'$module'(Status,N,P).
'$exec_directive'(module(N,P,Op), Status) :-
'$module'(Status,N,P,Op).
'$exec_directive'(meta_predicate(P), _) :-
'$meta_predicate'(P).
'$exec_directive'(dynamic(P), _) :-

View File

@ -122,6 +122,9 @@ print_message(help,M) :-
'$output_error_message'(domain_error(mutable,N), Where) :-
format(user_error,"[ DOMAIN ERROR- ~w: invalid mutable ~w ]~n",
[Where,N]).
'$output_error_message'(domain_error(module_decl_options,N), Where) :-
format(user_error,"[ DOMAIN ERROR- ~w: expect module declaration options, found ~w ]~n",
[Where,N]).
'$output_error_message'(domain_error(not_empty_list,_), Where) :-
format(user_error,"[ DOMAIN ERROR- ~w: found empty list ]~n",
[Where]).

View File

@ -69,8 +69,6 @@ version(yap,[4,1]).
system_mode(verbose,on) :- '$set_value'('$verbose',on).
system_mode(verbose,off) :- '$set_value'('$verbose',off).
mode(_).
:- op(1150,fx,(mode)).
:- dynamic 'extensions_to_present_answer'/1.

View File

@ -116,6 +116,7 @@ use_module(Module,V,Decls) :-
'$consulting_file_name'(Stream,F) :-
'$file_name'(Stream, F).
'$module'(reconsult,N,P) :- !,
'$abolish_module_data'(N),
'$module_dec'(N,P).
@ -129,6 +130,48 @@ use_module(Module,V,Decls) :-
),
'$module_dec'(N,P).
'$module'(O,N,P,Opts) :- !,
'$module'(O,N,P),
'$process_module_decls_options'(Opts,module(Opts,N,P)).
'$process_module_decls_options'(Var,Mod) :-
var(Var),
throw(error(instantiation_error,Mod)).
'$process_module_decls_options'([],_).
'$process_module_decls_options'([H|L],M) :-
'$process_module_decls_option'(H,M),
'$process_module_decls_options'(L,M).
'$process_module_decls_options'(T,M) :-
throw(error(type_error(list,T),M)).
'$process_module_decls_option'(Var,M) :-
var(Var),
throw(error(instantiation_error,M)).
'$process_module_decls_option'(At,_) :-
atom(At),
use_module(At).
'$process_module_decls_option'(library(L),_) :-
use_module(library(L)).
'$process_module_decls_option'(hidden(Bool),M) :-
'$process_hidden_module'(Bool, M).
'$process_module_decls_option'(Opt,M) :-
throw(error(domain_error(module_decl_options,Opt),M)).
'$process_hidden_module'(TNew,M) :-
'$convert_true_off_mod3'(TNew, New, M),
source_mode(Old, New),
'$prepare_restore_hidden'(Old,New).
'$convert_true_off_mod3'(true, off, _).
'$convert_true_off_mod3'(false, on, _).
'$convert_true_off_mod3'(X, _, M) :-
throw(error(domain_error(module_decl_options,hidden(X)),M)).
'$prepare_restore_hidden'(Old,Old) :- !.
'$prepare_restore_hidden'(Old,New) :-
'$recorda'('$system_initialisation', source_mode(New,Old), _).
module(N) :-
var(N),
throw(error(instantiation_error,module(N))).
@ -400,7 +443,7 @@ $trace_module(X,Y).
arg(I,H,Y), var(Y), !,
I1 is I-1,
'$module_u_vars'(I1,D,H,L).
$module_u_vars(I,D,H,L) :-
'$module_u_vars'(I,D,H,L) :-
I1 is I-1,
'$module_u_vars'(I1,D,H,L).
@ -410,7 +453,7 @@ $module_u_vars(I,D,H,L) :-
'$meta_expansion'(Mod,MP,G,G1,HVars) :-
functor(G,F,N),
% '$recorded'('$meta_predicate','$meta_predicate'(Mod,F,N,D),_), !,
$meta_predicate(F,Mod,N,D), !,
'$meta_predicate'(F,Mod,N,D), !,
functor(G1,F,N),
% format(user_error,'[expanding ~w:~w in ~w',[Mod,G,MP]),
'$meta_expansion_loop'(N,D,G,G1,HVars,MP).
@ -447,11 +490,6 @@ current_module(Mod,TFN) :-
source_module(Mod) :-
'$current_module'(Mod).
module(Mod) :-
atom(Mod),
( recordzifnot('$module','$module'(Mod),_) -> true; true),
'$current_module'(_,Mod).
$member(X,[X|_]) :- !.
$member(X,[_|L]) :- $member(X,L).