1/* Part of dcgutils
    2	Copyright 2012-2015 Samer Abdallah (Queen Mary University of London; UCL)
    3	 
    4	This program is free software; you can redistribute it and/or
    5	modify it under the terms of the GNU Lesser General Public License
    6	as published by the Free Software Foundation; either version 2
    7	of the License, or (at your option) any later version.
    8
    9	This program is distributed in the hope that it will be useful,
   10	but WITHOUT ANY WARRANTY; without even the implied warranty of
   11	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   12	GNU Lesser General Public License for more details.
   13
   14	You should have received a copy of the GNU Lesser General Public
   15	License along with this library; if not, write to the Free Software
   16	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   17*/
   18
   19:- module(dcg_shell,
   20	[	dcgshell/2
   21	,	dcgshell/3
   22	,	dcgshell/4
   23	,	make//0
   24	,	help/3
   25	,	time//1, time//2, time//3
   26	,	profile_phrase//1
   27	,	trace//1
   28	,	catch//3
   29	]).   30
   31
   32:- module_transparent 	
   33		dcgshell/2, dcgshell/3, dcgshell/4,
   34		dcgshell_x/6, shell_prompt/4, make//0.   35
   36:- use_module(library(termutils), [get_key/2]).
 dcgshell(+Interp, +Id, ?S1, ?S2) is semidet
 dcgshell(+Id, ?S1, ?S2) is semidet
 dcgshell(?S1, ?S2) is semidet
Runs an interactive shell where typed commands are interepreted as DCG phrases. The cumulative result of all these phrases takes the DCG state from S1 to S2. If present, Id is used to identify the shell and is written as part of the prompt. The default prompt is 'dcg'.

Pressing Ctrl-D at the prompt or typing 'halt' or 'end_of_file' terminates the shell unifying S2 with the final state. The command 'fail' terminates the shell and causes dcgshell/2 or dcgshell/3 as a whole to fail, without leaving any choice points.

dcgshell/4 allows the specification of an alternate interpreter other than call_dcg/3, which is the default in the other forms.

Special commands

module(M)
Switches context module of interpreter to M.
interp(I)
Change to a new interpreter. Eg, interp(time) will cause timing information to be printed after each command is interpreted.
X ^ Phrase
Causes Phrase to be interpreted after binding X to the id of the current interpreter. Since the id can be any term, you can use it as simple sort of environment in which you can keep data that might be useful later on.
   69dcgshell(S1,S2) :- dcgshell(call_dcg,dcg,S1,S2). 
   70dcgshell(Id,S1,S2) :- dcgshell(call_dcg,Id,S1,S2). 
   71dcgshell(Interp,Id,S1,S2) :- !,
   72	shell_prompt(Id,Interp,Goal,Bindings),
   73	dcgshell_x(Goal,Bindings,Interp,Id,S1,S2).
   74
   75
   76shell_prompt(Id,Interp,Goal,Bindings) :-
   77	context_module(Mod),
   78	format(atom(NA),'~p: ~p (~W) >> ',[Mod,Interp,Id,[portray(true),quoted(true),max_depth(3)]]),
   79	read_history(h,'!h',[trace,end_of_file],NA, Goal, Bindings).
   80
   81dcgshell_x(fail,_,_,_,_,_) :- !, fail.
   82dcgshell_x(halt,_,_,_,S,S) :- !, nl.
   83dcgshell_x(end_of_file,_,_,_,S,S) :- !, nl.
   84dcgshell_x(module(Mod),_,Interp,Id,S1,S2) :- !, @(dcgshell(Interp,Id,S1,S2), Mod).
   85dcgshell_x(interp(Int2),_,Int1,Id,S1,S2) :- !, 
   86	format('Changing interpreter from ~w to ~w.\n',[Int1,Int2]),
   87	dcgshell(Int2,Id,S1,S2).
   88
   89dcgshell_x(X^Goal,Bindings,Interp,Id,S1,S2) :- !,
   90	X=Id, dcgshell_x(Goal,Bindings,Interp,Id,S1,S2).
   91
   92dcgshell_x(Goal,Bindings,Interp,Id,S0,S2) :- !,
   93	catch( 
   94		(	current_prolog_flag(prompt_alternatives_on,PromptOn),
   95			call(Interp,Goal,S0,S1), 
   96			include(dcg_shell:bound,Bindings,BoundBindings),
   97			(	BoundBindings=[] 
   98			->	(	PromptOn=determinism
   99				->	write('\nok? [.,<return>=yes,;=no] '), 
  100               dcg_shell:get_key([';','\r','.'],K), (K='\r';K='.'), nl 
  101				;	true)
  102			;	dcg_shell:check_bindings(BoundBindings)
  103			),
  104			write('  Yes.\n\n')
  105		;	write('\n  No.\n'), S0=S1
  106		),
  107		Exception,
  108		(	Exception=dcg_shell:escape(Ex) -> throw(Ex)
  109		;	nl, print_message(error,Exception), S1=S0, nl)
  110	), !, 
  111	dcgshell(Interp,Id,S1,S2).
  112
  113bound(_=Value) :- nonvar(Value).
  114
  115
  116
  117% useful DCG shell commands
 make// is det
