1/* Part of LogicMOO Base Logicmoo Debug Tools
    2% ===================================================================
    3% File '$FILENAME.pl'
    4% Purpose: An Implementation in SWI-Prolog of certain debugging tools
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: '$FILENAME.pl' 1.0.0
    8% Revision: $Revision: 1.1 $
    9% Revised At:  $Date: 2002/07/11 21:57:28 $
   10% Licience: LGPL
   11% ===================================================================
   12*/
   13:- module(each_call_cleanup,
   14   [
   15      redo_call_cleanup/3,             % +Setup, +Goal, +Cleanup
   16      each_call_catcher_cleanup/4,     % +Setup, +Goal, ?Catcher, +Cleanup
   17      each_call_cleanup/3              % +Setup, +Goal, +Cleanup      
   18    ]).

Each call cleanup

Call Setup Goal Cleanup Each Iteration

See also
- https://groups.google.com/forum/#!searchin/comp.lang.prolog/redo_call_cleanup%7Csort:relevance/comp.lang.prolog/frH_4RzMAHg/2bBub5t6AwAJ

*/

   28:- meta_predicate
   29  redo_call_cleanup(0,0,0),
   30  each_call_catcher_cleanup(0,0,?,0),
   31  each_call_cleanup(0,0,0).
 redo_call_cleanup(:Setup, :Goal, :Cleanup)
@warn Setup/Cleanup do not share variables. If that is needed, use each_call_cleanup/3
   39redo_call_cleanup(Setup,Goal,Cleanup):- 
   40   must_be(ground,Setup),must_be(ground,Cleanup),
   41   % \+ \+ 
   42   '$sig_atomic'(Setup),
   43   catch( 
   44     ((Goal, deterministic(DET)),
   45       '$sig_atomic'(Cleanup),
   46         (DET == true -> !
   47          ; (true;('$sig_atomic'(Setup),fail)))), 
   48      E, 
   49      ('$sig_atomic'(Cleanup),throw(E))). 
 each_call_catcher_cleanup(:Setup, :Goal, +Catcher, :Cleanup)
Call Setup before Goal like normal but also before each Goal is redone. Also call Cleanup each time Goal is finished @bug Goal does not share variables with Setup/Cleanup Pairs
   58each_call_catcher_cleanup(Setup, Goal, Catcher, Cleanup):-
   59   setup_call_catcher_cleanup(true, 
   60     each_call_cleanup(Setup, Goal, Cleanup), Catcher, true).
 each_call_cleanup(:Setup, :Goal, :Cleanup)
Call Setup before Goal like normal but also before each Goal is redone. Also call Cleanup each time Goal is finished @bug Goal does not share variables with Setup/Cleanup Pairs
   69each_call_cleanup(Setup,Goal,Cleanup):- 
   70 ((ground(Setup);ground(Cleanup)) -> 
   71  redo_call_cleanup(Setup,Goal,Cleanup);
   72  setup_call_cleanup(
   73   asserta(('$each_call_cleanup'(Setup):-Cleanup),HND), 
   74   redo_call_cleanup(pt1(HND),Goal,pt2(HND)),
   75   erase(HND))).
   76
   77:- dynamic('$each_call_cleanup'/1).   78:- dynamic('$each_call_undo'/2).   79
   80pt1(HND) :- 
   81  clause('$each_call_cleanup'(Setup),Cleanup,HND),
   82    call(Setup),
   83      asserta('$each_call_undo'(HND,Cleanup)).
   84
   85pt2(HND) :- 
   86  retract('$each_call_undo'(HND,Cleanup))
   87    ->call(Cleanup);
   88      true