1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT LIBRARY COMPONENTS                          --
4--                                                                          --
5--                          G N A T . R E G P A T                           --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--               Copyright (C) 1986 by University of Toronto.               --
10--           Copyright (C) 1996-2003 Ada Core Technologies, Inc.            --
11--                                                                          --
12-- GNAT is free software;  you can  redistribute it  and/or modify it under --
13-- terms of the  GNU General Public License as published  by the Free Soft- --
14-- ware  Foundation;  either version 2,  or (at your option) any later ver- --
15-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
16-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
17-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
18-- for  more details.  You should have  received  a copy of the GNU General --
19-- Public License  distributed with GNAT;  see file COPYING.  If not, write --
20-- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
21-- MA 02111-1307, USA.                                                      --
22--                                                                          --
23-- As a special exception,  if other files  instantiate  generics from this --
24-- unit, or you link  this unit with other files  to produce an executable, --
25-- this  unit  does not  by itself cause  the resulting  executable  to  be --
26-- covered  by the  GNU  General  Public  License.  This exception does not --
27-- however invalidate  any other reasons why  the executable file  might be --
28-- covered by the  GNU Public License.                                      --
29--                                                                          --
30-- GNAT was originally developed  by the GNAT team at  New York University. --
31-- Extensive contributions were provided by Ada Core Technologies Inc.      --
32--                                                                          --
33------------------------------------------------------------------------------
34
35--  This package implements roughly the same set of regular expressions as
36--  are available in the Perl or Python programming languages.
37
38--  This is an extension of the original V7 style regular expression library
39--  written in C by Henry Spencer. Apart from the translation to Ada, the
40--  interface has been considerably changed to use the Ada String type
41--  instead of C-style nul-terminated strings.
42
43------------------------------------------------------------
44-- Summary of Pattern Matching Packages in GNAT Hierarchy --
45------------------------------------------------------------
46
47--  There are three related packages that perform pattern maching functions.
48--  the following is an outline of these packages, to help you determine
49--  which is best for your needs.
50
51--     GNAT.Regexp (files g-regexp.ads/g-regexp.adb)
52--       This is a simple package providing Unix-style regular expression
53--       matching with the restriction that it matches entire strings. It
54--       is particularly useful for file name matching, and in particular
55--       it provides "globbing patterns" that are useful in implementing
56--       unix or DOS style wild card matching for file names.
57
58--     GNAT.Regpat (files g-regpat.ads/g-regpat.adb)
59--       This is a more complete implementation of Unix-style regular
60--       expressions, copied from the Perl regular expression engine,
61--       written originally in C by Henry Spencer. It is functionally the
62--       same as that library.
63
64--     GNAT.Spitbol.Patterns (files g-spipat.ads/g-spipat.adb)
65--       This is a completely general pattern matching package based on the
66--       pattern language of SNOBOL4, as implemented in SPITBOL. The pattern
67--       language is modeled on context free grammars, with context sensitive
68--       extensions that provide full (type 0) computational capabilities.
69
70package GNAT.Regpat is
71pragma Preelaborate (Regpat);
72
73   --  The grammar is the following:
74
75   --     regexp ::= expr
76   --            ::= ^ expr               -- anchor at the beginning of string
77   --            ::= expr $               -- anchor at the end of string
78
79   --     expr   ::= term
80   --            ::= term | term          -- alternation (term or term ...)
81
82   --     term   ::= item
83   --            ::= item item ...        -- concatenation (item then item)
84
85   --     item   ::= elmt                 -- match elmt
86   --            ::= elmt *               -- zero or more elmt's
87   --            ::= elmt +               -- one or more elmt's
88   --            ::= elmt ?               -- matches elmt or nothing
89   --            ::= elmt *?              -- zero or more times, minimum number
90   --            ::= elmt +?              -- one or more times, minimum number
91   --            ::= elmt ??              -- zero or one time, minimum number
92   --            ::= elmt { num }         -- matches elmt exactly num times
93   --            ::= elmt { num , }       -- matches elmt at least num times
94   --            ::= elmt { num , num2 }  -- matches between num and num2 times
95   --            ::= elmt { num }?        -- matches elmt exactly num times
96   --            ::= elmt { num , }?      -- matches elmt at least num times
97   --                                        non-greedy version
98   --            ::= elmt { num , num2 }? -- matches between num and num2 times
99   --                                        non-greedy version
100
101   --     elmt   ::= nchr                 -- matches given character
102   --            ::= [range range ...]    -- matches any character listed
103   --            ::= [^ range range ...]  -- matches any character not listed
104   --            ::= .                    -- matches any single character
105   --                                     -- except newlines
106   --            ::= ( expr )             -- parens used for grouping
107   --            ::= \ num                -- reference to num-th parenthesis
108
109   --     range  ::= char - char          -- matches chars in given range
110   --            ::= nchr
111   --            ::= [: posix :]          -- any character in the POSIX range
112   --            ::= [:^ posix :]         -- not in the POSIX range
113
114   --     posix  ::= alnum                -- alphanumeric characters
115   --            ::= alpha                -- alphabetic characters
116   --            ::= ascii                -- ascii characters (0 .. 127)
117   --            ::= cntrl                -- control chars (0..31, 127..159)
118   --            ::= digit                -- digits ('0' .. '9')
119   --            ::= graph                -- graphic chars (32..126, 160..255)
120   --            ::= lower                -- lower case characters
121   --            ::= print                -- printable characters (32..127)
122   --            ::= punct                -- printable, except alphanumeric
123   --            ::= space                -- space characters
124   --            ::= upper                -- upper case characters
125   --            ::= word                 -- alphanumeric characters
126   --            ::= xdigit               -- hexadecimal chars (0..9, a..f)
127
128   --     char   ::= any character, including special characters
129   --                ASCII.NUL is not supported.
130
131   --     nchr   ::= any character except \()[].*+?^ or \char to match char
132   --                \n means a newline (ASCII.LF)
133   --                \t means a tab (ASCII.HT)
134   --                \r means a return (ASCII.CR)
135   --                \b matches the empty string at the beginning or end of a
136   --                   word. A word is defined as a set of alphanumerical
137   --                   characters (see \w below).
138   --                \B matches the empty string only when *not* at the
139   --                   beginning or end of a word.
140   --                \d matches any digit character ([0-9])
141   --                \D matches any non digit character ([^0-9])
142   --                \s matches any white space character. This is equivalent
143   --                   to [ \t\n\r\f\v]  (tab, form-feed, vertical-tab,...
144   --                \S matches any non-white space character.
145   --                \w matches any alphanumeric character or underscore.
146   --                   This include accented letters, as defined in the
147   --                   package Ada.Characters.Handling.
148   --                \W matches any non-alphanumeric character.
149   --                \A match the empty string only at the beginning of the
150   --                   string, whatever flags are used for Compile (the
151   --                   behavior of ^ can change, see Regexp_Flags below).
152   --                \G match the empty string only at the end of the
153   --                   string, whatever flags are used for Compile (the
154   --                   behavior of $ can change, see Regexp_Flags below).
155   --     ...    ::= is used to indication repetition (one or more terms)
156
157   --  Embedded newlines are not matched by the ^ operator.
158   --  It is possible to retrieve the substring matched a parenthesis
159   --  expression. Although the depth of parenthesis is not limited in the
160   --  regexp, only the first 9 substrings can be retrieved.
161
162   --  The highest value possible for the arguments to the curly operator ({})
163   --  are given by the constant Max_Curly_Repeat below.
164
165   --  The operators '*', '+', '?' and '{}' always match the longest possible
166   --  substring. They all have a non-greedy version (with an extra ? after the
167   --  operator), which matches the shortest possible substring.
168
169   --  For instance:
170   --      regexp="<.*>"   string="<h1>title</h1>"   matches="<h1>title</h1>"
171   --      regexp="<.*?>"  string="<h1>title</h1>"   matches="<h1>"
172   --
173   --  '{' and '}' are only considered as special characters if they appear
174   --  in a substring that looks exactly like '{n}', '{n,m}' or '{n,}', where
175   --  n and m are digits. No space is allowed. In other contexts, the curly
176   --  braces will simply be treated as normal characters.
177
178   --  Compiling Regular Expressions
179   --  =============================
180
181   --  To use this package, you first need to compile the regular expression
182   --  (a string) into a byte-code program, in a Pattern_Matcher structure.
183   --  This first step checks that the regexp is valid, and optimizes the
184   --  matching algorithms of the second step.
185
186   --  Two versions of the Compile subprogram are given: one in which this
187   --  package will compute itself the best possible size to allocate for the
188   --  byte code; the other where you must allocate enough memory yourself. An
189   --  exception is raised if there is not enough memory.
190
191   --     declare
192   --        Regexp : String := "a|b";
193
194   --        Matcher : Pattern_Matcher := Compile (Regexp);
195   --        --  The size for matcher is automatically allocated
196
197   --        Matcher2 : Pattern_Matcher (1000);
198   --        --  Some space is allocated directly.
199
200   --     begin
201   --        Compile (Matcher2, Regexp);
202   --        ...
203   --     end;
204
205   --  Note that the second version is significantly faster, since with the
206   --  first version the regular expression has in fact to be compiled twice
207   --  (first to compute the size, then to generate the byte code).
208
209   --  Note also that you can not use the function version of Compile if you
210   --  specify the size of the Pattern_Matcher, since the discriminants will
211   --  most probably be different and you will get a Constraint_Error
212
213   --  Matching Strings
214   --  ================
215
216   --  Once the regular expression has been compiled, you can use it as often
217   --  as needed to match strings.
218
219   --  Several versions of the Match subprogram are provided, with different
220   --  parameters and return results.
221
222   --  See the description under each of these subprograms.
223
224   --  Here is a short example showing how to get the substring matched by
225   --  the first parenthesis pair.
226
227   --     declare
228   --        Matches : Match_Array (0 .. 1);
229   --        Regexp  : String := "a(b|c)d";
230   --        Str     : String := "gacdg";
231
232   --     begin
233   --        Match (Compile (Regexp), Str, Matches);
234   --        return Str (Matches (1).First .. Matches (1).Last);
235   --        --  returns 'c'
236   --     end;
237
238   --  Finding all occurrences
239   --  =======================
240
241   --  Finding all the occurrences of a regular expression in a string cannot
242   --  be done by simply passing a slice of the string. This wouldn't work for
243   --  anchored regular expressions (the ones starting with "^" or ending with
244   --  "$").
245   --  Instead, you need to use the last parameter to Match (Data_First), as in
246   --  the following loop:
247
248   --     declare
249   --        Str     : String :=
250   --           "-- first line" & ASCII.LF & "-- second line";
251   --        Matches : Match_array (0 .. 0);
252   --        Regexp  : Pattern_Matcher := Compile ("^--", Multiple_Lines);
253   --        Current : Natural := Str'First;
254   --     begin
255   --        loop
256   --           Match (Regexp, Str, Matches, Current);
257   --           exit when Matches (0) = No_Match;
258   --
259   --           --  Process the match at position Matches (0).First
260   --
261   --           Current := Matches (0).Last + 1;
262   --        end loop;
263   --     end;
264
265   --  String Substitution
266   --  ===================
267
268   --  No subprogram is currently provided for string substitution.
269   --  However, this is easy to simulate with the parenthesis groups, as
270   --  shown below.
271
272   --  This example swaps the first two words of the string:
273
274   --     declare
275   --        Regexp  : String := "([a-z]+) +([a-z]+)";
276   --        Str     : String := " first   second third ";
277   --        Matches : Match_Array (0 .. 2);
278
279   --     begin
280   --        Match (Compile (Regexp), Str, Matches);
281   --        return Str (Str'First .. Matches (1).First - 1)
282   --               & Str (Matches (2).First .. Matches (2).Last)
283   --               & " "
284   --               & Str (Matches (1).First .. Matches (1).Last)
285   --               & Str (Matches (2).Last + 1 .. Str'Last);
286   --        --  returns " second first third "
287   --     end;
288
289   ---------------
290   -- Constants --
291   ---------------
292
293   Expression_Error : exception;
294   --  This exception is raised when trying to compile an invalid
295   --  regular expression. All subprograms taking an expression
296   --  as parameter may raise Expression_Error.
297
298   Max_Paren_Count : constant := 255;
299   --  Maximum number of parenthesis in a regular expression.
300   --  This is limited by the size of a Character, as found in the
301   --  byte-compiled version of regular expressions.
302
303   Max_Program_Size : constant := 2**15 - 1;
304   --  Maximum size that can be allocated for a program
305
306   Max_Curly_Repeat : constant := 32767;
307   --  Maximum number of repetition for the curly operator.
308   --  The digits in the {n}, {n,} and {n,m } operators can not be higher
309   --  than this constant, since they have to fit on two characters in the
310   --  byte-compiled version of regular expressions.
311
312   type Program_Size is range 0 .. Max_Program_Size;
313   for Program_Size'Size use 16;
314   --  Number of bytes allocated for the byte-compiled version of a regular
315   --  expression.
316
317   type Regexp_Flags is mod 256;
318   for Regexp_Flags'Size use 8;
319   --  Flags that can be given at compile time to specify default
320   --  properties for the regular expression.
321
322   No_Flags         : constant Regexp_Flags;
323   Case_Insensitive : constant Regexp_Flags;
324   --  The automaton is optimized so that the matching is done in a case
325   --  insensitive manner (upper case characters and lower case characters
326   --  are all treated the same way).
327
328   Single_Line      : constant Regexp_Flags;
329   --  Treat the Data we are matching as a single line. This means that
330   --  ^ and $ will ignore \n (unless Multiple_Lines is also specified),
331   --  and that '.' will match \n.
332
333   Multiple_Lines   : constant Regexp_Flags;
334   --  Treat the Data as multiple lines. This means that ^ and $ will also
335   --  match on internal newlines (ASCII.LF), in addition to the beginning
336   --  and end of the string.
337   --
338   --  This can be combined with Single_Line.
339
340   -----------------
341   -- Match_Array --
342   -----------------
343
344   subtype Match_Count is Natural range 0 .. Max_Paren_Count;
345
346   type Match_Location is record
347      First : Natural := 0;
348      Last  : Natural := 0;
349   end record;
350
351   type Match_Array is array (Match_Count range <>) of Match_Location;
352   --  The substring matching a given pair of parenthesis.
353   --  Index 0 is the whole substring that matched the full regular
354   --  expression.
355   --
356   --  For instance, if your regular expression is something like:
357   --  "a(b*)(c+)", then Match_Array(1) will be the indexes of the
358   --  substring that matched "b*" and Match_Array(2) will be the substring
359   --  that matched "c+".
360   --
361   --  The number of parenthesis groups that can be retrieved is unlimited,
362   --  and all the Match subprograms below can use a Match_Array of any size.
363   --  Indexes that do not have any matching parenthesis are set to
364   --  No_Match.
365
366   No_Match : constant Match_Location := (First => 0, Last => 0);
367   --  The No_Match constant is (0, 0) to differentiate between
368   --  matching a null string at position 1, which uses (1, 0)
369   --  and no match at all.
370
371   ------------------------------
372   -- Pattern_Matcher Creation --
373   ------------------------------
374
375   type Pattern_Matcher (Size : Program_Size) is private;
376   --  Type used to represent a regular expression compiled into byte code
377
378   Never_Match : constant Pattern_Matcher;
379   --  A regular expression that never matches anything
380
381   function Compile
382     (Expression : String;
383      Flags      : Regexp_Flags := No_Flags) return Pattern_Matcher;
384   --  Compile a regular expression into internal code.
385   --  Raises Expression_Error if Expression is not a legal regular expression.
386   --  The appropriate size is calculated automatically, but this means that
387   --  the regular expression has to be compiled twice (the first time to
388   --  calculate the size, the second time to actually generate the byte code).
389   --
390   --  Flags is the default value to use to set properties for Expression (case
391   --  sensitivity,...).
392
393   procedure Compile
394     (Matcher         : out Pattern_Matcher;
395      Expression      : String;
396      Final_Code_Size : out Program_Size;
397      Flags           : Regexp_Flags := No_Flags);
398   --  Compile a regular expression into into internal code
399   --  This procedure is significantly faster than the function
400   --  Compile, as there is a known maximum size for the matcher.
401   --  This function raises Storage_Error if Matcher is too small
402   --  to hold the resulting code, or Expression_Error is Expression
403   --  is not a legal regular expression.
404   --
405   --  Flags is the default value to use to set properties for Expression (case
406   --  sensitivity,...).
407
408   procedure Compile
409     (Matcher    : out Pattern_Matcher;
410      Expression : String;
411      Flags      : Regexp_Flags := No_Flags);
412   --  Same procedure as above, expect it does not return the final
413   --  program size.
414
415   function Paren_Count (Regexp : Pattern_Matcher) return Match_Count;
416   pragma Inline (Paren_Count);
417   --  Return the number of parenthesis pairs in Regexp.
418   --
419   --  This is the maximum index that will be filled if a Match_Array is
420   --  used as an argument to Match.
421   --
422   --  Thus, if you want to be sure to get all the parenthesis, you should
423   --  do something like:
424   --
425   --     declare
426   --        Regexp  : Pattern_Matcher := Compile ("a(b*)(c+)");
427   --        Matched : Match_Array (0 .. Paren_Count (Regexp));
428   --     begin
429   --        Match (Regexp, "a string", Matched);
430   --     end;
431
432   -------------
433   -- Quoting --
434   -------------
435
436   function Quote (Str : String) return String;
437   --  Return a version of Str so that every special character is quoted.
438   --  The resulting string can be used in a regular expression to match
439   --  exactly Str, whatever character was present in Str.
440
441   --------------
442   -- Matching --
443   --------------
444
445   procedure Match
446     (Expression     : String;
447      Data           : String;
448      Matches        : out Match_Array;
449      Size           : Program_Size := 0;
450      Data_First     : Integer      := -1;
451      Data_Last      : Positive     := Positive'Last);
452   --  Match Expression against Data (Data_First .. Data_Last) and store
453   --  result in Matches.
454   --
455   --  Data_First defaults to Data'First if unspecified (that is the
456   --  dummy value of -1 is interpreted to mean Data'First).
457   --
458   --  Data_Last defaults to Data'Last if unspecified (that is the
459   --  dummy value of Positive'Last is interpreted to mean Data'Last)
460   --
461   --  It is important that Data contains the whole string (or file) you
462   --  want to matched against, even if you start in the middle, since
463   --  otherwise regular expressions starting with "^" or ending with "$" will
464   --  be improperly processed.
465   --
466   --  Function raises Storage_Error if Size is too small for Expression,
467   --  or Expression_Error if Expression is not a legal regular expression.
468   --  If Size is 0, then the appropriate size is automatically calculated
469   --  by this package, but this is slightly slower.
470   --
471   --  At most Matches'Length parenthesis are returned.
472
473   function  Match
474     (Expression : String;
475      Data       : String;
476      Size       : Program_Size := 0;
477      Data_First : Integer  := -1;
478      Data_Last  : Positive := Positive'Last) return Natural;
479   --  Return the position where Data matches, or (Data'First - 1) if
480   --  there is no match.
481   --
482   --  Function raises Storage_Error if Size is too small for Expression
483   --  or Expression_Error if Expression is not a legal regular expression
484   --
485   --  If Size is 0, then the appropriate size is automatically calculated
486   --  by this package, but this is slightly slower.
487   --  See description of Data_First and Data_Last above.
488
489   function Match
490     (Expression : String;
491      Data       : String;
492      Size       : Program_Size := 0;
493      Data_First : Integer  := -1;
494      Data_Last  : Positive := Positive'Last) return Boolean;
495   --  Return True if Data matches Expression. Match raises Storage_Error
496   --  if Size is too small for Expression, or Expression_Error if Expression
497   --  is not a legal regular expression.
498   --
499   --  If Size is 0, then the appropriate size is automatically calculated
500   --  by this package, but this is slightly slower.
501   --
502   --  See description of Data_First and Data_Last above.
503
504   ------------------------------------------------
505   -- Matching a pre-compiled regular expression --
506   ------------------------------------------------
507
508   --  The following functions are significantly faster if you need to reuse
509   --  the same regular expression multiple times, since you only have to
510   --  compile it once.
511
512   function  Match
513     (Self       : Pattern_Matcher;
514      Data       : String;
515      Data_First : Integer  := -1;
516      Data_Last  : Positive := Positive'Last) return Natural;
517   --  Match Data using the given pattern matcher.
518   --  Return the position where Data matches, or (Data'First - 1) if there is
519   --  no match.
520   --
521   --  See description of Data_First and Data_Last above.
522
523   function  Match
524     (Self       : Pattern_Matcher;
525      Data       : String;
526      Data_First : Integer  := -1;
527      Data_Last  : Positive := Positive'Last) return Boolean;
528   --  Return True if Data matches using the given pattern matcher.
529   --
530   --  See description of Data_First and Data_Last above.
531
532   pragma Inline (Match);
533   --  All except the last one below
534
535   procedure Match
536     (Self       : Pattern_Matcher;
537      Data       : String;
538      Matches    : out Match_Array;
539      Data_First : Integer  := -1;
540      Data_Last  : Positive := Positive'Last);
541   --  Match Data using the given pattern matcher and store result in Matches.
542   --  The expression matches if Matches (0) /= No_Match.
543   --
544   --  At most Matches'Length parenthesis are returned.
545   --
546   --  See description of Data_First and Data_Last above.
547
548   -----------
549   -- Debug --
550   -----------
551
552   procedure Dump (Self : Pattern_Matcher);
553   --  Dump the compiled version of the regular expression matched by Self
554
555--------------------------
556-- Private Declarations --
557--------------------------
558
559private
560
561   subtype Pointer is Program_Size;
562   --  The Pointer type is used to point into Program_Data
563
564   --  Note that the pointer type is not necessarily 2 bytes
565   --  although it is stored in the program using 2 bytes
566
567   type Program_Data is array (Pointer range <>) of Character;
568
569   Program_First : constant := 1;
570
571   --  The "internal use only" fields in regexp are present to pass
572   --  info from compile to execute that permits the execute phase
573   --  to run lots faster on simple cases.  They are:
574
575   --     First              character that must begin a match or ASCII.Nul
576   --     Anchored           true iff match must start at beginning of line
577   --     Must_Have          pointer to string that match must include or null
578   --     Must_Have_Length   length of Must_Have string
579
580   --  First and Anchored permit very fast decisions on suitable
581   --  starting points for a match, cutting down the work a lot.
582   --  Must_Have permits fast rejection of lines that cannot possibly
583   --  match.
584
585   --  The Must_Have tests are costly enough that Optimize
586   --  supplies a Must_Have only if the r.e. contains something potentially
587   --  expensive (at present, the only such thing detected is * or +
588   --  at the start of the r.e., which can involve a lot of backup).
589   --  The length is supplied because the test in Execute needs it
590   --  and Optimize is computing it anyway.
591
592   --  The initialization is meant to fail-safe in case the user of this
593   --  package tries to use an uninitialized matcher. This takes advantage
594   --  of the knowledge that ASCII.Nul translates to the end-of-program (EOP)
595   --  instruction code of the state machine.
596
597   No_Flags         : constant Regexp_Flags := 0;
598   Case_Insensitive : constant Regexp_Flags := 1;
599   Single_Line      : constant Regexp_Flags := 2;
600   Multiple_Lines   : constant Regexp_Flags := 4;
601
602   type Pattern_Matcher (Size : Pointer) is record
603      First            : Character    := ASCII.NUL;  --  internal use only
604      Anchored         : Boolean      := False;      --  internal use only
605      Must_Have        : Pointer      := 0;          --  internal use only
606      Must_Have_Length : Natural      := 0;          --  internal use only
607      Paren_Count      : Natural      := 0;          --  # paren groups
608      Flags            : Regexp_Flags := No_Flags;
609      Program          : Program_Data (Program_First .. Size) :=
610                           (others => ASCII.NUL);
611   end record;
612
613   Never_Match : constant Pattern_Matcher :=
614      (0, ASCII.NUL, False, 0, 0, 0, No_Flags, (others => ASCII.NUL));
615
616end GNAT.Regpat;
617