1/* Part of LogicMOO Base Logicmoo Debug Tools
    2% ===================================================================
    3% File 'with_no_x.pl'
    4% Purpose: An Implementation in SWI-Prolog of certain debugging tools
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles logicmoo@gmail.com ;
    7% Version: 'with_no_x.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% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/util/logicmoo_util_with_assertions.pl
   14:- module(with_no_x,[ with_no_x/1, with_no_xdbg/1, no_x_flags/0, with_no_x_flag/2, no_xdbg_flags/0, with_no_xdbg_flag/2]).

Utility LOGICMOO WITH NO X

Suspends use of X Windows temporarily for headless code.

   22:- meta_predicate with_no_x(:).   23:- meta_predicate with_no_xdbg(:).   24
   25:- thread_local(tlbugger:show_must_go_on/1).   26% WAS OFF  :- system:use_module(library(gui_tracer)).
 with_no_x(:Goal) is nondet
Using No X.
   33with_no_x_flag(gui_tracer,false).
   34with_no_x_flag(nodebugx,true).
   35with_no_x_flag(xpce,false).
   36with_no_x_flag(no_sandbox,true).
   37
   38no_x_flags:- forall(with_no_x_flag(X,V),set_prolog_flag(X,V)).
   39
   40with_no_x(G):- getenv('DISPLAY',DISP),!,call_cleanup((unsetenv('DISPLAY'),with_no_x(G)),setenv('DISPLAY',DISP)).
   41with_no_x(G):- with_no_x_flag(X,V),current_prolog_flag(X,Was),Was\==V,!,
   42 call_cleanup((set_prolog_flag(X,V),with_no_x(G)),set_prolog_flag(X,Was)).
   43with_no_x(G):- locally_each(tlbugger:show_must_go_on(true),call(G)).
   44
   45with_no_xdbg_flag(gui_tracer, false).
   46with_no_xdbg_flag(backtrace,false).
   47with_no_xdbg_flag(debug_threads,false).
   48with_no_xdbg_flag(debug,false).
   49with_no_xdbg_flag(report_error,false).
   50with_no_xdbg_flag(debug_on_error,false).
   51%with_no_xdbg_flag(autoload,true).
   52with_no_xdbg_flag(trace_gc,false).
   53with_no_xdbg_flag(debug_term_position,false).
   54with_no_xdbg_flag(warn_override_implicit_import,false).
   55
   56with_no_xdbg_flag(verbose_file_search,false).
   57with_no_xdbg_flag(verbose_autoload,false).
   58with_no_xdbg_flag(verbose_load,false).
   59with_no_xdbg_flag(verbose,silent).
   60
   61%with_no_xdbg_flag(unknown,warning).
   62
   63no_xdbg_flags:- forall(with_no_xdbg_flag(X,V),set_prolog_flag(X,V)).
   64
   65with_no_xdbg(G):- tracing,!,call_cleanup((notrace,with_no_xdbg(G)),trace).
   66with_no_xdbg(G):- with_no_xdbg_flag(X,V),
   67  current_prolog_flag(X,Was),Was\==V,!,call_cleanup((set_prolog_flag(X,V),with_no_xdbg(G)),set_prolog_flag(X,Was)).
   68with_no_xdbg(G):- with_no_x(G)