1:- module(dcg_util, [
    2    at_least//2,
    3    at_least//3,
    4    eos//0,
    5    exactly//2,
    6    exactly//3,
    7    followed_by//1,
    8    generous//2,
    9    greedy//1,
   10    greedy//2,
   11    list//3,
   12    parsing//0,
   13    when_generating//1,
   14    when_parsing//1
   15]).   16
   17:- use_module(library(clpfd)).
 at_least(N:nonneg, :Dcg)//
Like at_least//3 but discards the matches.
   22:- meta_predicate at_least(+,3,*,*).   23at_least(N,Goal) -->
   24    at_least(N,Goal,_).
 at_least(N:nonneg, :Dcg, Matches:list)//
Consumes at least N matches of Dcg. Dcg is called with one extra parameter which should be bound to a representation of what Dcg parsed. After N matches, it consumes as many more matches as possible.
   33:- meta_predicate at_least(+,3,?,*,*).   34at_least(N0,Goal,[X|Xs]) -->
   35    { N0 > 0 },
   36    !,
   37    call(Goal,X),
   38    { N is N0 - 1 },
   39    at_least(N,Goal,Xs).
   40at_least(0,Goal,Xs) -->
   41    greedy(Goal,Xs).
 exactly(N:nonneg, :Dcg)//
Like exactly//3 but discards the matches.
   47:- meta_predicate exactly(+,3,*,*).   48exactly(N,Goal) -->
   49    exactly(N,Goal,_).
 exactly(N:nonneg, :Dcg, Matches:list)//
Consumes exactly N matches of Dcg. Dcg is called with one extra parameter which should be bound to a representation of what Dcg parsed.
   57:- meta_predicate exactly(+,3,?,*,*).   58exactly(0,Goal,[]) -->
   59    ( parsing -> \+ call(Goal,_); [] ),
   60    !.
   61exactly(N0,Goal,[X|Xs]) -->
   62    { N0 #> 0 },    { N #= N0 - 1 },    call(Goal,X),    exactly(N,Goal,Xs).
 generous(:Goal, Matches:list)//
Consume as few matches of Goal as possible. Goal is called with one extra argument which should be bound to a representation of what Dcg parsed.
   73:- meta_predicate generous(3,-,*,*).   74generous(_Goal,[]) -->
   75    [].
   76generous(Goal,[X|Xs]) -->
   77    call(Goal,X),
   78    generous(Goal,Xs).
 greedy(:Dcg)//
Like greedy//2 but discards the matches.
   84:- meta_predicate greedy(3,*,*).   85greedy(Goal) -->
   86    greedy(Goal,_).
 greedy(:Dcg, Matches:list)//
Like generous//2 but consumes as many matches as possible. Gives back matches on backtracking.
   93:- meta_predicate greedy(3,-,*,*).   94greedy(Goal,[X|Xs]) -->
   95    call(Goal,X),
   96    greedy(Goal,Xs).
   97greedy(_,[]) -->
   98    [].
 list(:ElemDcg, :SeparatorDcg, Elems:list)//
Describes a list in which the elements match ElemDcg and the separators match SeparatorDcg. Elems is the list of elements found. The set of patterns matched by ElemDcg and SeparatorDcg should be disjoint. ElemDcg is called with one extra argument. SeparatorDcg is called without any extra arguments.

On backtracking, gives back elements and their associated separators. Always matches at least one element (without a trailing separator).

  111:- meta_predicate list(3,2,?,?,?).  112list(ElemDCG, SepDCG, [Elem|Tail]) -->
  113    call(ElemDCG, Elem),
  114    ( call(SepDCG),
  115      list(ElemDCG, SepDCG, Tail)
  116    ; "",
  117      { Tail = [] }
  118    ).
 followed_by(:Dcg)//
True if Dcg would match. Consumes nothing.
  124:- meta_predicate followed_by(//,*,*).  125followed_by(Goal) -->
  126    \+ \+ Goal.
 eos//
Matches the end of string position.
  132eos([],[]).
 when_generating(:Goal)//
Call Goal when the DCG operates in generator mode. Otherwise, it's a noop.
  139:- meta_predicate when_generating(0,?,?).  140when_generating(Goal) -->
  141    ( parsing -> []; { call(Goal) } ).
 when_parsing(:Goal)//
Call Goal when the DCG operates in parsing mode. Otherwise, it's a noop.
  148:- meta_predicate when_parsing(0,?,?).  149when_parsing(Goal) -->
  150    ( parsing -> { call(Goal) }; [] ).
 parsing// is semidet
True if the DCG is operating as a parser. Specifically, the DCG list is not a variable.
  157parsing(H,H) :-
  158    nonvar(H)