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)).
22:- meta_predicate at_least( , , , ). 23at_least(N,Goal) --> 24 at_least(N,Goal,_).
33:- meta_predicate at_least( , , , , ). 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).
47:- meta_predicate exactly( , , , ). 48exactly(N,Goal) --> 49 exactly(N,Goal,_).
57:- meta_predicate exactly( , , , , ). 58exactly(0,Goal,[]) --> 59 ( parsing -> \+ call(Goal,_); [] ), 60 !. 61exactly(N0,Goal,[X|Xs]) --> 62 { N0 #> 0 }, 63 { N #= N0 - 1 }, 64 call(Goal,X), 65 exactly(N,Goal,Xs).
73:- meta_predicate generous( , , , ). 74generous(_Goal,[]) --> 75 []. 76generous(Goal,[X|Xs]) --> 77 call(Goal,X), 78 generous(Goal,Xs).
84:- meta_predicate greedy( , , ). 85greedy(Goal) --> 86 greedy(Goal,_).
93:- meta_predicate greedy( , , , ). 94greedy(Goal,[X|Xs]) --> 95 call(Goal,X), 96 greedy(Goal,Xs). 97greedy(_,[]) --> 98 [].
On backtracking, gives back elements and their associated separators. Always matches at least one element (without a trailing separator).
111:- meta_predicate list( , , , , ). 112list(ElemDCG, SepDCG, [Elem|Tail]) --> 113 call(ElemDCG, Elem), 114 ( call(SepDCG), 115 list(ElemDCG, SepDCG, Tail) 116 ; "", 117 { Tail = [] } 118 ).
124:- meta_predicate followed_by( , , ). 125followed_by(Goal) --> 126 \+ \+ .
132eos([],[]).
139:- meta_predicate when_generating( , , ). 140when_generating(Goal) --> 141 ( parsing -> []; { call(Goal) } ).
148:- meta_predicate when_parsing( , , ). 149when_parsing(Goal) --> 150 ( parsing -> { call(Goal) }; [] ).
157parsing(H,H) :-
158 nonvar(H)