]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/stdlib/marshal.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / stdlib / marshal.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1997 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the GNU Library General Public License, with    *)
10 (*  the special exception on linking described in file ../LICENSE.     *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: marshal.mli 7164 2005-10-25 18:34:07Z doligez $ *)
15
16 (** Marshaling of data structures.
17
18    This module provides functions to encode arbitrary data structures
19    as sequences of bytes, which can then be written on a file or
20    sent over a pipe or network connection.  The bytes can then
21    be read back later, possibly in another process, and decoded back
22    into a data structure. The format for the byte sequences
23    is compatible across all machines for a given version of Objective Caml.
24
25    Warning: marshaling is currently not type-safe. The type
26    of marshaled data is not transmitted along the value of the data,
27    making it impossible to check that the data read back possesses the
28    type expected by the context. In particular, the result type of
29    the [Marshal.from_*] functions is given as ['a], but this is
30    misleading: the returned Caml value does not possess type ['a]
31    for all ['a]; it has one, unique type which cannot be determined
32    at compile-type.  The programmer should explicitly give the expected
33    type of the returned value, using the following syntax:
34    - [(Marshal.from_channel chan : type)].
35    Anything can happen at run-time if the object in the file does not
36    belong to the given type.
37
38    The representation of marshaled values is not human-readable,
39    and uses bytes that are not printable characters. Therefore,
40    input and output channels used in conjunction with [Marshal.to_channel]
41    and [Marshal.from_channel] must be opened in binary mode, using e.g.
42    [open_out_bin] or [open_in_bin]; channels opened in text mode will
43    cause unmarshaling errors on platforms where text channels behave
44    differently than binary channels, e.g. Windows.
45 *)
46
47 type extern_flags =
48     No_sharing                          (** Don't preserve sharing *)
49   | Closures                            (** Send function closures *)
50 (** The flags to the [Marshal.to_*] functions below. *)
51
52 val to_channel : out_channel -> 'a -> extern_flags list -> unit
53 (** [Marshal.to_channel chan v flags] writes the representation
54    of [v] on channel [chan]. The [flags] argument is a
55    possibly empty list of flags that governs the marshaling
56    behavior with respect to sharing and functional values.
57
58    If [flags] does not contain [Marshal.No_sharing], circularities
59    and sharing inside the value [v] are detected and preserved
60    in the sequence of bytes produced. In particular, this
61    guarantees that marshaling always terminates. Sharing
62    between values marshaled by successive calls to
63    [Marshal.to_channel] is not detected, though.
64    If [flags] contains [Marshal.No_sharing], sharing is ignored.
65    This results in faster marshaling if [v] contains no shared
66    substructures, but may cause slower marshaling and larger
67    byte representations if [v] actually contains sharing,
68    or even non-termination if [v] contains cycles.
69
70    If [flags] does not contain [Marshal.Closures],
71    marshaling fails when it encounters a functional value
72    inside [v]: only ``pure'' data structures, containing neither
73    functions nor objects, can safely be transmitted between
74    different programs. If [flags] contains [Marshal.Closures],
75    functional values will be marshaled as a position in the code
76    of the program. In this case, the output of marshaling can
77    only be read back in processes that run exactly the same program,
78    with exactly the same compiled code. (This is checked
79    at un-marshaling time, using an MD5 digest of the code
80    transmitted along with the code position.) *)
81
82 external to_string :
83   'a -> extern_flags list -> string = "caml_output_value_to_string"
84 (** [Marshal.to_string v flags] returns a string containing
85    the representation of [v] as a sequence of bytes.
86    The [flags] argument has the same meaning as for
87    {!Marshal.to_channel}. *)
88
89 val to_buffer : string -> int -> int -> 'a -> extern_flags list -> int
90 (** [Marshal.to_buffer buff ofs len v flags] marshals the value [v],
91    storing its byte representation in the string [buff],
92    starting at character number [ofs], and writing at most
93    [len] characters.  It returns the number of characters
94    actually written to the string. If the byte representation
95    of [v] does not fit in [len] characters, the exception [Failure]
96    is raised. *)
97
98 val from_channel : in_channel -> 'a
99 (** [Marshal.from_channel chan] reads from channel [chan] the
100    byte representation of a structured value, as produced by
101    one of the [Marshal.to_*] functions, and reconstructs and
102    returns the corresponding value.*)
103
104 val from_string : string -> int -> 'a
105 (** [Marshal.from_string buff ofs] unmarshals a structured value
106    like {!Marshal.from_channel} does, except that the byte
107    representation is not read from a channel, but taken from
108    the string [buff], starting at position [ofs]. *)
109
110 val header_size : int
111 (** The bytes representing a marshaled value are composed of
112    a fixed-size header and a variable-sized data part,
113    whose size can be determined from the header.
114    {!Marshal.header_size} is the size, in characters, of the header.
115    {!Marshal.data_size}[ buff ofs] is the size, in characters,
116    of the data part, assuming a valid header is stored in
117    [buff] starting at position [ofs].
118    Finally, {!Marshal.total_size}[ buff ofs] is the total size,
119    in characters, of the marshaled value.
120    Both {!Marshal.data_size} and {!Marshal.total_size} raise [Failure]
121    if [buff], [ofs] does not contain a valid header.
122
123    To read the byte representation of a marshaled value into
124    a string buffer, the program needs to read first
125    {!Marshal.header_size} characters into the buffer,
126    then determine the length of the remainder of the
127    representation using {!Marshal.data_size},
128    make sure the buffer is large enough to hold the remaining
129    data, then read it, and finally call {!Marshal.from_string}
130    to unmarshal the value. *)
131
132 val data_size : string -> int -> int
133 (** See {!Marshal.header_size}.*)
134
135 val total_size : string -> int -> int
136 (** See {!Marshal.header_size}.*)