cleanup patches.

git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@654 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
vsc 2002-10-27 18:11:01 +00:00
parent 4eb3336b3c
commit 8c71464b80
3 changed files with 31 additions and 12 deletions

View File

@ -5616,10 +5616,10 @@ Unify the current value of mutable term @var{M} with term @var{D}.
@cnindex is_mutable/1
Holds if @var{D} is a mutable term.
@item set_mutable(?@var{D},+@var{M})
@findex set_mutable/2
@syindex set_mutable/2
@cnindex set_mutable/2
@item get_mutable(?@var{D},+@var{M})
@findex get_mutable/2
@syindex get_mutable/2
@cnindex get_mutable/2
Unify the current value of mutable term @var{M} with term @var{D}.
@item update_mutable(+@var{D},+@var{M})
@ -8191,10 +8191,24 @@ term @var{Term}.
@cindex cleanup
@t{call_cleanup/1} and @t{call_cleanup/2} allow predicates to register
code for execution after the call is finished. This library is loaded
with the @code{use_module(library(cleanup))} command.
code for execution after the call is finished. Predicates can be
declared to be @t{fragile} to ensure that @t{call_cleanup} is called
for any Goal which needs it. This library is loaded with the
@code{use_module(library(cleanup))} command.
@table @code
@item :- fragile @var{P},....,@var{Pn}
@findex fragile
@syindex fragile
@cnindex fragile
Declares the predicate @var{P}=@t{[module:]name/arity} as a fragile
predicate, module is optional, default is the current
typein_module. Whenever such a fragile predicate is used in a query
it will be called through call_cleanup/1.
@example
:- fragile foo/1,bar:baz/2.
@end example
@item call_cleanup(+@var{Goal})
@findex call_cleanup/1
@syindex call_cleanup/1

View File

@ -137,9 +137,10 @@ on_cleanupz(L,G) :-
% helpers
cleanup_expansion(X) :-
var(X),!,throw(error(instantiation_error,fragile(X))).
cleanup_expansion((H,T)) :- cleanup_expansion(H),cleanup_expansion(T).
cleanup_expansion([H,T]) :- cleanup_expansion(H),cleanup_expansion(T).
cleanup_expansion(G/A) :-
cleanup_expansion((H,T)) :- !,cleanup_expansion(H),cleanup_expansion(T).
cleanup_expansion([H,T]) :- !, cleanup_expansion(H),
( T = [] -> true ; cleanup_expansion(T) ).
cleanup_expansion(M:G/A) :-
atom(G),integer(A),!,
compose_var_goal(G/A,GG),
\+ user:goal_expansion(GG,M,call_cleanup(M:GG)),
@ -149,6 +150,8 @@ cleanup_expansion(G/A) :-
NG=call_cleanup(M:GG)
; bb_put(expansion_toggle,1),
NG=M:GG )).
cleanup_expansion(G/A) :-
!,prolog_flag(typein_module,M),cleanup_expansion(M:G/A).
cleanup_expansion(X) :-
!,throw(error(instantiation_error,fragile(X))).

View File

@ -75,10 +75,12 @@ portray_clause(_).
'$portray_clause'(Stream, (Pred :- true)) :- !,
'$beautify_vars'(Pred),
'$format'(Stream, "~q.~n", [Pred]).
writeq(Stream, Pred),
'$format'(Stream, ".~n", []).
'$portray_clause'(Stream, (Pred:-Body)) :-
'$beautify_vars'((Pred:-Body)),
'$format'(Stream, "~q :-", [Pred]),
writeq(Stream, Pred),
'$format'(Stream, " :-", []),
'$write_body'(Body, 3, ',', Stream),
'$format'(Stream, ".~n", []).
@ -128,7 +130,7 @@ portray_clause(_).
'$format'(Stream, "~n~*c)",[I,0' ]).
'$write_body'(X,I,T,Stream) :-
'$beforelit'(T,I,Stream),
'$format'(Stream,"~q",[X]).
writeq(Stream,X).
'$write_disj'((Q;S),I0,I,C,Stream) :- !,