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