summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2006-04-16 23:28:22 +0000
committerDamien Doligez <damien.doligez-inria.fr>2006-04-16 23:28:22 +0000
commit1279ab4b76cad7001b3b47902d4813947f427031 (patch)
treeedfd352c4bc8217cfb8a943844840b23734722a0 /stdlib
parent8604fbe7f330eaaeda35680fbf1d641a4c4a6798 (diff)
fusion des changements 3.09.1 -> 3.09.2
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@7382 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/Makefile.nt3
-rw-r--r--stdlib/filename.ml68
-rw-r--r--stdlib/pervasives.mli6
-rw-r--r--stdlib/printf.ml2
-rw-r--r--stdlib/sys.ml2
5 files changed, 53 insertions, 28 deletions
diff --git a/stdlib/Makefile.nt b/stdlib/Makefile.nt
index 9ef5c8a18..ba34029d3 100644
--- a/stdlib/Makefile.nt
+++ b/stdlib/Makefile.nt
@@ -32,7 +32,8 @@ OTHERS=array.cmo list.cmo char.cmo string.cmo sys.cmo \
set.cmo map.cmo stack.cmo queue.cmo stream.cmo buffer.cmo \
printf.cmo format.cmo scanf.cmo \
arg.cmo printexc.cmo gc.cmo \
- digest.cmo random.cmo callback.cmo camlinternalOO.cmo oo.cmo \
+ digest.cmo random.cmo callback.cmo \
+ camlinternalOO.cmo oo.cmo camlinternalMod.cmo \
genlex.cmo weak.cmo \
lazy.cmo filename.cmo complex.cmo \
arrayLabels.cmo listLabels.cmo stringLabels.cmo moreLabels.cmo stdLabels.cmo
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index d6c24fc1b..3883a40a9 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -25,6 +25,24 @@ let generic_quote quotequote s =
Buffer.add_char b '\'';
Buffer.contents b
+let generic_basename rindex_dir_sep current_dir_name name =
+ let raw_name =
+ try
+ let p = rindex_dir_sep name + 1 in
+ String.sub name p (String.length name - p)
+ with Not_found ->
+ name
+ in
+ if raw_name = "" then current_dir_name else raw_name
+
+let generic_dirname rindex_dir_sep current_dir_name dir_sep name =
+ try
+ match rindex_dir_sep name with
+ 0 -> dir_sep
+ | n -> String.sub name 0 n
+ with Not_found ->
+ current_dir_name
+
module Unix = struct
let current_dir_name = "."
let parent_dir_name = ".."
@@ -43,6 +61,8 @@ module Unix = struct
let temp_dir_name =
try Sys.getenv "TMPDIR" with Not_found -> "/tmp"
let quote = generic_quote "'\\''"
+ let basename = generic_basename rindex_dir_sep current_dir_name
+ let dirname = generic_dirname rindex_dir_sep current_dir_name dir_sep
end
module Win32 = struct
@@ -53,7 +73,7 @@ module Win32 = struct
let rindex_dir_sep s =
let rec pos i =
if i < 0 then raise Not_found
- else if (let c = s.[i] in c = '/' || c = '\\' || c = ':') then i
+ else if is_dir_sep s i then i
else pos (i - 1)
in pos (String.length s - 1)
let is_relative n =
@@ -87,6 +107,23 @@ module Win32 = struct
done;
Buffer.add_char b '\"';
Buffer.contents b
+ let has_drive s =
+ let is_letter = function
+ | 'A' .. 'Z' | 'a' .. 'z' -> true
+ | _ -> false
+ in
+ String.length s >= 2 && is_letter s.[0] && s.[1] = ':'
+ let drive_and_path s =
+ if has_drive s
+ then (String.sub s 0 2, String.sub s 2 (String.length s - 2))
+ else ("", s)
+ let dirname s =
+ let (drive, path) = drive_and_path s in
+ let dir = generic_dirname rindex_dir_sep current_dir_name dir_sep path in
+ drive ^ dir
+ let basename s =
+ let (drive, path) = drive_and_path s in
+ generic_basename rindex_dir_sep current_dir_name path
end
module Cygwin = struct
@@ -100,26 +137,29 @@ module Cygwin = struct
let check_suffix = Win32.check_suffix
let temp_dir_name = Unix.temp_dir_name
let quote = Unix.quote
+ let basename = generic_basename rindex_dir_sep current_dir_name
+ let dirname = generic_dirname rindex_dir_sep current_dir_name dir_sep
end
let (current_dir_name, parent_dir_name, dir_sep, is_dir_sep, rindex_dir_sep,
- is_relative, is_implicit, check_suffix, temp_dir_name, quote) =
+ is_relative, is_implicit, check_suffix, temp_dir_name, quote, basename,
+ dirname) =
match Sys.os_type with
"Unix" ->
(Unix.current_dir_name, Unix.parent_dir_name, Unix.dir_sep,
Unix.is_dir_sep, Unix.rindex_dir_sep,
Unix.is_relative, Unix.is_implicit, Unix.check_suffix,
- Unix.temp_dir_name, Unix.quote)
+ Unix.temp_dir_name, Unix.quote, Unix.basename, Unix.dirname)
| "Win32" ->
(Win32.current_dir_name, Win32.parent_dir_name, Win32.dir_sep,
Win32.is_dir_sep, Win32.rindex_dir_sep,
Win32.is_relative, Win32.is_implicit, Win32.check_suffix,
- Win32.temp_dir_name, Win32.quote)
+ Win32.temp_dir_name, Win32.quote, Win32.basename, Win32.dirname)
| "Cygwin" ->
(Cygwin.current_dir_name, Cygwin.parent_dir_name, Cygwin.dir_sep,
Cygwin.is_dir_sep, Cygwin.rindex_dir_sep,
Cygwin.is_relative, Cygwin.is_implicit, Cygwin.check_suffix,
- Cygwin.temp_dir_name, Cygwin.quote)
+ Cygwin.temp_dir_name, Cygwin.quote, Cygwin.basename, Cygwin.dirname)
| _ -> assert false
let concat dirname filename =
@@ -128,24 +168,6 @@ let concat dirname filename =
then dirname ^ filename
else dirname ^ dir_sep ^ filename
-let basename name =
- let raw_name =
- try
- let p = rindex_dir_sep name + 1 in
- String.sub name p (String.length name - p)
- with Not_found ->
- name
- in
- if raw_name = "" then current_dir_name else raw_name
-
-let dirname name =
- try
- match rindex_dir_sep name with
- 0 -> dir_sep
- | n -> String.sub name 0 n
- with Not_found ->
- current_dir_name
-
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
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index 1af15bd4a..7ed1b5aec 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -172,10 +172,12 @@ external ( mod ) : int -> int -> int = "%modint"
[x = (x / y) * y + x mod y] and
[abs(x mod y) <= abs(y)-1].
If [y = 0], [x mod y] raises [Division_by_zero].
- Notice that [x mod y] is negative if and only if [x < 0]. *)
+ Notice that [x mod y] is nonpositive if and only if [x < 0].
+ Raise [Division_by_zero] if [y] is zero. *)
val abs : int -> int
-(** Return the absolute value of the argument. *)
+(** Return the absolute value of the argument. Note that this may be
+ negative if the argument is [min_int]. *)
val max_int : int
(** The greatest representable integer. *)
diff --git a/stdlib/printf.ml b/stdlib/printf.ml
index 69c2ecf63..872fc076c 100644
--- a/stdlib/printf.ml
+++ b/stdlib/printf.ml
@@ -296,7 +296,7 @@ let kapr kpr fmt =
else Obj.magic (fun x -> loop (succ i) (x :: args)) in
loop 0 [];;
-type param_spec = Spec_none | Spec_index of index;;
+type param_spec = Spec_none | Spec_index of index;;
(* To scan an optional positional parameter specification,
i.e. an integer followed by a $.
diff --git a/stdlib/sys.ml b/stdlib/sys.ml
index 7ed1a5071..2bf16cc39 100644
--- a/stdlib/sys.ml
+++ b/stdlib/sys.ml
@@ -78,4 +78,4 @@ let catch_break on =
(* OCaml version string, must be in the format described in sys.mli. *)
-let ocaml_version = "3.10+dev6 (2006-04-05)";;
+let ocaml_version = "3.10+dev7 (2006-04-17)";;