summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/array.ml27
-rw-r--r--stdlib/array.mli24
-rw-r--r--stdlib/filename.ml37
-rw-r--r--stdlib/filename.mli9
-rw-r--r--stdlib/genlex.mli4
-rw-r--r--stdlib/string.ml14
-rw-r--r--stdlib/string.mli9
7 files changed, 90 insertions, 34 deletions
diff --git a/stdlib/array.ml b/stdlib/array.ml
index 7a103f4ea..f6477d1f9 100644
--- a/stdlib/array.ml
+++ b/stdlib/array.ml
@@ -111,6 +111,19 @@ let map f a =
r
end
+let iteri f a =
+ for i = 0 to length a - 1 do f i (unsafe_get a i) done
+
+let mapi f a =
+ let l = length a in
+ if l = 0 then [||] else begin
+ let r = create l (f 0 (unsafe_get a 0)) in
+ for i = 1 to l - 1 do
+ unsafe_set r i (f i (unsafe_get a i))
+ done;
+ r
+ end
+
let to_list a =
let rec tolist i res =
if i < 0 then res else tolist (i - 1) (unsafe_get a i :: res) in
@@ -124,3 +137,17 @@ let of_list = function
[] -> a
| hd::tl -> unsafe_set a i hd; fill (i+1) tl in
fill 1 tl
+
+let fold_left f x a =
+ let r = ref x in
+ for i = 0 to Array.length a - 1 do
+ r := f !r (unsafe_get a i)
+ done;
+ !r
+
+let fold_right f a x =
+ let r = ref x in
+ for i = Array.length a - 1 downto 0 do
+ r := f (unsafe_get a i) !r
+ done;
+ !r
diff --git a/stdlib/array.mli b/stdlib/array.mli
index 3815161f7..0672c732b 100644
--- a/stdlib/array.mli
+++ b/stdlib/array.mli
@@ -74,6 +74,11 @@ val blit: 'a array -> int -> 'a array -> int -> int -> unit
Raise [Invalid_argument "Array.blit"] if [o1] and [len] do not
designate a valid subarray of [v1], or if [o2] and [len] do not
designate a valid subarray of [v2]. *)
+val to_list: 'a array -> 'a list
+ (* [Array.to_list a] returns the list of all the elements of [a]. *)
+val of_list: 'a list -> 'a array
+ (* [Array.of_list l] returns a fresh array containing the elements
+ of [l]. *)
val iter: ('a -> 'b) -> 'a array -> unit
(* [Array.iter f a] applies function [f] in turn to all
the elements of [a], discarding all the results:
@@ -82,12 +87,19 @@ val map: ('a -> 'b) -> 'a array -> 'b array
(* [Array.map f a] applies function [f] to all the elements of [a],
and builds an array with the results returned by [f]:
[[| f a.(0); f a.(1); ...; f a.(Array.length a - 1) |]]. *)
-val to_list: 'a array -> 'a list
- (* [Array.to_list a] returns the list of all the elements of [a]. *)
-val of_list: 'a list -> 'a array
- (* [Array.of_list l] returns a fresh array containing the elements
- of [l]. *)
-
+val iteri: (int -> 'a -> 'b) -> 'a array -> unit
+val mapi: (int -> 'a -> 'b) -> 'a array -> 'b array
+ (* Same as [Array.iter] and [Array.map] respectively, but the
+ function is applied to the index of the element as first argument,
+ and the element itself as second argument. *)
+val fold_left: ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a
+ (* [Array.fold_left f x a] computes
+ [f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)],
+ where [n] is the length of the array [a]. *)
+val fold_right: ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a
+ (* [Array.fold_right f a x] computes
+ [f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))],
+ where [n] is the length of the array [a]. *)
(*--*)
external unsafe_get: 'a array -> int -> 'a = "%array_unsafe_get"
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index e32ba2868..5ec18a217 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -16,7 +16,7 @@ let current_dir_name =
| "Unix" -> "."
| "Win32" -> "."
| "MacOS" -> ":"
- | _ -> invalid_arg "Filename.current_dir_name: unknown system"
+ | _ -> assert false
let unix_concat dirname filename =
let l = String.length dirname in
@@ -41,7 +41,7 @@ let concat =
| "Unix" -> unix_concat
| "Win32" -> wnt_concat
| "MacOS" -> mac_concat
- | _ -> invalid_arg "Filename.concat: unknown system"
+ | _ -> assert false
let unix_is_relative n = String.length n < 1 || n.[0] <> '/';;
@@ -67,11 +67,9 @@ let wnt_is_implicit n =
let contains_colon n =
try
- for i = 0 to String.length n - 1 do
- if n.[i] = ':' then raise Exit
- done;
+ String.index n ':'; true
+ with Not_found ->
false
- with Exit -> true
;;
let mac_is_relative n =
@@ -86,7 +84,7 @@ let (is_relative, is_implicit) =
| "Unix" -> (unix_is_relative, unix_is_implicit)
| "Win32" -> (wnt_is_relative, wnt_is_implicit)
| "MacOS" -> (mac_is_relative, mac_is_implicit)
- | _ -> invalid_arg "Filename.is_relative: unknown system"
+ | _ -> assert false
let unix_check_suffix name suff =
String.length name >= String.length suff &&
@@ -106,19 +104,12 @@ let check_suffix =
| "Unix" -> unix_check_suffix
| "Win32" -> wnt_check_suffix
| "MacOS" -> mac_check_suffix
- | _ -> invalid_arg "Filename.check_suffix: unknown system"
+ | _ -> assert false
let chop_suffix name suff =
let n = String.length name - String.length suff in
if n < 0 then invalid_arg "Filename.chop_suffix" else String.sub name 0 n
-let rindex s c =
- let rec pos i =
- if i < 0 then raise Not_found
- else if s.[i] = c then i
- else pos (i - 1)
- in pos (String.length s - 1)
-
let wnt_rindexsep s =
let rec pos i =
if i < 0 then raise Not_found
@@ -128,20 +119,20 @@ let wnt_rindexsep s =
let chop_extension name =
try
- String.sub name 0 (rindex name '.')
+ String.sub name 0 (String.rindex name '.')
with Not_found ->
invalid_arg "Filename.chop_extension"
let unix_basename name =
try
- let p = rindex name '/' + 1 in
+ let p = String.rindex name '/' + 1 in
String.sub name p (String.length name - p)
with Not_found ->
name
let unix_dirname name =
try
- match rindex name '/' with
+ match String.rindex name '/' with
0 -> "/"
| n -> String.sub name 0 n
with Not_found ->
@@ -164,12 +155,12 @@ let wnt_dirname name =
let mac_basename name =
try
- let p = rindex name ':' + 1 in
+ let p = String.rindex name ':' + 1 in
String.sub name p (String.length name - p)
with Not_found -> name
let mac_dirname name =
- try match rindex name ':' with
+ try match String.rindex name ':' with
| 0 -> ":"
| n -> String.sub name 0 n
with Not_found -> ":"
@@ -179,21 +170,21 @@ let basename =
| "Unix" -> unix_basename
| "Win32" -> wnt_basename
| "MacOS" -> mac_basename
- | _ -> invalid_arg "Filename.basename: unknown system"
+ | _ -> assert false
let dirname =
match Sys.os_type with
| "Unix" -> unix_dirname
| "Win32" -> wnt_dirname
| "MacOS" -> mac_dirname
- | _ -> invalid_arg "Filename.dirname: unknown system"
+ | _ -> assert false
let temporary_directory =
match Sys.os_type with
| "Unix" -> (try Sys.getenv "TMPDIR" with Not_found -> "/tmp")
| "Win32" -> (try Sys.getenv "TEMP" with Not_found -> "C:\\temp")
| "MacOS" -> (try Sys.getenv "TempFolder" with Not_found -> ":")
- | _ -> invalid_arg "Filename.temporary_directory: unknown system"
+ | _ -> assert false
external open_desc: string -> open_flag list -> int -> int = "sys_open"
external close_desc: int -> unit = "sys_close"
diff --git a/stdlib/filename.mli b/stdlib/filename.mli
index 8d65790e1..e09f88616 100644
--- a/stdlib/filename.mli
+++ b/stdlib/filename.mli
@@ -51,7 +51,10 @@ val dirname : string -> string
val temp_file: string -> string -> string
(* [temp_file prefix suffix] returns the name of a
non-existent temporary file in the temporary directory.
- The temporary directory is [/tmp] by default; if set,
- the value of the environment variable [TMPDIR] is used instead.
The base name of the temporary file is formed by concatenating
- [prefix], then a suitably chosen integer number, then [suffix]. *)
+ [prefix], then a suitably chosen integer number, then [suffix].
+ Under Unix, the temporary directory is [/tmp] by default; if set,
+ the value of the environment variable [TMPDIR] is used instead.
+ Under Windows, the name of the temporary directory is the
+ value of the environment variable [TEMP],
+ or [C:\temp] by default. *)
diff --git a/stdlib/genlex.mli b/stdlib/genlex.mli
index e11fdb344..f228fc688 100644
--- a/stdlib/genlex.mli
+++ b/stdlib/genlex.mli
@@ -51,11 +51,11 @@ val make_lexer: string list -> (char Stream.t -> token Stream.t)
The associated parser would be a function from [token stream]
to, for instance, [int], and would have rules such as:
[
- let parse_expr = function
+ let parse_expr = parser
[< 'Int n >] -> n
| [< 'Kwd "("; n = parse_expr; 'Kwd ")" >] -> n
| [< n1 = parse_expr; n2 = parse_remainder n1 >] -> n2
- and parse_remainder n1 = function
+ and parse_remainder n1 = parser
[< 'Kwd "+"; n2 = parse_expr >] -> n1+n2
| ...
]
diff --git a/stdlib/string.ml b/stdlib/string.ml
index be074fa10..0556b273e 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -136,3 +136,17 @@ let apply1 f s =
let capitalize s = apply1 Char.uppercase s
let uncapitalize s = apply1 Char.lowercase s
+
+let index s c =
+ let rec idx i =
+ if i >= String.length s then raise Not_found
+ else if s.[i] = c then i
+ else idx (i+1)
+ in idx 0
+
+let rindex s c =
+ let rec idx i =
+ if i < 0 then raise Not_found
+ else if s.[i] = c then i
+ else idx (i-1)
+ in idx (String.length s - 1)
diff --git a/stdlib/string.mli b/stdlib/string.mli
index d12b52180..627c8ad62 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -70,6 +70,15 @@ val escaped: string -> string
by escape sequences, following the lexical conventions of
Objective Caml. *)
+val index: string -> char -> int
+ (* [index s c] returns the position of the leftmost occurrence of
+ character [c] in string [s]. Raise [Not_found] if [c] does not
+ occur in [s]. *)
+val rindex: string -> char -> int
+ (* [rindex s c] returns the position of the rightmost occurrence of
+ character [c] in string [s]. Raise [Not_found] if [c] does not
+ occur in [s]. *)
+
val uppercase: string -> string
(* Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO