Ajout de Marshal.total_length

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1685 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1997-07-31 19:06:38 +00:00
parent ceb5c77382
commit 8cd35202f4
2 changed files with 15 additions and 8 deletions

View File

@ -4,7 +4,7 @@
(* *) (* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *) (* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Copyright 1997 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *) (* Automatique. Distributed only by permission. *)
(* *) (* *)
(***********************************************************************) (***********************************************************************)
@ -17,7 +17,8 @@ type extern_flags =
external to_channel: out_channel -> 'a -> extern_flags list -> unit external to_channel: out_channel -> 'a -> extern_flags list -> unit
= "output_value" = "output_value"
external to_string: 'a -> extern_flags list -> string = "output_value_to_string" external to_string: 'a -> extern_flags list -> string
= "output_value_to_string"
external to_buffer_unsafe: external to_buffer_unsafe:
string -> int -> int -> 'a -> extern_flags list -> unit string -> int -> int -> 'a -> extern_flags list -> unit
= "output_value_to_buffer" = "output_value_to_buffer"
@ -36,6 +37,7 @@ let data_size buff ofs =
if ofs < 0 || ofs + header_size > String.length buff if ofs < 0 || ofs + header_size > String.length buff
then invalid_arg "Marshal.data_size" then invalid_arg "Marshal.data_size"
else data_size_unsafe buff ofs else data_size_unsafe buff ofs
let total_size buff ofs = header_size + data_size buff ofs
let from_string buff ofs = let from_string buff ofs =
if ofs < 0 || ofs + header_size > String.length buff if ofs < 0 || ofs + header_size > String.length buff

View File

@ -4,7 +4,7 @@
(* *) (* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *) (* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Copyright 1997 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *) (* Automatique. Distributed only by permission. *)
(* *) (* *)
(***********************************************************************) (***********************************************************************)
@ -30,7 +30,7 @@
at compile-type. The programmer should explicitly give the expected at compile-type. The programmer should explicitly give the expected
type of the returned value, using the following syntax: type of the returned value, using the following syntax:
[(Marshal.from_channel chan : type)]. [(Marshal.from_channel chan : type)].
The behavior is unspecified if the object in the file does not Anything can happen at run-time if the object in the file does not
belong to the given type. belong to the given type.
The representation of marshaled values is not human-readable, The representation of marshaled values is not human-readable,
@ -106,19 +106,24 @@ val from_string: string -> int -> 'a
val header_size : int val header_size : int
val data_size : string -> int -> int val data_size : string -> int -> int
val total_size : string -> int -> int
(* The bytes representing a marshaled value are composed of (* The bytes representing a marshaled value are composed of
a fixed-size header and a variable-sized data part, a fixed-size header and a variable-sized data part,
whose size can be determined from the header. whose size can be determined from the header.
[Marshal.header_size] is the size, in characters, of the header. [Marshal.header_size] is the size, in characters, of the header.
[Marshal.data_size buff ofs] is the size, in characters, [Marshal.data_size buff ofs] is the size, in characters,
of the data part, assuming a valid header is stored in of the data part, assuming a valid header is stored in
[buff] starting at position [ofs]. It raises [Failure] [buff] starting at position [ofs].
Finally, [Marshal.total_size buff ofs] is the total size,
in characters, of the marshaled value.
Both [Marshal.data_size] and [Marshal.total_size] raise [Failure]
if [buff], [ofs] does not contain a valid header. if [buff], [ofs] does not contain a valid header.
To read the byte representation of a marshaled value into To read the byte representation of a marshaled value into
a string buffer, one needs to read first [Marshal.header_size] a string buffer, the program needs to read first
characters into the buffer, then determine the length of the [Marshal.header_size] characters into the buffer,
remainder of the representation using [Marshal.data_size], then determine the length of the remainder of the
representation using [Marshal.data_size],
make sure the buffer is large enough to hold the variable make sure the buffer is large enough to hold the variable
size, then read it, and finally call [Marshal.from_string] size, then read it, and finally call [Marshal.from_string]
to unmarshal the value. *) to unmarshal the value. *)