This file is indexed.

/usr/lib/ocaml/xstr/xstr_match.mli is in libxstr-ocaml-dev 0.2.1-22build1.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

  1
  2
  3
  4
  5
  6
  7
  8
  9
 10
 11
 12
 13
 14
 15
 16
 17
 18
 19
 20
 21
 22
 23
 24
 25
 26
 27
 28
 29
 30
 31
 32
 33
 34
 35
 36
 37
 38
 39
 40
 41
 42
 43
 44
 45
 46
 47
 48
 49
 50
 51
 52
 53
 54
 55
 56
 57
 58
 59
 60
 61
 62
 63
 64
 65
 66
 67
 68
 69
 70
 71
 72
 73
 74
 75
 76
 77
 78
 79
 80
 81
 82
 83
 84
 85
 86
 87
 88
 89
 90
 91
 92
 93
 94
 95
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
(* $Id: xstr_match.mli,v 1.2 1999/07/04 20:02:08 gerd Exp $
 * ----------------------------------------------------------------------
 * Matching strings
 *)

(* Copyright 1999 by Gerd Stolpmann *)

type variable
   (* A 'variable' can record matched regions *)

type charset
   (* sets of characters *)

type matcher =
    Literal of string
  | Anystring 
  | Lazystring 
  | Anychar
  | Anystring_from of charset
  | Lazystring_from of charset
  | Anychar_from of charset
  | Nullstring
  | Alternative of matcher list list
  | Optional of matcher list
  | Record of (variable * matcher list)
  | Scanner of (string -> int)
;;

(* Literal s:            matches literally s and nothing else
 * Anystring/Lazystring  matches a string of arbitrary length with arbitrary
 *                       contents
 * Anystring_from s/    
 * Lazystring_from s     matches a string of arbitrary length with characters
 *                       from charset s
 * Anychar:              matches an arbitrary character
 * Anychar_from s:       matches a character from charset s
 * Nullstring:           matches the empty string
 * Alternative 
 *   [ ml1; ml2; ... ]
 *                    first tries the sequence ml1, then ml2, and so on
 *                    until one of the sequences leads to a match of the
 *                    whole string
 * Optional ml:       first tries the sequence ml, them the empty string.
 *                    = Alternative [ml; [Nullstring]]
 * Record (v, ml):    matches the same as ml, but the region of the string
 *                    is recorded in v
 * Scanner f:         f s is called where s is the rest to match. The function
 *                    should return the number of characters it can match,
 *                    or raise Not_found
 *)


val match_string : matcher list -> string -> bool

  (* match_string ml s:
   * Tries to match 'ml' against the string 's'; returns true on success, and
   * false otherwise.
   * As side-effect, the variables in 'ml' are set.
   * Matching proceeds from left to right, and for some of the matchers there
   * are particular matching orders. The first match that is found using
   * this order is returned (i.e. the variables get their values from this
   * match).
   * Notes:
   * - Anystring and Anystring_from are "greedy"; they try to match as much
   *   as possible.
   * - In contrast to this, Lazystring and Lazystring_from are "lazy"; they
   *   try to match as few as possible.
   * - Alternatives are tested from left to right.
   * - Options are first tested with argument, then with the empty string
   *   (i.e. "greedy")
   *)

type replacer =
    ReplaceLiteral of string
  | ReplaceVar of variable
  | ReplaceFunction of (unit -> string)
;;


type rflag =
    Anchored
  | Limit of int
  (* | RightToLeft *)
;;

val replace_matched_substrings : matcher list -> replacer list -> rflag list
                                  -> string -> (string * int)

  (* replace_matched_substrings ml rl fl s:
   *
   * All substrings of 's' are matched against 'ml' in turn, and all
   * non-overlapping matchings are replaced according 'rl'. The standard
   * behaviour is to test from left to right, and to replace all occurences
   * of substrings.
   * This can be modified by 'fl':
   *   - Anchored:  Not the substrings of 's', but only 's' itself is 
   *                matched against 'ml'. 
   *   - Limit n:   At most 'n' replacements will be done.
   *   - RightToLeft:  Begin with the rightmost matching; proceed with more
   *                   left matchings (NOT YET IMPLEMENTED!!!!)
   * The meaning of 'rl': Every matching is replaced by the sequence of
   * the elements of 'rl'.
   *   - ReplaceLiteral t:  Replace the string t
   *   - ReplaceVar v:      Replace the contents of 'v' or the empty string,
   *                        if v has no matching
   *   - ReplaceFunction f: Replace f(). You may raise Not_found or
   *        Match_failure to skip to the next matching.
   * 'replace_matched_substrings' returns the number of replacements.
   *)


