array.mli: documentation des cas d'erreur de make, make_matrix
string.mli: documentation des cas d'erreur de create, make buffer.ml, buffer.mli: blindage de create hashtbl.ml, hashtbl.mli: blindage de create pervasives.ml: fix typo dans bool_of_string gc.mli: utilisation de {r with l=v} dans l'exemple git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2411 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
3f10f2b54d
commit
10270afb11
|
@ -5,7 +5,7 @@
|
|||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* Automatique. Distributed only by permission. *)
|
||||
(* en Automatique. Distributed only by permission. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
|
@ -36,7 +36,11 @@ external create: int -> 'a -> 'a array = "make_vect"
|
|||
physically equal to [x] (in the sense of the [==] predicate).
|
||||
Consequently, if [x] is mutable, it is shared among all elements
|
||||
of the array, and modifying [x] through one of the array entries
|
||||
will modify all other entries at the same time. *)
|
||||
will modify all other entries at the same time.
|
||||
Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_array_length].
|
||||
If the value of [x] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2].
|
||||
[Array.create] is a deprecated alias for [Array.make]. *)
|
||||
val init: int -> (int -> 'a) -> 'a array
|
||||
(* [Array.init n f] returns a fresh array of length [n],
|
||||
with element number [i] initialized to the result of [f i].
|
||||
|
@ -49,7 +53,13 @@ val create_matrix: int -> int -> 'a -> 'a array array
|
|||
second dimension [dimy]. All the elements of this new matrix
|
||||
are initially physically equal to [e].
|
||||
The element ([x,y]) of a matrix [m] is accessed
|
||||
with the notation [m.(x).(y)]. *)
|
||||
with the notation [m.(x).(y)].
|
||||
Raise [Invalid_argument] if [dimx] or [dimy] is less than 1 or
|
||||
greater than [Sys.max_array_length].
|
||||
If the value of [e] is a floating-point number, then the maximum
|
||||
size is only [Sys.max_array_length / 2].
|
||||
[Array.create_matrix] is a deprecated alias for [Array.make_matrix].
|
||||
*)
|
||||
val append: 'a array -> 'a array -> 'a array
|
||||
(* [Array.append v1 v2] returns a fresh array containing the
|
||||
concatenation of the arrays [v1] and [v2]. *)
|
||||
|
|
|
@ -18,7 +18,8 @@ type t =
|
|||
initial_buffer : string}
|
||||
|
||||
let create n =
|
||||
if n <= 0 then invalid_arg "Buffer.create";
|
||||
let n = if n < 1 then 1 else n in
|
||||
let n = if n > Sys.max_string_length then Sys.max_string_length else n in
|
||||
let s = String.create n in
|
||||
{buffer = s; position = 0; length = String.length s; initial_buffer = s}
|
||||
|
||||
|
|
|
@ -29,7 +29,9 @@ val create : int -> t
|
|||
as the number of characters that are expected to be stored in
|
||||
the buffer (for instance, 80 for a buffer that holds one output
|
||||
line). Nothing bad will happen if the buffer grows beyond that
|
||||
limit, however. In doubt, take [n = 16] for instance. *)
|
||||
limit, however. In doubt, take [n = 16] for instance.
|
||||
If [n] is not between 1 and [Sys.max_string_length], it will
|
||||
be clipped to that interval. *)
|
||||
val contents : t -> string
|
||||
(* Return a copy of the current contents of the buffer.
|
||||
The buffer itself is unchanged. *)
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
||||
(* Automatique. Distributed only by permission. *)
|
||||
(* en Automatique. Distributed only by permission. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
|
@ -118,13 +118,7 @@ external get : unit -> control = "gc_get"
|
|||
(* Return the current values of the GC parameters in a [control] record. *)
|
||||
external set : control -> unit = "gc_set"
|
||||
(* [set r] changes the GC parameters according to the [control] record [r].
|
||||
The normal usage is:
|
||||
[
|
||||
let r = Gc.get () in (* Get the current parameters. *)
|
||||
r.verbose <- 13; (* Change some of them. *)
|
||||
Gc.set r (* Set the new values. *)
|
||||
]
|
||||
*)
|
||||
The normal usage is: [ Gc.set { (Gc.get()) with Gc.verbose = 13 } ]. *)
|
||||
external minor : unit -> unit = "gc_minor"
|
||||
(* Trigger a minor collection. *)
|
||||
external major : unit -> unit = "gc_major"
|
||||
|
|
|
@ -29,8 +29,9 @@ and ('a, 'b) bucketlist =
|
|||
| Cons of 'a * 'b * ('a, 'b) bucketlist
|
||||
|
||||
let create initial_size =
|
||||
if initial_size <= 0 then invalid_arg "Hashtbl.create" else
|
||||
{ max_len = 3; data = Array.create initial_size Empty }
|
||||
let s = if initial_size < 1 then 1 else initial_size in
|
||||
let s = if s > Sys.max_array_length then Sys.max_array_length else s in
|
||||
{ max_len = 3; data = Array.make s Empty }
|
||||
|
||||
let clear h =
|
||||
for i = 0 to Array.length h.data - 1 do
|
||||
|
|
|
@ -24,8 +24,7 @@ val create : int -> ('a,'b) t
|
|||
(* [Hashtbl.create n] creates a new, empty hash table, with
|
||||
initial size [n]. The table grows as needed, so [n] is
|
||||
just an initial guess. Better results are said to be
|
||||
achieved when [n] is a prime number.
|
||||
Raise [Invalid_argument] if [n] is less than 1. *)
|
||||
achieved when [n] is a prime number. *)
|
||||
|
||||
val clear : ('a, 'b) t -> unit
|
||||
(* Empty a hash table. *)
|
||||
|
|
|
@ -147,7 +147,7 @@ let string_of_bool b =
|
|||
let bool_of_string = function
|
||||
| "true" -> true
|
||||
| "false" -> false
|
||||
| _ -> invalid_arg "string_of_bool"
|
||||
| _ -> invalid_arg "bool_of_string"
|
||||
|
||||
let string_of_int n =
|
||||
format_int "%d" n
|
||||
|
|
|
@ -32,10 +32,14 @@ external set : string -> int -> char -> unit = "%string_safe_set"
|
|||
|
||||
external create : int -> string = "create_string"
|
||||
(* [String.create n] returns a fresh string of length [n].
|
||||
The string initially contains arbitrary characters. *)
|
||||
The string initially contains arbitrary characters.
|
||||
Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length].
|
||||
*)
|
||||
val make : int -> char -> string
|
||||
(* [String.make n c] returns a fresh string of length [n],
|
||||
filled with the character [c]. *)
|
||||
filled with the character [c].
|
||||
Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length].
|
||||
*)
|
||||
val copy : string -> string
|
||||
(* Return a copy of the given string. *)
|
||||
val sub : string -> int -> int -> string
|
||||
|
|
Loading…
Reference in New Issue