~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to stdlib/string.ml

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
(*                                                                     *)
12
12
(***********************************************************************)
13
13
 
14
 
(* $Id: string.ml,v 1.26 2007/01/30 09:34:36 xleroy Exp $ *)
 
14
(* $Id: string.ml,v 1.28.2.1 2008/11/12 10:53:47 doligez Exp $ *)
15
15
 
16
16
(* String operations *)
17
17
 
87
87
    for i = 0 to length s - 1 do
88
88
      n := !n +
89
89
        (match unsafe_get s i with
90
 
           '"' | '\\' | '\n' | '\t' -> 2
91
 
          | c -> if is_printable c then 1 else 4)
 
90
         | '"' | '\\' | '\n' | '\t' | '\r' | '\b' -> 2
 
91
         | c -> if is_printable c then 1 else 4)
92
92
    done;
93
93
    if !n = length s then s else begin
94
94
      let s' = create !n in
96
96
        for i = 0 to length s - 1 do
97
97
          begin
98
98
            match unsafe_get s i with
99
 
              ('"' | '\\') as c ->
 
99
            | ('"' | '\\') as c ->
100
100
                unsafe_set s' !n '\\'; incr n; unsafe_set s' !n c
101
101
            | '\n' ->
102
102
                unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'n'
103
103
            | '\t' ->
104
104
                unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 't'
 
105
            | '\r' ->
 
106
                unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'r'
 
107
            | '\b' ->
 
108
                unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'b'
105
109
            | c ->
106
110
                if is_printable c then
107
111
                  unsafe_set s' !n c
144
148
 
145
149
let rec index_rec s lim i c =
146
150
  if i >= lim then raise Not_found else
147
 
  if unsafe_get s i = c then i else index_rec s lim (i+1) c;;
 
151
  if unsafe_get s i = c then i else index_rec s lim (i + 1) c;;
148
152
 
149
153
let index s c = index_rec s (length s) 0 c;;
150
154
 
151
155
let index_from s i c =
152
 
  if i < 0 || i > length s then invalid_arg "String.index_from" else
153
 
  index_rec s (length s) i c;;
 
156
  let l = length s in
 
157
  if i < 0 || i > l then invalid_arg "String.index_from" else
 
158
  index_rec s l i c;;
154
159
 
155
160
let rec rindex_rec s i c =
156
161
  if i < 0 then raise Not_found else
157
 
  if unsafe_get s i = c then i else rindex_rec s (i-1) c;;
 
162
  if unsafe_get s i = c then i else rindex_rec s (i - 1) c;;
158
163
 
159
164
let rindex s c = rindex_rec s (length s - 1) c;;
160
165
 
163
168
  rindex_rec s i c;;
164
169
 
165
170
let contains_from s i c =
166
 
  if i < 0 || i > length s then invalid_arg "String.contains_from" else
167
 
  try ignore(index_rec s (length s) i c); true with Not_found -> false;;
 
171
  let l = length s in
 
172
  if i < 0 || i > l then invalid_arg "String.contains_from" else
 
173
  try ignore (index_rec s l i c); true with Not_found -> false;;
 
174
 
 
175
let contains s c = contains_from s 0 c;;
168
176
 
169
177
let rcontains_from s i c =
170
178
  if i < 0 || i >= length s then invalid_arg "String.rcontains_from" else
171
 
  try ignore(rindex_rec s i c); true with Not_found -> false;;
172
 
 
173
 
let contains s c = contains_from s 0 c;;
 
179
  try ignore (rindex_rec s i c); true with Not_found -> false;;
174
180
 
175
181
type t = string
176
182
 
177
 
let compare (x: t) (y: t) = Pervasives.compare x y
 
183
let compare = Pervasives.compare