1% 2% extension to match regular expression (recognizer only, i.e., on success just move cursor) 3% 4:- module(rexp_pPEGxt, [re_match/6]). 5 6:- use_module(library(pcre),[re_matchsub/4]). 7 8re_match(RExp,_Env,Input,PosIn,PosOut,[]) :- 9 string_length(Input,ILen), PosIn < ILen, % guard against domain error 10 re_matchsub(RExp,Input,Sub,[start(PosIn),anchored(true)]), % pcre caches compiled RE's 11 string_length(Sub.0,Len), % length of matched string (0th entry of dict Sub) 12 PosOut is PosIn+Len. % move cursor