home *** CD-ROM | disk | FTP | other *** search
/ NetNews Usenet Archive 1992 #20 / NN_1992_20.iso / spool / comp / lang / prolog / 1663 < prev    next >
Encoding:
Internet Message Format  |  1992-09-08  |  3.0 KB

  1. Xref: sparky comp.lang.prolog:1663 comp.lang.c:13292
  2. Path: sparky!uunet!mcsun!sunic!dkuug!diku!torbenm
  3. From: torbenm@diku.dk (Torben AEgidius Mogensen)
  4. Newsgroups: comp.lang.prolog,comp.lang.c
  5. Subject: Re: Need code to match strings with regular expressions
  6. Message-ID: <1992Sep7.094208.13949@odin.diku.dk>
  7. Date: 7 Sep 92 09:42:08 GMT
  8. References: <82078@bcsaic.boeing.com>
  9. Sender: torbenm@freke.diku.dk
  10. Organization: Department of Computer Science, U of Copenhagen
  11. Lines: 103
  12.  
  13. milan@bcsaic.boeing.com (Milan Richter) writes:
  14.  
  15. >I am looking for a public domain code for matching strings with regular
  16. >expressions. Essentially, given a string and a regular expression (such as,
  17. >e.g., are used in emacs), I want to tell whether they match.
  18.  
  19. >Can anyone provide pointers to either C or Prolog implementation?
  20.  
  21. Below is a Prolog program that does this. It is not terribly
  22. efficient, as it doesn't generate an automaton but rewrites the
  23. regular expression as it reads the text. Partial evaluation with
  24. respect to the regular expression can yield a program equivalent to an
  25. automaton.
  26.  
  27.     Torben Mogensen (torbenm@diku.dk)
  28.  
  29.  
  30. % interpreter for regular expressions
  31.  
  32. :- op(300,yf,*).
  33. :- op(200,fx,`).
  34.  
  35. % R ::= empty       -- empty string
  36. %    |  ` Symbol    -- terminal symbol
  37. %    |  R ; R       -- alternative
  38. %    |  R , R       -- sequence
  39. %    |  R *         -- repetition
  40.  
  41. accepts(R,[]) :-
  42.     accepts_empty(R).
  43. accepts(R,[S|Ss]) :-
  44.     first(R,S),    % test if S can start R
  45.     next(R,S,R1),    % find reg-exp R1 for rest of string
  46.     accepts(R1,Ss).    % and test that
  47.  
  48.  
  49. accepts_empty(empty).
  50. accepts_empty((R1 ; R2)) :-
  51.     accepts_empty(R1) ->    % the use of -> reduces backtracking.
  52.      true ;            % ! could be used instead (but I hate !).
  53.      accepts_empty(R2).
  54. accepts_empty((R1 , R2)) :-
  55.     accepts_empty(R1),
  56.     accepts_empty(R2).
  57. accepts_empty(_ *).
  58.  
  59. first(` S,S).
  60. first((R1 ; R2),S) :-
  61.     first(R1,S) ;
  62.     (first(R2,S), \+ first(R1,S)).    % reduces backtracking (\+ is not)
  63. first((R1 , R2),S) :-
  64.     first(R1,S) ;
  65.     (accepts_empty(R1), first(R2,S), \+ first(R1,S)).    % ditto
  66. first(R *,S) :-
  67.     first(R,S).
  68.  
  69. next(` S,S,empty).
  70. next((R1 ; R2),S,R) :-
  71.     first(R1,S) ->
  72.      next(R1,S,R11),
  73.      (first(R2,S) ->
  74.        next(R2,S,R21),
  75.        reduce_or(R11,R21,R) ;
  76.        R = R11) ;
  77.      next(R2,S,R).
  78. next((R1 , R2),S,R) :-
  79.     first(R1,S) ->
  80.      next(R1,S,R11),
  81.      (accepts_empty(R1), first(R2,S) ->
  82. z       next(R2,S,R21),
  83.        reduce_seq(R11,R2,R3),
  84.        reduce_or(R3,R21,R) ;
  85.        reduce_seq(R11,R2,R)) ;
  86.      next(R2,S,R).
  87. next(R *,S,R2) :-
  88.     next(R,S,R1),
  89.     reduce_seq(R1,R *,R2).
  90.  
  91. % these reduce the derived regular expressions to avoid blow-up of size
  92.  
  93. reduce_or(R1,R2,R) :-
  94.     R1 = R2 ->
  95.      R = R1 ;
  96.      ((R1 = (R3,R2) ; R1 = (R2,R3)), accepts_empty(R3) ->
  97.        R = R1 ;
  98.        ((R2 = (R3,R1) ; R2 = (R1,R3)), accepts_empty(R3) ->
  99.          R = R2 ;
  100.          (R1 = (R2 ; _) ->
  101.            R = R1 ;
  102.            (R1 = (_ ; R2) ->
  103.              R = R1 ;
  104.          (R2 = (R1 ; _) ->
  105.                R = R2 ;
  106.                 (R2 = (_ ; R1) ->
  107.                   R = R2 ;
  108.                   R = (R1 ; R2))))))).
  109.  
  110. reduce_seq(R1,R2,R) :-
  111.     R1 = empty ->
  112.      R = R2 ;
  113.      (R2 = empty ->
  114.       R = R1 ;
  115.       R = (R1 , R2)).
  116.