This file is indexed.

/usr/lib/ocaml/oasis/OASISString.ml is in liboasis-ocaml-dev 0.3.0-4.

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
(** Various string utilities.
   
    Mostly inspired by extlib and batteries ExtString and BatString libraries.

    @author Sylvain Le Gall
  *)

let nsplitf str f =
  if str = "" then
    []
  else
    let buf = Buffer.create 13 in
    let lst = ref [] in
    let push () =
      lst := Buffer.contents buf :: !lst;
      Buffer.clear buf
    in
    let str_len = String.length str in
      for i = 0 to str_len - 1 do
        if f str.[i] then
          push ()
        else
          Buffer.add_char buf str.[i]
      done;
      push ();
      List.rev !lst

(** [nsplit c s] Split the string [s] at char [c]. It doesn't include the
    separator.
  *)
let nsplit str c =
  nsplitf str ((=) c)

let find ~what ?(offset=0) str =
  let what_idx = ref 0 in
  let str_idx = ref offset in 
    while !str_idx < String.length str && 
          !what_idx < String.length what do
      if str.[!str_idx] = what.[!what_idx] then
        incr what_idx
      else
        what_idx := 0;
      incr str_idx
    done;
    if !what_idx <> String.length what then
      raise Not_found
    else 
      !str_idx - !what_idx

let sub_start str len = 
  let str_len = String.length str in
  if len >= str_len then
    ""
  else
    String.sub str len (str_len - len)

let sub_end ?(offset=0) str len =
  let str_len = String.length str in
  if len >= str_len then
    ""
  else
    String.sub str 0 (str_len - len)

let starts_with ~what ?(offset=0) str =
  let what_idx = ref 0 in
  let str_idx = ref offset in
  let ok = ref true in
    while !ok &&
          !str_idx < String.length str && 
          !what_idx < String.length what do
      if str.[!str_idx] = what.[!what_idx] then
        incr what_idx
      else
        ok := false;
      incr str_idx
    done;
    if !what_idx = String.length what then
      true
    else 
      false

let strip_starts_with ~what str =
  if starts_with ~what str then
    sub_start str (String.length what)
  else
    raise Not_found

let ends_with ~what ?(offset=0) str =
  let what_idx = ref ((String.length what) - 1) in
  let str_idx = ref ((String.length str) - 1) in
  let ok = ref true in
    while !ok &&
          offset <= !str_idx && 
          0 <= !what_idx do
      if str.[!str_idx] = what.[!what_idx] then
        decr what_idx
      else
        ok := false;
      decr str_idx
    done;
    if !what_idx = -1 then
      true
    else 
      false

let strip_ends_with ~what str =
  if ends_with ~what str then
    sub_end str (String.length what)
  else
    raise Not_found

let replace_chars f s =
  let buf = String.make (String.length s) 'X' in
    for i = 0 to String.length s - 1 do
      buf.[i] <- f s.[i]
    done;
    buf

(* END EXPORT *)

let is_whitespace =
  function
    | ' ' | '\r' | '\n' | '\t' -> true
    |  _  -> false

let tokenize ?(is_whitespace=is_whitespace) ?(tokens=[]) str =
  let lst = ref [] in
  let buf = Buffer.create 13 in
  let idx = ref 0 in    
  let push () = 
    (* Push the content of the buffer on the list. *)
    if Buffer.length buf > 0 then
      begin
        lst := Buffer.contents buf :: !lst;
        Buffer.clear buf
      end
  in
  let match_token () = 
    List.exists
      (fun tok ->
         if starts_with ~what:tok ~offset:!idx str then
           begin
             push ();
             lst := tok :: !lst;
             idx := !idx + (String.length tok);
             true
           end
         else
           false)
      tokens
  in
    while !idx < String.length str do
      let c = str.[!idx] in
      if is_whitespace c then
        begin
          push ();
          incr idx
        end
      else if match_token () then
        begin
          ()
        end
      else
        begin
          Buffer.add_char buf c;
          incr idx
        end
    done;
    push ();
    List.rev !lst

let tokenize_genlex ?(tokens=[]) str =
  let strm = Genlex.make_lexer tokens (Stream.of_string str) in
  let lst = ref [] in
    Stream.iter (fun tok -> lst := tok :: !lst) strm;
    List.rev !lst

let split str c =
  let idx = String.index str c in
    String.sub str 0 idx,
    String.sub str (idx + 1) (String.length str - idx - 1)

let trim str =
  let start_non_blank = ref 0 in
  let stop_non_blank = ref ((String.length str) - 1) in
    while !start_non_blank < String.length str &&
          is_whitespace (str.[!start_non_blank]) do
      incr start_non_blank
    done;
    while !start_non_blank <= !stop_non_blank &&
          is_whitespace (str.[!stop_non_blank]) do
      decr stop_non_blank
    done;
    String.sub str !start_non_blank (!stop_non_blank - !start_non_blank + 1)

let fold_left f acc str =
  let racc = ref acc in
    for i = 0 to String.length str - 1 do
      racc := f !racc str.[i]
    done;
    !racc