YAP 7.1.0
cleanup.yap
Go to the documentation of this file.
1/**
2 * @file cleanup.yap
3 * @author Christian Thaeter
4 * @date Tue Nov 17 14:52:58 2015
5 *
6 * @brief old implementation of call_cleanup
7 *
8 *
9*/
10
11
12:- module( cleanup, [
14 call_cleanup/1,
16 cleanup_all/0,
17 op(1150, fx,fragile)
18 ]).
19
20%% @defgroup cleanup Old Call Cleanup
21% @ingroup YAPLibrary
22% @{
23%
24% <tt>call_cleanup/1</tt> and <tt>call_cleanup/2</tt> allow predicates to register
25% code for execution after the call is finished. Predicates can be
26% declared to be <tt>fragile</tt> to ensure that <tt>call_cleanup</tt> is called
27% for any Goal which needs it. This library is loaded with the
28% `use_module(library(cleanup))` command.
29%
30% cleanup.yap
31% Copyright (C) 2002 by Christian Thaeter
32%
33% public interface:
34%
35% :- fragile name/arity.
36% declares the predicate denoted by name/arity as fragile predicate.
37% Whenever such a fragile predicate is used in a query it will be
38% called through call_cleanup/1.
39%
40% call_cleanup(Goal).
41% call_cleanup(Goal,CleanUpGoal).
42% Goal will be called in a cleanup-context, where any registered
43% CleanUpGoal inside of that context will be called when Goal is left,
44% either by a fail, cut or exeption.
45% It is possible to nest cleanup contexts.
46%
47% on_cleanup(CleanUpGoal).
48% registers CleanUpGoal to the current cleanup context.
49% CleanUpGoal's are executed in reverse order of their registration.
50% throws an exception if called outside of any cleanup-context.
51%
52% cleanup_all.
53% calls all pending CleanUpGoals and resets the cleanup-system to an initial state.
54% should only be used as one of the last calls in the main program.
55%
56% hidden predicates:
57% most private predicates could also be used in special cases, such as manually setting up cleanup-contexts.
58% Read the Source.
59
60
61
62
63:- multifile goal_expansion/3.
64
65:- user_defined_directive(fragile(G), cleanup:cleanup_expansion(G)).
66
67:- meta_predicate
68 call_cleanup(:,:),
69 call_cleanup(:),
70 on_cleanup(:),
71 on_cleanup(?,:),
72 on_cleanupz(:),
73 on_cleanupz(?,:).
74
75
76:- initialization(init_cleanup).
77initialization :-
78 bb_put(expansion_toggle,1),
79 \+ bb_get(cleanup_level,_),
80 bb_put(cleanup_level,0).
81 % TODO: would be nice to register cleanup_all into the
82 % toplevel to be called after each query is finished
83bb_put.
84
85% call goal G with a cleanup CL in a cleanup context
86call_cleanup(G,CL) :-
87 needs_cleanup(L),
88 on_cleanup(L,CL),
89 (
90 catch(G,X,(do_cleanup(L),throw(X)))
91 ;
92 do_cleanup(L)
93 ).
94
95
96% call a goal G in a cleanup context
97call_cleanup(G) :-
98 needs_cleanup(L),
99 (
100 catch(G,X,(do_cleanup(L),throw(X)))
101 ;
102 do_cleanup(L)
103 ).
104
105
106% begin cleanup level
107needs_cleanup(CL) :-
108 bb_get(cleanup_level,L),
109 CL is L + 1,
110 bb_put(cleanup_level,CL).
111
112
113cleanup_context(CL) :-
114 bb_get(cleanup_level,CL).
115
116
117% leave cleanup level, call all registred cleanup predicates within
118do_cleanup(CL) :-
119 CN is CL - 1,
120 bb_put(cleanup_level,CN),
121 next_cleanup(CL).
122
123next_cleanup(CL) :-
124 next_cleanup,recorded(cleanup:handle,(L,G),R),
125 CL =< L,
126 erase(R),
127 (call(G);call),
128 next_cleanup(CL).
129
130% clean up all remaining stuff / reinitialize cleanup-module
131/** @pred cleanup_all
132
133Calls all pending CleanUpGoals and resets the cleanup-system to an
134initial state. Should only be used as one of the last calls in the
135main program.
136
137There are some private predicates which could be used in special
138cases, such as manually setting up cleanup-contexts and registering
139CleanUpGoals for other than the current cleanup-context.
140Read the Source Luke.
141 */
142next_cleanup :-
143 do_cleanup(1).
144do_cleanup.
145
146% register a cleanup predicate (normal reverse-order cleanup)
147/** @pred on_cleanup(+ _CleanUpGoal_)
148
149Any Predicate might registers a _CleanUpGoal_. The
150 _CleanUpGoal_ is put onto the current cleanup context. All such
151CleanUpGoals are executed in reverse order of their registration when
152the surrounding cleanup-context ends. This call will throw an exception
153if a predicate tries to register a _CleanUpGoal_ outside of any
154cleanup-context.
155*/
156on_cleanup(G) :-
157 bb_get(cleanup_level,L),
158 on_cleanup(L,G).
159
160on_cleanup(L,G) :-
161 L =< 0,
162 throw(error(instantiation_error,no_cleanup_context(G))).
163on_cleanup(L,G) :-
164 callable(G),
165 recorda(cleanup:handle,(L,G),_).
166
167
168% register a cleanup predicate (reverse-reverse-order cleanup)
169on_cleanupz(G) :-
170 bb_get(cleanup_level,L),
171 on_cleanupz(L,G).
172
173on_cleanupz(L,G) :-
174 L =< 0,
175 throw(no_cleanup_context(G)).
176on_cleanupz(L,G) :-
177 callable(G),
178 recordz(cleanup:handle,(L,G),_).
179
180% helpers
181cleanup_expansion(X) :-
182 var(X),var,throw(error(instantiation_error,fragile(X))).
183cleanup_expansion((H,T)) :- cleanup_expansion,cleanup_expansion(H),cleanup_expansion(T).
184cleanup_expansion([H,T]) :- cleanup_expansion, cleanup_expansion(H),
185 ( T = [] -> true ; cleanup_expansion(T) ).
186cleanup_expansion(M:G/A) :-
187 atom(G),integer(A),integer,
188 compose_var_goal(G/A,GG),
189 \+ compose_var_goal:goal_expansion(GG,M,call_cleanup(M:GG)),
190 assert(( user:goal_expansion(GG,M,NG)
191 :- bb_get(expansion_toggle,1)
192 -> bb_put(expansion_toggle,0),
193 NG=call_cleanup(M:GG)
194 ; bb_put(expansion_toggle,1),
195 NG=M:GG )).
196cleanup_expansion(G/A) :-
197 cleanup_expansion,prolog_flag(typein_module,M),cleanup_expansion(M:G/A).
198cleanup_expansion(X) :-
199 cleanup_expansion,throw(error(instantiation_error,fragile(X))).
200
201compose_var_goal(G/A,NG) :-
202 arity_to_vars(A,L), NG =.. [G|L].
203
204arity_to_vars(N,L) :-
205 arity_to_vars(N,[],L).
206arity_to_vars(N,L1,L2) :-
207 N > 0,
208 NN is N-1,
209 LT = [L|L1],
210 arity_to_vars(NN,LT,L2).
211arity_to_vars(0,L,L).
212
213/**
214@}
215*/
216
callable( ?_Goal_ )
catch( : Goal,+ Exception,+ Action)
throw(+ Ball)
bb_get(+ Key,? Term)
bb_put(+ Key,? Term)
assert(+ C)
erase(+ R)
recordz(+ K, T,- R)
goal_expansion( :G,+ M,- NG)
initialization(+ G)
call( 0:P )
call_cleanup(: Goal, : CleanUpGoal)
atom( T)
integer( T)
var( T)
on_cleanup(+ CleanUpGoal)