34
35:- module(each_call_cleanup,
36 [
37 each_call_cleanup/3, 38 each_call_catcher_cleanup/4, 39 redo_call_cleanup/3, 40 trusted_redo_call_cleanup/3 41 ]).
51:- meta_predicate
52 redo_call_cleanup(0,0,0),
53 call_then_cut(0),
54 each_call_catcher_cleanup(0,0,?,0),
55 each_call_cleanup(0,0,0),
56 trusted_redo_call_cleanup(0,0,0). 57
58
59
61
62call_then_cut(G):-
63 prolog_current_choice(CP),
64 prolog_choice_attribute(CP,parent,PC),
65 prolog_choice_attribute(PC,frame,Frame),prolog_frame_attribute(Frame,goal,PG),
66 prolog_choice_attribute(CP,frame,CFrame),prolog_frame_attribute(CFrame,goal,CG),nop(dmsg(call_then_cut(PG,CG))),
67 call((G,(deterministic(true)->prolog_cut_to(PC);true))).
68
69
70
71:- module_transparent(pt1/1). 72:- module_transparent(pt2/1).
80redo_call_cleanup(Setup,Goal,Cleanup):-
81 assertion(each_call_cleanup:unshared_vars(Setup,Goal,Cleanup)),
82 trusted_redo_call_cleanup(Setup,Goal,Cleanup).
83
84trusted_redo_call_cleanup(Setup,Goal,Cleanup):-
85 \+ \+ '$sig_atomic'(Setup),
86 catch(
87 ((Goal, deterministic(DET)),
88 '$sig_atomic'(Cleanup),
89 (DET == true -> !
90 ; (true;('$sig_atomic'(Setup),fail)))),
91 E,
92 ('$sig_atomic'(Cleanup),throw(E))).
100each_call_catcher_cleanup(Setup, Goal, Catcher, Cleanup):-
101 setup_call_catcher_cleanup(true,
102 each_call_cleanup(Setup, Goal, Cleanup), Catcher, true).
103
104:- thread_local(ecc:'$each_call_cleanup'/2). 105:- thread_local(ecc:'$each_call_undo'/2).
113each_call_cleanup(Setup,Goal,Cleanup):-
114 ((ground(Setup);ground(Cleanup)) ->
115 trusted_redo_call_cleanup(Setup,Goal,Cleanup);
116 setup_call_cleanup(
117 asserta((ecc:'$each_call_cleanup'(Setup,Cleanup)),HND),
118 trusted_redo_call_cleanup(pt1(HND),Goal,pt2(HND)),
119 (pt2(HND),erase(HND)))).
120
121 124
125ecc:throw_failure(Why):- throw(error(assertion_error(Why),_)).
126
127pt1(HND) :-
128 clause(ecc:'$each_call_cleanup'(Setup,Cleanup),true,HND)
129 ->
130 ('$sig_atomic'(Setup) ->
131 asserta(ecc:'$each_call_undo'(HND,Cleanup)) ;
132 ecc:throw_failure(failed_setup(Setup)))
133 ;
134 ecc:throw_failure(pt1(HND)).
135
136pt2(HND) :-
137 retract(ecc:'$each_call_undo'(HND,Cleanup)) ->
138 ('$sig_atomic'(Cleanup)->true ;ecc:throw_failure(failed_cleanup(Cleanup)));
139 ecc:throw_failure(failed('$each_call_undo'(HND))).
140
141:- if(true). 142:- system:import(each_call_cleanup/3). 143:- system:import(each_call_catcher_cleanup/4). 144:- system:import(redo_call_cleanup/3). 145:- system:import(pt1/1). 146:- system:import(pt2/1). 147:- endif. 148
151unshared_vars(Setup,_,_):- ground(Setup),!.
152unshared_vars(Setup,Goal,Cleanup):-
153 term_variables(Setup,SVs),
154 term_variables(Cleanup,CVs),
155 ( CVs==[] -> true; unshared_set(SVs,CVs)),
156 term_variables(Goal,GVs),
157 ( GVs==[] -> true;
158 (unshared_set(SVs,GVs),
159 unshared_set(CVs,GVs))).
160
161unshared_set([],_).
162unshared_set([E1|Set1],Set2):-
163 not_in_identical(E1,Set2),
164 unshared_set(Set1,Set2).
165
166not_in_identical(X, [Y|Ys]) :- X \== Y, not_in_identical(X, Ys)
Each call cleanup
Call Setup Goal Cleanup Each Iteration
*/