1/* Part of LogicMOO Base An Implementation a MUD server in SWI-Prolog
    2% ===================================================================
    3% File 'dcg_meta.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: 'logicmoo_util_bugger.pl' 1.0.0
    8% Revision:  $Revision: 1.1 $
    9% Created: $Date: 2002/07/11 21:57:28 $
   10% Revised At:   $Date: 2021/07/11 21:57:28 $
   11% ===================================================================
   12*/
   13:- module(dcg_must,[
   14	 dcg_peek/3]).

Utility LOGICMOO_DCG_MUST

Allows you to debug DCGs easier.

   22:- set_module(class(library)).   23
   24:- use_module(library(logicmoo_common)).   25
   26%dcg_must_each_det(G, S, E):- phrase(G, S, E), !.
   27quietly(DCG, S, E):- setup_call_cleanup(quietly(phrase(DCG, S, E)),true,true).
   28% quietly(DCG,S,E):- quietly(phrase(DCG,S,E)).
   29notrace(DCG,S,E):- quietly(DCG,S,E). %notrace(phrase(DCG,S,E)).
   30must(DCG,S,E):- must(phrase(DCG,S,E)).
   31ignore_must(DCG,S,E):- ignore_must(phrase(DCG,S,E)).
   32
   33dcg_if_defined(DCG,S,E):- catch(phrase(DCG,S,E),error(existence_error(procedure,_),context(_,_47656)),fail).
   34
   35dcg_peek(DCG,S,S):- phrase(DCG,S,_).
   36
   37dcg_must_each_det(_, S, _):- S == [], !, fail.
   38dcg_must_each_det((G1, G2), S, E):- !, must(phrase(G1, S, M)), !, dcg_must_each_det(G2, M, E), !.
   39dcg_must_each_det(G, S, E):- !, must(phrase(G, S, E)), !.
   40
   41dcg_and(DCG1, DCG2, S, E) :- dcg_condition(DCG1, S, E), phrase(DCG2, S, E), !.
   42dcg_unless(DCG1, DCG2, S, E) :- \+ dcg_condition(DCG1, S, _), !, phrase(DCG2, S, E).
   43dcg_when(DCG1, DCG2, S, E) :- dcg_condition(DCG1, S, _),!, phrase(DCG2, S, E).
   44dcg_length(Len,S,E):- \+ var(Len) -> (length(L,Len), append(L,E,S)); 
   45   (length(S,Full),between(Full,0,Len),length(L,Len), append(L,E,S)).
   46dcg_from_right(DCG1, DCG2, S, E) :- length(S,Full), between(Full,0,Start), dcg_scan(DCG1,Start,DCG2,S,E).
   47dcg_from_left(DCG1,  DCG2, S, E) :- length(S,Full), between(0,Full,Start), dcg_scan(DCG1,Start,DCG2,S,E).
   48
   49dcg_scan(DCG1,Start2,DCG2,S,E):- 
   50  length(Before,Start2), append(Before,Mid,S), \+ \+ phrase(DCG2, Mid, _), 
   51  phrase(DCG1, Before, []), phrase(DCG2, Mid, E).
   52
   53dcg_condition([], S, _):- S \== [], !, fail.
   54dcg_condition(DCG, S, E):- phrase(DCG, S, E).
   55
   56
   57% Push a new term onto DCG stack
   58dcg_push(List, S, ListS):- is_list(List), !, =(List,ListO), append(ListO, S, ListS).
   59dcg_push(A, S, [B|S]):- =(A,B).
   60
   61:- fixup_exports.