3:- module(with, [
    4              with/2,           % +Term, :Goal
    5              manage_context/3 % +Term, :Setup, :Cleanup
    6          ]).

Context managers for SWI Prolog

This module provides context management for various types of Prolog objects, such as IO streams, dynamic clauses, and settings. User defined contexts can be implemented using the multifile predicate manage_context/3. manage_context(Term, Setup, Cleanup) defines a setup/cleanup pair for a specific type of term. `with(Term, Goal)` calls Goal using setup_call_cleanup/3, with the corresponding setup and cleanup goals.

There is one difference between the semantics of setup_call_cleanup/3 and the corresponding goal using this library. Setup and Cleanup goals must succeed. If they fail, the error `error(mode_error(must_succeed, FailingGoal))` is thrown.

For example, the provided manage_context/3 clause for opening files could be defined:

with:manage_context(open(File, Mode, Stream),
                    open(File, Mode, Stream),
                    close(Stream)).

The result is that the following are equivalent:

?- setup_call_cleanup(open(File, read, Stream),
   is_stream(Stream),
   close(Stream)).

?- use_module(library(with)),
   with(open(File, read, Stream),
        is_stream(Stream)).

To show defined context managers, using `listing/1`. E.g, the context managers packaged with this module are:

?- use_module(library(with)), listing(with:manage_context/3).

manage_context(open(A, C, D),  (absolute_file_name(A, B), open(B, C, D)), close(D)).
manage_context(assertz(A), assertz(A, B), erase(B)).
manage_context(setting(A, B),  (setting(A, C), set_setting(A, B)), set_setting(A, C)).
author
- Eyal Dechter <eyaldechter@gmail.com>

*/

 with(+Term, :Goal) is det
Call Goal with the context manager associated with Term.
throws
- error(instantiation_error, _) If Term is a variable.
- error(mode_error(must_succeed, Goal)) If Goal is a setup or cleanup goal for context and Goal does not succeed.
   70:- meta_predicate with(:, 0).   71with(MList, Goal) :-
   72    strip_module(MList, M, List),
   73    is_list(List),
   74    !,
   75    collect_context_managers(List, M, SetupGoals, CleanupGoals),
   76    setup_call_cleanup(maplist(call, SetupGoals),
   77                       Goal,
   78                       maplist(call, CleanupGoals)
   79                      ).
   80with(MTerm, Goal) :-
   81    strip_module(MTerm, M, Term),
   82    with(M:[Term], Goal).
 collect_context_managers(+Terms:list, +Mod:atom, -SetupGoals:list, -CleanupGoals:list) is det
   87collect_context_managers([], _, [], []).
   88collect_context_managers([Term|Rest], M, [SetupGoal|SGs], [CleanupGoal|CGs]) :-
   89    (term_has_context_manager(Term, M, Setup, Cleanup) ->
   90         SetupGoal = ctx_must_succeed(Setup),
   91         CleanupGoal = ctx_must_succeed(Cleanup)
   92    ;
   93    existence_error(context_manager, M:Term)
   94    ),
   95    collect_context_managers(Rest, M, SGs, CGs).
   96
   97
   98ctx_must_succeed(M:Goal) :-
   99    (M:Goal -> true
  100    ;
  101    throw(error(mode_error(must_succeed, M:Goal), _))
  102    ).
 term_has_context_manager(+Term, +Module, -Setup:callable, -Cleanup:cleanup) is semidet
True if there is a unique context manager for Term.
  108term_has_context_manager(Term, M, M:Setup, M:Cleanup) :-
  109    must_be(nonvar, Term),
  110    manage_context(Term, Setup, Cleanup).
 manage_context(Term, :Setup, :Cleanup) is det
If true, goals Setup and Cleanup are called to manage context associated with Term. Use this multifile predicate to define context managers.
  119:- multifile manage_context/3.  120
  121
  122/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  123     IO Stream context managers
  124- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  125manage_context(open(File, Mode, Stream),
  126               (
  127                   absolute_file_name(File, AbsFile), 
  128                   open(AbsFile, Mode, Stream)
  129               ),
  130               close(Stream)).
  131
  132/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  133     Dynamic DB context managers
  134- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  135manage_context(assertz(Clause), assertz(Clause, Ref), erase(Ref)).
  136manage_context(asserta(Clause), asserta(Clause, Ref), erase(Ref)).
  137
  138
  139
  140/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  141     library(settings) context managers
  142- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  143manage_context(setting(Setting, NewValue),
  144               (
  145                   setting(Setting, OldValue),
  146                   set_setting(Setting, NewValue)
  147               ),
  148               set_setting(Setting, OldValue)
  149              ).
  150
  151/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  152     library(debug) context managers
  153- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  154manage_context(debug(Spec),
  155               (
  156                   prolog_debug:debug_target(Spec, Topic, _),
  157                   (debugging(Topic, Previous) -> true; Previous = false),
  158                   debug(Spec)
  159               ),
  160               (
  161                   nodebug(Spec),
  162                   ( (Previous == true, debugging(Topic, false)) ->
  163                          debug(Topic)
  164                     ;
  165                     true
  166                   )
  167               )
  168              ).
  169
  170manage_context(nodebug(Spec),
  171               nodebug(Spec),
  172               debug(Spec)). 
  173
  174                     
  175                
  176
  177/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  178     setenv/unsetenv context manager 
  179- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  180manage_context(setenv(Name, Value),
  181               (
  182                   (getenv(Name, V) ->
  183                        Previous = just(V)                        
  184                   ;
  185                   Previous = nothing                   
  186                   ),
  187                  setenv(Name, Value) 
  188               ),
  189               (Previous = just(V) ->
  190                    setenv(Name, V)
  191               ;
  192               unsetenv(Name)                   
  193               )
  194              ).
  195
  196/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  197     set_prolog_flag context manager
  198- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  199manage_context(set_prolog_flag(Name, NewValue),
  200               (
  201                   (current_prolog_flag(Name, OldValue) ->
  202                        set_prolog_flag(Name, NewValue)
  203                   ;
  204                   existence_error(prolog_flag, Name)
  205                   )
  206               ),
  207               set_prolog_flag(Name, OldValue)
  208              )