DCG shell command to update loaded files, just as with make/0.
  122make --> {make}.
 help(+Topic)// is det
Look-up help on Topic, just as with help/1.
  127help(A) --> {help(A)}.
 time(+G:phrase(S))// is semidet
 time(+G:pred(A,S,S), ?X:A)// is semidet
 time(+G:pred(A,B,S,S), ?X:A, ?Y:B)// is semidet
Time execution of DCG phrase G. Any extra arguments are passed to G as in call/N.
  136:- meta_predicate time(//,?,?), time(3,?,?,?), time(4,?,?,?,?).  137time(G,A,B) :- time(call_dcg(G,A,B)).
  138time(G,A,B,C) :- time(call(G,A,B,C)).
  139time(G,A,B,C,D) :- time(call(G,A,B,C,D)).
 profile_phrase(+G:phrase(_))// is semidet
Profile execution of DCG phrase G.
  144:- meta_predicate profile_phrase(//,?,?).  145profile_phrase(G,A,B) :- profile(call_dcg(G,A,B)).
  146
  147
  148:- meta_predicate catch(//,?,//,?,?).  149catch(Phrase,Ex,Handler,S1,S2) :-
  150	catch(call_dcg(Phrase,S1,S2),
  151		Ex, call_dcg(Handler,S1,S2)).
  152
  153:- meta_predicate trace(//,?,?).  154trace(Goal,S1,S2) :-
  155	setup_call_cleanup( trace, call_dcg(Goal,S1,S2), notrace).
  156
  157% ----------------------------- Extract from meta.pl ------------------------
 check_bindings(+Bindings:list(binding)) is semidet
Allow user to review variable bindings. Fails if the user rejects the current set of values. Bindings is a list of Name=Value pairs, ie
binding ---> (atom=term).

The current Prolog flags are used to determine the print format (see answer_write_options in current_prolog_flag/2).

  171check_bindings([]) :- nl. % !! Do we always want this?
  172check_bindings([B|BT]) :-
  173	current_prolog_flag(answer_write_options,Opts),
  174	write_bindings(Opts,[B|BT]),
  175	get_key([';','\r','.'],K), (K='\r';K='.'), nl. 
 write_bindings(+Bindings:list(binding)) is semidet
Allow user to view variable bindings without any interaction. Bindings is a list of Name=Value pairs.

The current Prolog flags are used to determine the print format (see answer_write_options in current_prolog_flag/2).

  186write_bindings([]) :- !. % !! Do we always want this?
  187write_bindings(B) :-
  188	current_prolog_flag(answer_write_options,Opts),
  189	write_bindings(Opts,B), nl, nl.
  190
  191write_bindings(Opts,[N=V]) :- 
  192	(	true % nonvar(V)
  193	->	format('\n  ~w = ~@ ',[N,write_term(V,Opts)])
  194	;	true
  195	).
  196
  197write_bindings(Opts,[N=V,X|T]) :- 
  198	(	true % nonvar(V)
  199	->	format('\n  ~w = ~@ ',[N,write_term(V,Opts)])
  200	;	true
  201	),
  202	write_bindings(Opts,[X|T])