summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/.cvsignore1
-rw-r--r--stdlib/.depend278
-rw-r--r--stdlib/buffer.ml8
-rw-r--r--stdlib/buffer.mli9
-rw-r--r--stdlib/filename.ml12
-rw-r--r--stdlib/filename.mli9
-rw-r--r--stdlib/format.mli44
-rw-r--r--stdlib/obj.ml3
-rw-r--r--stdlib/obj.mli5
-rw-r--r--stdlib/pervasives.mli14
-rw-r--r--stdlib/printexc.ml17
-rw-r--r--stdlib/printexc.mli10
-rw-r--r--stdlib/scanf.mli18
-rw-r--r--stdlib/stdlib.mllib67
14 files changed, 297 insertions, 198 deletions
diff --git a/stdlib/.cvsignore b/stdlib/.cvsignore
index 343f6abd6..6aa0cd421 100644
--- a/stdlib/.cvsignore
+++ b/stdlib/.cvsignore
@@ -4,3 +4,4 @@ labelled-*
caml
*.annot
sys.ml
+*.a
diff --git a/stdlib/.depend b/stdlib/.depend
index faa338218..5aae75f71 100644
--- a/stdlib/.depend
+++ b/stdlib/.depend
@@ -1,144 +1,146 @@
-arg.cmi:
-array.cmi:
-arrayLabels.cmi:
-buffer.cmi:
-callback.cmi:
-camlinternalLazy.cmi:
-camlinternalMod.cmi: obj.cmi
-camlinternalOO.cmi: obj.cmi
-char.cmi:
-complex.cmi:
-digest.cmi:
-filename.cmi:
-format.cmi: buffer.cmi
-gc.cmi:
-genlex.cmi: stream.cmi
-hashtbl.cmi:
-int32.cmi:
-int64.cmi:
-lazy.cmi:
-lexing.cmi:
-list.cmi:
-listLabels.cmi:
-map.cmi:
-marshal.cmi:
-moreLabels.cmi: set.cmi map.cmi hashtbl.cmi
-nativeint.cmi:
-obj.cmi:
-oo.cmi: camlinternalOO.cmi
-parsing.cmi: obj.cmi lexing.cmi
-pervasives.cmi:
-printexc.cmi:
-printf.cmi: obj.cmi buffer.cmi
-queue.cmi:
-random.cmi: nativeint.cmi int64.cmi int32.cmi
-scanf.cmi:
-set.cmi:
-sort.cmi:
-stack.cmi:
-stdLabels.cmi:
-stream.cmi:
-string.cmi:
-stringLabels.cmi:
-sys.cmi:
-weak.cmi: hashtbl.cmi
-arg.cmo: sys.cmi string.cmi printf.cmi list.cmi buffer.cmi array.cmi arg.cmi
-arg.cmx: sys.cmx string.cmx printf.cmx list.cmx buffer.cmx array.cmx arg.cmi
-array.cmo: array.cmi
-array.cmx: array.cmi
-arrayLabels.cmo: array.cmi arrayLabels.cmi
-arrayLabels.cmx: array.cmx arrayLabels.cmi
-buffer.cmo: sys.cmi string.cmi buffer.cmi
-buffer.cmx: sys.cmx string.cmx buffer.cmi
-callback.cmo: obj.cmi callback.cmi
-callback.cmx: obj.cmx callback.cmi
-camlinternalLazy.cmo: obj.cmi camlinternalLazy.cmi
-camlinternalLazy.cmx: obj.cmx camlinternalLazy.cmi
-camlinternalMod.cmo: obj.cmi camlinternalOO.cmi array.cmi camlinternalMod.cmi
-camlinternalMod.cmx: obj.cmx camlinternalOO.cmx array.cmx camlinternalMod.cmi
+arg.cmi:
+array.cmi:
+arrayLabels.cmi:
+buffer.cmi:
+callback.cmi:
+camlinternalLazy.cmi:
+camlinternalMod.cmi: obj.cmi
+camlinternalOO.cmi: obj.cmi
+char.cmi:
+complex.cmi:
+digest.cmi:
+filename.cmi:
+format.cmi: pervasives.cmi buffer.cmi
+gc.cmi:
+genlex.cmi: stream.cmi
+hashtbl.cmi:
+int32.cmi:
+int64.cmi:
+lazy.cmi:
+lexing.cmi:
+list.cmi:
+listLabels.cmi:
+map.cmi:
+marshal.cmi:
+moreLabels.cmi: set.cmi map.cmi hashtbl.cmi
+nativeint.cmi:
+obj.cmi:
+oo.cmi: camlinternalOO.cmi
+parsing.cmi: obj.cmi lexing.cmi
+pervasives.cmi:
+printexc.cmi:
+printf.cmi: obj.cmi buffer.cmi
+queue.cmi:
+random.cmi: nativeint.cmi int64.cmi int32.cmi
+scanf.cmi: pervasives.cmi
+set.cmi:
+sort.cmi:
+stack.cmi:
+stdLabels.cmi:
+stream.cmi:
+string.cmi:
+stringLabels.cmi:
+sys.cmi:
+weak.cmi: hashtbl.cmi
+arg.cmo: sys.cmi string.cmi printf.cmi list.cmi buffer.cmi array.cmi arg.cmi
+arg.cmx: sys.cmx string.cmx printf.cmx list.cmx buffer.cmx array.cmx arg.cmi
+array.cmo: array.cmi
+array.cmx: array.cmi
+arrayLabels.cmo: array.cmi arrayLabels.cmi
+arrayLabels.cmx: array.cmx arrayLabels.cmi
+buffer.cmo: sys.cmi string.cmi buffer.cmi
+buffer.cmx: sys.cmx string.cmx buffer.cmi
+callback.cmo: obj.cmi callback.cmi
+callback.cmx: obj.cmx callback.cmi
+camlinternalLazy.cmo: obj.cmi camlinternalLazy.cmi
+camlinternalLazy.cmx: obj.cmx camlinternalLazy.cmi
+camlinternalMod.cmo: obj.cmi camlinternalOO.cmi array.cmi camlinternalMod.cmi
+camlinternalMod.cmx: obj.cmx camlinternalOO.cmx array.cmx camlinternalMod.cmi
camlinternalOO.cmo: sys.cmi string.cmi obj.cmi map.cmi list.cmi char.cmi \
- array.cmi camlinternalOO.cmi
+ array.cmi camlinternalOO.cmi
camlinternalOO.cmx: sys.cmx string.cmx obj.cmx map.cmx list.cmx char.cmx \
- array.cmx camlinternalOO.cmi
-char.cmo: char.cmi
-char.cmx: char.cmi
-complex.cmo: complex.cmi
-complex.cmx: complex.cmi
-digest.cmo: string.cmi printf.cmi digest.cmi
-digest.cmx: string.cmx printf.cmx digest.cmi
+ array.cmx camlinternalOO.cmi
+char.cmo: char.cmi
+char.cmx: char.cmi
+complex.cmo: complex.cmi
+complex.cmx: complex.cmi
+digest.cmo: string.cmi printf.cmi digest.cmi
+digest.cmx: string.cmx printf.cmx digest.cmi
filename.cmo: sys.cmi string.cmi random.cmi printf.cmi buffer.cmi \
- filename.cmi
+ filename.cmi
filename.cmx: sys.cmx string.cmx random.cmx printf.cmx buffer.cmx \
- filename.cmi
-format.cmo: string.cmi printf.cmi obj.cmi list.cmi buffer.cmi format.cmi
-format.cmx: string.cmx printf.cmx obj.cmx list.cmx buffer.cmx format.cmi
-gc.cmo: sys.cmi printf.cmi gc.cmi
-gc.cmx: sys.cmx printf.cmx gc.cmi
-genlex.cmo: string.cmi stream.cmi list.cmi hashtbl.cmi char.cmi genlex.cmi
-genlex.cmx: string.cmx stream.cmx list.cmx hashtbl.cmx char.cmx genlex.cmi
-hashtbl.cmo: sys.cmi array.cmi hashtbl.cmi
-hashtbl.cmx: sys.cmx array.cmx hashtbl.cmi
-int32.cmo: pervasives.cmi int32.cmi
-int32.cmx: pervasives.cmx int32.cmi
-int64.cmo: pervasives.cmi int64.cmi
-int64.cmx: pervasives.cmx int64.cmi
-lazy.cmo: obj.cmi camlinternalLazy.cmi lazy.cmi
-lazy.cmx: obj.cmx camlinternalLazy.cmx lazy.cmi
-lexing.cmo: sys.cmi string.cmi array.cmi lexing.cmi
-lexing.cmx: sys.cmx string.cmx array.cmx lexing.cmi
-list.cmo: list.cmi
-list.cmx: list.cmi
-listLabels.cmo: list.cmi listLabels.cmi
-listLabels.cmx: list.cmx listLabels.cmi
-map.cmo: map.cmi
-map.cmx: map.cmi
-marshal.cmo: string.cmi marshal.cmi
-marshal.cmx: string.cmx marshal.cmi
-moreLabels.cmo: set.cmi map.cmi hashtbl.cmi moreLabels.cmi
-moreLabels.cmx: set.cmx map.cmx hashtbl.cmx moreLabels.cmi
-nativeint.cmo: sys.cmi pervasives.cmi nativeint.cmi
-nativeint.cmx: sys.cmx pervasives.cmx nativeint.cmi
-obj.cmo: marshal.cmi obj.cmi
-obj.cmx: marshal.cmx obj.cmi
-oo.cmo: camlinternalOO.cmi oo.cmi
-oo.cmx: camlinternalOO.cmx oo.cmi
-parsing.cmo: obj.cmi lexing.cmi array.cmi parsing.cmi
-parsing.cmx: obj.cmx lexing.cmx array.cmx parsing.cmi
-pervasives.cmo: pervasives.cmi
-pervasives.cmx: pervasives.cmi
-printexc.cmo: printf.cmi obj.cmi buffer.cmi array.cmi printexc.cmi
-printexc.cmx: printf.cmx obj.cmx buffer.cmx array.cmx printexc.cmi
-printf.cmo: string.cmi obj.cmi list.cmi char.cmi buffer.cmi array.cmi \
- printf.cmi
-printf.cmx: string.cmx obj.cmx list.cmx char.cmx buffer.cmx array.cmx \
- printf.cmi
-queue.cmo: obj.cmi queue.cmi
-queue.cmx: obj.cmx queue.cmi
+ filename.cmi
+format.cmo: string.cmi printf.cmi pervasives.cmi obj.cmi list.cmi buffer.cmi \
+ format.cmi
+format.cmx: string.cmx printf.cmx pervasives.cmx obj.cmx list.cmx buffer.cmx \
+ format.cmi
+gc.cmo: sys.cmi printf.cmi gc.cmi
+gc.cmx: sys.cmx printf.cmx gc.cmi
+genlex.cmo: string.cmi stream.cmi list.cmi hashtbl.cmi char.cmi genlex.cmi
+genlex.cmx: string.cmx stream.cmx list.cmx hashtbl.cmx char.cmx genlex.cmi
+hashtbl.cmo: sys.cmi array.cmi hashtbl.cmi
+hashtbl.cmx: sys.cmx array.cmx hashtbl.cmi
+int32.cmo: pervasives.cmi int32.cmi
+int32.cmx: pervasives.cmx int32.cmi
+int64.cmo: pervasives.cmi int64.cmi
+int64.cmx: pervasives.cmx int64.cmi
+lazy.cmo: obj.cmi camlinternalLazy.cmi lazy.cmi
+lazy.cmx: obj.cmx camlinternalLazy.cmx lazy.cmi
+lexing.cmo: sys.cmi string.cmi array.cmi lexing.cmi
+lexing.cmx: sys.cmx string.cmx array.cmx lexing.cmi
+list.cmo: list.cmi
+list.cmx: list.cmi
+listLabels.cmo: list.cmi listLabels.cmi
+listLabels.cmx: list.cmx listLabels.cmi
+map.cmo: map.cmi
+map.cmx: map.cmi
+marshal.cmo: string.cmi marshal.cmi
+marshal.cmx: string.cmx marshal.cmi
+moreLabels.cmo: set.cmi map.cmi hashtbl.cmi moreLabels.cmi
+moreLabels.cmx: set.cmx map.cmx hashtbl.cmx moreLabels.cmi
+nativeint.cmo: sys.cmi pervasives.cmi nativeint.cmi
+nativeint.cmx: sys.cmx pervasives.cmx nativeint.cmi
+obj.cmo: marshal.cmi array.cmi obj.cmi
+obj.cmx: marshal.cmx array.cmx obj.cmi
+oo.cmo: camlinternalOO.cmi oo.cmi
+oo.cmx: camlinternalOO.cmx oo.cmi
+parsing.cmo: obj.cmi lexing.cmi array.cmi parsing.cmi
+parsing.cmx: obj.cmx lexing.cmx array.cmx parsing.cmi
+pervasives.cmo: pervasives.cmi
+pervasives.cmx: pervasives.cmi
+printexc.cmo: printf.cmi obj.cmi buffer.cmi array.cmi printexc.cmi
+printexc.cmx: printf.cmx obj.cmx buffer.cmx array.cmx printexc.cmi
+printf.cmo: string.cmi pervasives.cmi obj.cmi list.cmi char.cmi buffer.cmi \
+ array.cmi printf.cmi
+printf.cmx: string.cmx pervasives.cmx obj.cmx list.cmx char.cmx buffer.cmx \
+ array.cmx printf.cmi
+queue.cmo: obj.cmi queue.cmi
+queue.cmx: obj.cmx queue.cmi
random.cmo: string.cmi pervasives.cmi nativeint.cmi int64.cmi int32.cmi \
- digest.cmi char.cmi array.cmi random.cmi
+ digest.cmi char.cmi array.cmi random.cmi
random.cmx: string.cmx pervasives.cmx nativeint.cmx int64.cmx int32.cmx \
- digest.cmx char.cmx array.cmx random.cmi
-scanf.cmo: string.cmi printf.cmi obj.cmi list.cmi hashtbl.cmi buffer.cmi \
- array.cmi scanf.cmi
-scanf.cmx: string.cmx printf.cmx obj.cmx list.cmx hashtbl.cmx buffer.cmx \
- array.cmx scanf.cmi
-set.cmo: set.cmi
-set.cmx: set.cmi
-sort.cmo: array.cmi sort.cmi
-sort.cmx: array.cmx sort.cmi
-stack.cmo: list.cmi stack.cmi
-stack.cmx: list.cmx stack.cmi
-stdLabels.cmo: stringLabels.cmi listLabels.cmi arrayLabels.cmi stdLabels.cmi
-stdLabels.cmx: stringLabels.cmx listLabels.cmx arrayLabels.cmx stdLabels.cmi
-std_exit.cmo:
-std_exit.cmx:
-stream.cmo: string.cmi obj.cmi list.cmi lazy.cmi stream.cmi
-stream.cmx: string.cmx obj.cmx list.cmx lazy.cmx stream.cmi
-string.cmo: pervasives.cmi list.cmi char.cmi string.cmi
-string.cmx: pervasives.cmx list.cmx char.cmx string.cmi
-stringLabels.cmo: string.cmi stringLabels.cmi
-stringLabels.cmx: string.cmx stringLabels.cmi
-sys.cmo: sys.cmi
-sys.cmx: sys.cmi
-weak.cmo: sys.cmi obj.cmi hashtbl.cmi array.cmi weak.cmi
-weak.cmx: sys.cmx obj.cmx hashtbl.cmx array.cmx weak.cmi
+ digest.cmx char.cmx array.cmx random.cmi
+scanf.cmo: string.cmi printf.cmi pervasives.cmi obj.cmi list.cmi hashtbl.cmi \
+ buffer.cmi array.cmi scanf.cmi
+scanf.cmx: string.cmx printf.cmx pervasives.cmx obj.cmx list.cmx hashtbl.cmx \
+ buffer.cmx array.cmx scanf.cmi
+set.cmo: set.cmi
+set.cmx: set.cmi
+sort.cmo: array.cmi sort.cmi
+sort.cmx: array.cmx sort.cmi
+stack.cmo: list.cmi stack.cmi
+stack.cmx: list.cmx stack.cmi
+stdLabels.cmo: stringLabels.cmi listLabels.cmi arrayLabels.cmi stdLabels.cmi
+stdLabels.cmx: stringLabels.cmx listLabels.cmx arrayLabels.cmx stdLabels.cmi
+std_exit.cmo:
+std_exit.cmx:
+stream.cmo: string.cmi obj.cmi list.cmi lazy.cmi stream.cmi
+stream.cmx: string.cmx obj.cmx list.cmx lazy.cmx stream.cmi
+string.cmo: pervasives.cmi list.cmi char.cmi string.cmi
+string.cmx: pervasives.cmx list.cmx char.cmx string.cmi
+stringLabels.cmo: string.cmi stringLabels.cmi
+stringLabels.cmx: string.cmx stringLabels.cmi
+sys.cmo: sys.cmi
+sys.cmx: sys.cmi
+weak.cmo: sys.cmi obj.cmi hashtbl.cmi array.cmi weak.cmi
+weak.cmx: sys.cmx obj.cmx hashtbl.cmx array.cmx weak.cmi
diff --git a/stdlib/buffer.ml b/stdlib/buffer.ml
index 8dfe87599..088840981 100644
--- a/stdlib/buffer.ml
+++ b/stdlib/buffer.ml
@@ -39,6 +39,14 @@ let sub b ofs len =
end
;;
+let blit src srcoff dst dstoff len =
+ if len < 0 || srcoff < 0 || srcoff > src.position - len
+ || dstoff < 0 || dstoff > (String.length dst) - len
+ then invalid_arg "Buffer.blit"
+ else
+ String.blit src.buffer srcoff dst dstoff len
+;;
+
let nth b ofs =
if ofs < 0 || ofs >= b.position then
invalid_arg "Buffer.nth"
diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli
index d7afbb183..32d15349e 100644
--- a/stdlib/buffer.mli
+++ b/stdlib/buffer.mli
@@ -48,6 +48,15 @@ current contents of the buffer [b] starting at offset [off] of length
[len] bytes. May raise [Invalid_argument] if out of bounds request. The
buffer itself is unaffected. *)
+val blit : t -> int -> string -> int -> int -> unit
+(** [Buffer.blit src srcoff dst dstoff len] copies [len] characters from
+ the current contents of the buffer [src], starting at offset [srcoff]
+ to string [dst], starting at character [dstoff].
+
+ Raise [Invalid_argument] if [srcoff] and [len] do not designate a valid
+ substring of [src], or if [dstoff] and [len] do not designate a valid
+ substring of [dst]. *)
+
val nth : t -> int -> char
(** get the n-th character of the buffer. Raise [Invalid_argument] if
index out of bounds *)
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index d3a68cf63..e11f1e330 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -194,14 +194,14 @@ external close_desc: int -> unit = "caml_sys_close"
let prng = Random.State.make_self_init ();;
-let temp_file_name prefix suffix =
+let temp_file_name temp_dir prefix suffix =
let rnd = (Random.State.bits prng) land 0xFFFFFF in
- concat temp_dir_name (Printf.sprintf "%s%06x%s" prefix rnd suffix)
+ concat temp_dir (Printf.sprintf "%s%06x%s" prefix rnd suffix)
;;
-let temp_file prefix suffix =
+let temp_file ?(temp_dir=temp_dir_name) prefix suffix =
let rec try_name counter =
- let name = temp_file_name prefix suffix in
+ let name = temp_file_name temp_dir prefix suffix in
try
close_desc(open_desc name [Open_wronly; Open_creat; Open_excl] 0o600);
name
@@ -209,9 +209,9 @@ let temp_file prefix suffix =
if counter >= 1000 then raise e else try_name (counter + 1)
in try_name 0
-let open_temp_file ?(mode = [Open_text]) prefix suffix =
+let open_temp_file ?(mode = [Open_text]) ?(temp_dir=temp_dir_name) prefix suffix =
let rec try_name counter =
- let name = temp_file_name prefix suffix in
+ let name = temp_file_name temp_dir prefix suffix in
try
(name,
open_out_gen (Open_wronly::Open_creat::Open_excl::mode) 0o600 name)
diff --git a/stdlib/filename.mli b/stdlib/filename.mli
index 3a968e0a1..e01660952 100644
--- a/stdlib/filename.mli
+++ b/stdlib/filename.mli
@@ -22,6 +22,9 @@ val parent_dir_name : string
(** The conventional name for the parent of the current directory
(e.g. [..] in Unix). *)
+val dir_sep : string
+(** The directory separator (e.g. [/] in Unix). *)
+
val concat : string -> string -> string
(** [concat dir file] returns a file name that designates file
[file] in directory [dir]. *)
@@ -68,11 +71,13 @@ val basename : string -> string
val dirname : string -> string
(** See {!Filename.basename}. *)
-val temp_file : string -> string -> string
+val temp_file : ?temp_dir: string -> string -> string -> string
(** [temp_file prefix suffix] returns the name of a
fresh temporary file in the temporary directory.
The base name of the temporary file is formed by concatenating
[prefix], then a suitably chosen integer number, then [suffix].
+ The optional argument [temp_dir] indicates the temporary directory
+ to use, defaulting to {!Filename.temp_dir_name}.
The temporary file is created empty, with permissions [0o600]
(readable and writable only by the file owner). The file is
guaranteed to be different from any other file that existed when
@@ -80,7 +85,7 @@ val temp_file : string -> string -> string
*)
val open_temp_file :
- ?mode: open_flag list -> string -> string -> string * out_channel
+ ?mode: open_flag list -> ?temp_dir: string -> string -> string -> string * out_channel
(** Same as {!Filename.temp_file}, but returns both the name of a fresh
temporary file, and an output channel opened (atomically) on
this file. This function is more secure than [temp_file]: there
diff --git a/stdlib/format.mli b/stdlib/format.mli
index 897ebb3ef..58cb29e24 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -359,7 +359,45 @@ val get_formatter_output_functions :
unit -> (string -> int -> int -> unit) * (unit -> unit);;
(** Return the current output functions of the pretty-printer. *)
-(** {6 Changing the meaning of printing tags} *)
+(** {6 Changing the meaning of standard formatter pretty printing} *)
+
+(** The [Format] module is versatile enough to let you completely redefine
+ the meaning of pretty printing: you may provide your own functions to define
+ how to handle indentation, line breaking, and even printing of all the
+ characters that have to be printed! *)
+
+val set_all_formatter_output_functions :
+ out:(string -> int -> int -> unit) ->
+ flush:(unit -> unit) ->
+ newline:(unit -> unit) ->
+ spaces:(int -> unit) ->
+ unit;;
+(** [set_all_formatter_output_functions out flush outnewline outspace]
+ redirects the pretty-printer output to the functions [out] and
+ [flush] as described in [set_formatter_output_functions]. In
+ addition, the pretty-printer function that outputs a newline is set
+ to the function [outnewline] and the function that outputs
+ indentation spaces is set to the function [outspace].
+
+ This way, you can change the meaning of indentation (which can be
+ something else than just printing space characters) and the
+ meaning of new lines opening (which can be connected to any other
+ action needed by the application at hand). The two functions
+ [outspace] and [outnewline] are normally connected to [out] and
+ [flush]: respective default values for [outspace] and [outnewline]
+ are [out (String.make n ' ') 0 n] and [out "\n" 0 1]. *)
+
+val get_all_formatter_output_functions :
+ unit ->
+ (string -> int -> int -> unit) *
+ (unit -> unit) *
+ (unit -> unit) *
+ (int -> unit);;
+(** Return the current output functions of the pretty-printer,
+ including line breaking and indentation functions. Useful to record the
+ current setting and restore it afterwards. *)
+
+(** {6 Changing the meaning of printing semantics tags} *)
type formatter_tag_functions = {
mark_open_tag : tag -> string;
@@ -429,10 +467,10 @@ type formatter_output_meaning = {
(** {6 Changing the meaning of the standard output pretty printer} *)
val set_formatter_output_meaning : formatter_output_meaning -> unit
- (** Set the output functions according to the given meaning. *)
+ (** Set the output functions according to the given meaning. *)
;;
val get_formatter_output_meaning : formatter_output_meaning
- (** Get the current meaning of the output functions. *)
+ (** Get the current meaning of the output functions. *)
;;
(** An alternative way to modify the behaviour of output functions in an
diff --git a/stdlib/obj.ml b/stdlib/obj.ml
index 9685be38f..922febd65 100644
--- a/stdlib/obj.ml
+++ b/stdlib/obj.ml
@@ -27,9 +27,12 @@ external set_tag : t -> int -> unit = "caml_obj_set_tag"
external size : t -> int = "%obj_size"
external field : t -> int -> t = "%obj_field"
external set_field : t -> int -> t -> unit = "%obj_set_field"
+let double_field x i = Array.get (obj x : float array) i
+let set_double_field x i v = Array.set (obj x : float array) i v
external new_block : int -> int -> t = "caml_obj_block"
external dup : t -> t = "caml_obj_dup"
external truncate : t -> int -> unit = "caml_obj_truncate"
+external add_offset : t -> int -> t = "caml_obj_add_offset"
let marshal (obj : t) =
Marshal.to_string obj []
diff --git a/stdlib/obj.mli b/stdlib/obj.mli
index a35b119bd..34b78fdb4 100644
--- a/stdlib/obj.mli
+++ b/stdlib/obj.mli
@@ -28,11 +28,14 @@ external is_int : t -> bool = "%obj_is_int"
external tag : t -> int = "caml_obj_tag"
external set_tag : t -> int -> unit = "caml_obj_set_tag"
external size : t -> int = "%obj_size"
-external truncate : t -> int -> unit = "caml_obj_truncate"
external field : t -> int -> t = "%obj_field"
external set_field : t -> int -> t -> unit = "%obj_set_field"
+val double_field : t -> int -> float
+val set_double_field : t -> int -> float -> unit
external new_block : int -> int -> t = "caml_obj_block"
external dup : t -> t = "caml_obj_dup"
+external truncate : t -> int -> unit = "caml_obj_truncate"
+external add_offset : t -> int -> t = "caml_obj_add_offset"
val lazy_tag : int
val closure_tag : int
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index 47282e360..7a1e68dd9 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -71,7 +71,7 @@ external ( >= ) : 'a -> 'a -> bool = "%greaterequal"
The ordering is compatible with [(=)]. As in the case
of [(=)], mutable structures are compared by contents.
Comparison between functional values raises [Invalid_argument].
- Comparison between cyclic structures does not terminate. *)
+ Comparison between cyclic structures may not terminate. *)
external compare : 'a -> 'a -> int = "%compare"
(** [compare x y] returns [0] if [x] is equal to [y],
@@ -93,10 +93,14 @@ external compare : 'a -> 'a -> int = "%compare"
the {!List.sort} and {!Array.sort} functions. *)
val min : 'a -> 'a -> 'a
-(** Return the smaller of the two arguments. *)
+(** Return the smaller of the two arguments.
+ The result is unspecified if one of the arguments contains
+ the float value [nan]. *)
val max : 'a -> 'a -> 'a
-(** Return the greater of the two arguments. *)
+(** Return the greater of the two arguments.
+ The result is unspecified if one of the arguments contains
+ the float value [nan]. *)
external ( == ) : 'a -> 'a -> bool = "%eq"
(** [e1 == e2] tests for physical equality of [e1] and [e2].
@@ -228,8 +232,8 @@ external ( asr ) : int -> int -> int = "%asrint"
[neg_infinity] for [-1.0 /. 0.0], and [nan] (``not a number'')
for [0.0 /. 0.0]. These special numbers then propagate through
floating-point computations as expected: for instance,
- [1.0 /. infinity] is [0.0], and any operation with [nan] as
- argument returns [nan] as result.
+ [1.0 /. infinity] is [0.0], and any arithmetic operation with [nan]
+ as argument returns [nan] as result.
*)
external ( ~-. ) : float -> float = "%negfloat"
diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml
index f06717c27..11e7d4fd6 100644
--- a/stdlib/printexc.ml
+++ b/stdlib/printexc.ml
@@ -15,6 +15,8 @@
open Printf;;
+let printers = ref []
+
let locfmt = format_of_string "File \"%s\", line %d, characters %d-%d: %s";;
let field x i =
@@ -48,9 +50,16 @@ let to_string = function
| Assert_failure(file, line, char) ->
sprintf locfmt file line char (char+6) "Assertion failed"
| x ->
- let x = Obj.repr x in
- let constructor = (Obj.magic(Obj.field (Obj.field x 0) 0) : string) in
- constructor ^ (fields x)
+ let rec conv = function
+ | hd :: tl ->
+ (match try hd x with _ -> None with
+ | Some s -> s
+ | None -> conv tl)
+ | [] ->
+ let x = Obj.repr x in
+ let constructor = (Obj.magic(Obj.field (Obj.field x 0) 0) : string) in
+ constructor ^ (fields x) in
+ conv !printers
;;
let print fct arg =
@@ -125,3 +134,5 @@ let get_backtrace () =
external record_backtrace: bool -> unit = "caml_record_backtrace"
external backtrace_status: unit -> bool = "caml_backtrace_status"
+let register_printer fn =
+ printers := fn :: !printers
diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli
index a3ae6ba7b..99729e10f 100644
--- a/stdlib/printexc.mli
+++ b/stdlib/printexc.mli
@@ -57,3 +57,13 @@ val record_backtrace: bool -> unit
val backtrace_status: unit -> bool
(** [Printexc.backtrace_status()] returns [true] if exception
backtraces are currently recorded, [false] if not. *)
+
+val register_printer : (exn -> string option) -> unit
+(** [Printexc.register_printer fn] registers [fn] as an exception printer.
+ The printer should return [None] if it does not know how to convert
+ the passed exception, and [Some s] with [s] the resulting string if
+ it can convert the passed exception.
+ When converting an exception into a string, the printers will be invoked
+ in the reverse order of their registrations, until a printer returns
+ a [Some s] value (if no such printer exists, the runtime will use a
+ generic printer). *)
diff --git a/stdlib/scanf.mli b/stdlib/scanf.mli
index 21861b66a..d3033f028 100644
--- a/stdlib/scanf.mli
+++ b/stdlib/scanf.mli
@@ -215,12 +215,15 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
(** {7 The space character in format strings} *)
(** As mentioned above, a plain character in the format string is just
- matched with the characters of the input; however, one character is a
- special exception to this simple rule: the space character (ASCII code
- 32) does not match a single space character, but any amount of
+ matched with the next character of the input; however, two characters are
+ special exceptions to this rule: the space character ([' '] or ASCII code
+ 32) and the line feed character (['\n'] or ASCII code 10).
+ A space does not match a single space character, but any amount of
``whitespace'' in the input. More precisely, a space inside the format
string matches {e any number} of tab, space, line feed and carriage
- return characters.
+ return characters. Similarly, a line feed character in the format string
+ matches either a single line feed or a carriage return followed by a line
+ feed.
Matching {e any} amount of whitespace, a space in the format string
also matches no amount of whitespace at all; hence, the call [bscanf ib
@@ -305,6 +308,7 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
- [N] or [L]: returns the number of tokens read so far.
- [!]: matches the end of input condition.
- [%]: matches one [%] character in the input.
+ - [,]: the no-op delimiter for conversion specifications.
Following the [%] character that introduces a conversion, there may be
the special flag [_]: the conversion that follows occurs as usual,
@@ -379,7 +383,7 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
[End_of_file]: if the end of input is reached the conversion succeeds and
simply returns the characters read so far, or [""] if none were ever read. *)
-(** {6 Specialized formatted input functions} *)
+(** {6 Specialised formatted input functions} *)
val fscanf : Pervasives.in_channel -> ('a, 'b, 'c, 'd) scanner;;
(** Same as {!Scanf.bscanf}, but reads from the given regular input channel.
@@ -416,8 +420,8 @@ val bscanf_format :
Scanning.in_channel -> ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
(('a, 'b, 'c, 'd, 'e, 'f) format6 -> 'g) -> 'g;;
(** [bscanf_format ic fmt f] reads a format string token from the formatted
- input channel [ic], according to the given format string [fmt], and applies [f] to
- the resulting format string value.
+ input channel [ic], according to the given format string [fmt], and
+ applies [f] to the resulting format string value.
Raise [Scan_failure] if the format string value read does not have the
same type as [fmt]. *)
diff --git a/stdlib/stdlib.mllib b/stdlib/stdlib.mllib
index 9f835c6fa..91265e5da 100644
--- a/stdlib/stdlib.mllib
+++ b/stdlib/stdlib.mllib
@@ -1,48 +1,49 @@
-# This file lists all standard library modules.
+# This file lists all standard library modules
+# (in the same order as Makefile.shared).
# It is used in particular to know what to expunge in toplevels.
# $Id$
Pervasives
-Arg
Array
-ArrayLabels
-Buffer
-Callback
-CamlinternalLazy
-CamlinternalMod
-CamlinternalOO
+List
Char
-Complex
-Digest
-Filename
-Format
-Gc
-Genlex
+String
+Sys
Hashtbl
+Sort
+Marshal
+Obj
Int32
Int64
-Lazy
-Lexing
-List
-ListLabels
-Map
-Marshal
-MoreLabels
Nativeint
-Obj
-Oo
+Lexing
Parsing
-Printexc
-Printf
-Queue
-Random
-Scanf
Set
-Sort
+Map
Stack
-StdLabels
+Queue
+CamlinternalLazy
+Lazy
Stream
-String
-StringLabels
-Sys
+Buffer
+Printf
+Format
+Scanf
+Arg
+Printexc
+Gc
+Digest
+Random
+Callback
+CamlinternalOO
+Oo
+CamlinternalMod
+Genlex
Weak
+Filename
+Complex
+ArrayLabels
+ListLabels
+StringLabels
+MoreLabels
+StdLabels