val var : string -> variable

  (* var s: creates new variable with initial value s. If this variable
   * is used in a subsequent matching, and a value is found, the value
   * is overwritten; otherwise the old value persists.
   * - Initial vales are stored as references to strings
   * - Matched values are stored as triples (s,from,len) where 's' is the
   *   input string of the matching function
   *
   * [Note thread-safety: variables must not be shared by multiple threads.]
   *)

val var_matched  : variable -> bool

  (* returns true if the variable matched a value in the last match_string *)

val string_of_var : variable -> string

  (* returns the current value of the variable *)

val found_string_of_var : variable -> string

  (* returns the current value of the variable only if there was a match
   * for this variable in the last match_string; otherwise raise Not_found 
   *)

val mkset : string -> charset

  (* creates a set from readable description. The string simply enumerates
   * the characters of the set, and the notation "x-y" is possible, too.
   * To include '-' in the set, put it at the beginning or end.
   *)

val mknegset : string -> charset

  (* creates the complement that mkset would create *)


(* ---------------------------------------------------------------------- *)

(* EXAMPLE:
 *
 * let v = var "" in
 * let _ = match_string [ Literal "("; Record (v, [Anystring]); Literal ")" ]
 *                      s 
 * in found_string_of_var v
 *
 * - if s is "(abc)" returns "abc"
 * - if the parantheses are missing, raises Not_found
 *
 * VARIANT I:
 *
 * let v = var "" in
 * let _ = match_string [ Lazystring;
 *                        Literal "("; Record (v, [Lazystring]); Literal ")";
 *                        Anystring ]
 *                      s 
 * in found_string_of_var v
 *
 * - finds the first substring with parantheses, e.g.
 *   s = "abc(def)ghi(jkl)mno" returns "def"
 *
 * To get the last substring, swap Lazystring and Anystring at the beginning
 * resp. end.
 *
 * VARIANT II:
 *
 * let v = var "" in
 * let _ = match_string [ Lazystring;
 *                        Literal "("; Record (v, [Anystring]); Literal ")";
 *                        Anystring ]
 *                      s 
 * in found_string_of_var v
 *
 * - for s = "abc(def)ghi(jkl)mno" it is returned "def)ghi(jkl"
 *)

(* ---------------------------------------------------------------------- *)

(* EXAMPLE:
 *
 * let v = var "" in
 * let digits = mkset "0-9" in
 * let digits_re = [ Record(v, [ Anychar_from digits;  Anystring_from digits])]
 * in
 * replace_matched_substrings digits_re [ ReplaceLiteral "D" ] [] "ab012cd456fg"
 *
 * yields: ("abDcdDfg", 2)
 *
 * VARIANT I: 
 *
 * replace_matched_substrings digits_re [ ReplaceLiteral "D" ] 
 *                                      [ Limit 1 ] "ab012cd456fg"
 *
 * yields: ("abDcd456fg", 1)
 * 
 * VARIANT II:
 * 
 * replace_matched_substrings digits_re [ ReplaceLiteral "D" ] 
 *                                      [ Anchored ] "ab012cd456fg"
 *
 * yields: ("ab012cd456fg", 0)
 *
 * VARIANT III:
 * 
 * replace_matched_substrings digits_re [ ReplaceLiteral "D" ] 
 *                                      [ Anchored ] "012"
 *
 * yields: ("D", 1)
 *
 * VARIANT IV:
 * 
 * let f() = string_of_int(1+int_of_string(string_of_var v)) in
 * replace_matched_substrings digits_re [ ReplaceFunction f ] 
 *                                      [] "ab012cd456fg"
 *
 * yields: ("ab13cd457fg", 2)
 *)


(* ======================================================================
 * History:
 * 
 * $Log: xstr_match.mli,v $
 * Revision 1.2  1999/07/04 20:02:08  gerd
 * 	Added Lazystring, Lazystring_from.
 * 	Added replace_matched_substring function.
 * 	Changed the structure of 'variable'. 'sref' is either an arbitrary
 * string, or it is the input string of the matching function. 'from' and
 * 'len' are always used.
 *
 * Revision 1.1  1999/06/27 23:03:38  gerd
 * 	Initial revision.
 *
 * 
 *)