Revert r13746 (demanded by Xavier)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13748 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Fabrice Le Fessant 2013-06-05 17:54:20 +00:00
parent ad6c285818
commit 504e86d722
5 changed files with 41 additions and 41 deletions

View File

@ -159,7 +159,7 @@ let parse_args s =
*)
let parse_args s =
let args = String.split s ',' in
let args = Misc.split s ',' in
let rec iter is_after args before after =
match args with
[] ->
@ -171,7 +171,7 @@ let parse_args s =
| "_" :: tail -> iter true tail before after
| arg :: tail ->
let binding = try
String.cut_at arg '='
Misc.cut_at arg '='
with Not_found ->
raise (SyntaxError ("missing '=' in " ^ arg))
in
@ -239,7 +239,7 @@ let read_OCAMLPARAM position =
| "pp" -> preprocessor := Some v
| "runtime-variant" -> runtime_variant := v
| "open" -> implicit_modules := String.split v ','
| "open" -> implicit_modules := Misc.split v ','
| "cc" -> c_compiler := Some v
(* assembly sources *)

View File

@ -203,23 +203,3 @@ let rcontains_from s i c =
type t = string
let compare (x: t) (y: t) = Pervasives.compare x y
(* split a string [s] at every char [c], and return the list of sub-strings *)
let split s c =
let len = length s in
let rec iter pos to_rev =
if pos = len then List.rev ("" :: to_rev) else
match try
Some ( index_from s pos c )
with Not_found -> None
with
Some pos2 ->
if pos2 = pos then iter (pos+1) ("" :: to_rev) else
iter (pos2+1) ((sub s pos (pos2-pos)) :: to_rev)
| None -> List.rev ( sub s pos (len-pos) :: to_rev )
in
iter 0 []
let cut_at s c =
let pos = index s c in
sub s 0 pos, sub s (pos+1) (length s - pos - 1)

View File

@ -219,24 +219,6 @@ val compare: t -> t -> int
allows the module [String] to be passed as argument to the functors
{!Set.Make} and {!Map.Make}. *)
val split : string -> char -> string list
(** [String.split string char] splits the string [string] at every char
[char], and returns the list of sub-strings between the chars.
[String.concat (String.make 1 c) (String.split s c)] is the identity.
@since 4.01
*)
val cut_at : string -> char -> string * string
(** [String.cut_at s c] returns a pair containing the sub-string before
the first occurrence of [c] in [s], and the sub-string after the
first occurrence of [c] in [s].
[let (before, after) = String.cut_at s c in
before ^ String.make 1 c ^ after] is the identity if [s] contains [c].
Raise [Not_found] if the character does not appear in the string
@since 4.01
*)
(**/**)
(* The following is for system use only. Do not call directly. *)

View File

@ -314,3 +314,23 @@ let edit_distance a b cutoff =
else Some result
end
(* split a string [s] at every char [c], and return the list of sub-strings *)
let split s c =
let len = String.length s in
let rec iter pos to_rev =
if pos = len then List.rev ("" :: to_rev) else
match try
Some ( String.index_from s pos c )
with Not_found -> None
with
Some pos2 ->
if pos2 = pos then iter (pos+1) ("" :: to_rev) else
iter (pos2+1) ((String.sub s pos (pos2-pos)) :: to_rev)
| None -> List.rev ( String.sub s pos (len-pos) :: to_rev )
in
iter 0 []
let cut_at s c =
let pos = String.index s c in
String.sub s 0 pos, String.sub s (pos+1) (String.length s - pos - 1)

View File

@ -146,3 +146,21 @@ val edit_distance : string -> string -> int -> int option
letters, or swapping of adjacent letters to go from one word to the
other. The particular algorithm may change in the future.
*)
val split : string -> char -> string list
(** [String.split string char] splits the string [string] at every char
[char], and returns the list of sub-strings between the chars.
[String.concat (String.make 1 c) (String.split s c)] is the identity.
@since 4.01
*)
val cut_at : string -> char -> string * string
(** [String.cut_at s c] returns a pair containing the sub-string before
the first occurrence of [c] in [s], and the sub-string after the
first occurrence of [c] in [s].
[let (before, after) = String.cut_at s c in
before ^ String.make 1 c ^ after] is the identity if [s] contains [c].
Raise [Not_found] if the character does not appear in the string
@since 4.01
*)