home *** CD-ROM | disk | FTP | other *** search
/ ftp.cs.yorku.ca 2015 / ftp.cs.yorku.ca.tar / ftp.cs.yorku.ca / pub / peter / SVT / clean.prolog < prev    next >
Text File  |  2002-07-29  |  3KB  |  99 lines

  1. /* 
  2.    clean.prolog cleans up a code fragment so that when converted to 
  3.    term, Prolog will parse it.
  4.   
  5.    contains various utilities used by both symbex and wp.
  6.  
  7. Version 1.1, March 28, 1998: added matchP, fixed clean so op can begin string.
  8.         1.4        brackets/3 turns array index expressions into terms.
  9.         string_to_term moved here (for both symbex & wp).
  10.         1.4.1, March 27: matchP and charsNoComm repaired, fixComment added.
  11.  
  12. :- module(cleanup, [clean/2, matchP/5, upto/5, break/2,
  13.             string_to_term/2]).
  14. */
  15.  
  16. :- ensure_loaded([library(basics), library(charsio), library(change_arg),
  17.           library(ctypes), library(lists)]).
  18.  
  19. clean(Old, New) :- 
  20.     parseOld(Prefix, NewSubstring, Old, Rest),
  21.     clean(Rest, NewRest), 
  22.     append([Prefix, NewSubstring, NewRest], New).
  23. clean(Old, Old).
  24.  
  25.  
  26. parseOld(Prefix, New) --> chars(Prefix), {matchOp(Old, New)}, Old.
  27.  
  28. string_to_term(String, Term) :-
  29.         clean(String, Cleaned),
  30.         brackets(Indexed, Cleaned, []),
  31.         chars_to_term(Indexed, Term1),
  32.         deIndex(Term1, Term).  
  33.  
  34. deIndex(Expr, Final) :-
  35.         path_arg(Path, Expr, Term),
  36.         Term =.. [F, 'INDEX'(Index)],
  37.         change_path_arg(Path, Expr, Modified, array(F, Index)),
  38.         !,
  39.         deIndex(Modified, Final).
  40. deIndex(Expr, Expr).      
  41.  
  42. % common grammatical rules
  43.  
  44. chars([C]) --> [C].
  45. chars([C | Rest]) --> [C], chars(Rest).
  46. chars([]) --> [].
  47.  
  48. upto([], C, Stop) --> C, ! ; Stop, !, {fail}.
  49. upto([X|Rest], C, Stop) --> [X], upto(Rest, C, Stop).  
  50.         % matches up to C inclusive
  51.     % requires a C in the string being matched to succeed
  52.     % requires a Stop to prevent scanning to end of string
  53.     % before failing. 
  54.  
  55. skip([X | Rest] , C) --> 
  56.     [X], { [X] \== C }, skip(Rest, C).
  57.          % chars up to and not including a stop character C   
  58.      % scans to end of the string if no C.
  59. skip([], _) --> [].
  60.  
  61. break --> [C], {is_space(C)}, break ; [].   
  62. %==============================================
  63.  
  64. matchOp("!=", "<>").
  65. matchOp("!", " not ").
  66. matchOp("||", " or ").
  67. matchOp("&&", " and ").
  68. matchOp("==", " = ").
  69. matchOp("0x", "16'").
  70.  
  71. matchP(LB, RB, String) --> LB, !, matched(LB, RB, String), RB.
  72. matched(LB, RB, String) --> 
  73.     matchP(LB, RB, S), 
  74.        (
  75.         {append([LB, S, RB], String)}
  76.        ;
  77.         matched(LB, RB, S1), {append([LB, S, RB, S1], String)}
  78.        ).
  79. matched(_, _, []) --> [].
  80. matched(LB, RB, [C | Rest]) -->  [C], matched(LB, RB, Rest).
  81.  
  82. bracket(E) -->
  83.     "[", matched("[", "]", Exp), "]",
  84.     { phrase(brackets(E), Exp)}.
  85.  
  86. brackets(S) -->
  87.     chars(Pre), bracket(E), brackets(Post),
  88.     {append([Pre, "('INDEX'(", E, "))", Post], S)}.
  89. brackets(S) --> chars(S).
  90.  
  91. fixComment(Fixed) -->
  92.         upto(Pre, "//", "//"), break, "{", 
  93.     upto(Comment, "}", "}"),
  94.     fixComment(F1),
  95.     { append([Pre, "//", [12], Comment, [12], F1], Fixed)}.
  96. fixComment(Fixed) --> chars(Fixed).
  97.  
  98.  
  99.