]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/stdlib/marshal.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / stdlib / marshal.ml
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.ml 7164 2005-10-25 18:34:07Z doligez $ *)
15
16 type extern_flags =
17     No_sharing
18   | Closures
19
20 external to_channel: out_channel -> 'a -> extern_flags list -> unit
21     = "caml_output_value"
22 external to_string: 'a -> extern_flags list -> string
23     = "caml_output_value_to_string"
24 external to_buffer_unsafe:
25       string -> int -> int -> 'a -> extern_flags list -> int
26     = "caml_output_value_to_buffer"
27
28 let to_buffer buff ofs len v flags =
29   if ofs < 0 || len < 0 || ofs > String.length buff - len
30   then invalid_arg "Marshal.to_buffer: substring out of bounds"
31   else to_buffer_unsafe buff ofs len v flags
32
33 external from_channel: in_channel -> 'a = "caml_input_value"
34 external from_string_unsafe: string -> int -> 'a
35                            = "caml_input_value_from_string"
36 external data_size_unsafe: string -> int -> int = "caml_marshal_data_size"
37
38 let header_size = 20
39 let data_size buff ofs =
40   if ofs < 0 || ofs > String.length buff - header_size
41   then invalid_arg "Marshal.data_size"
42   else data_size_unsafe buff ofs
43 let total_size buff ofs = header_size + data_size buff ofs
44
45 let from_string buff ofs =
46   if ofs < 0 || ofs > String.length buff - header_size
47   then invalid_arg "Marshal.from_size"
48   else begin
49     let len = data_size_unsafe buff ofs in
50     if ofs > String.length buff - (header_size + len)
51     then invalid_arg "Marshal.from_string"
52     else from_string_unsafe buff ofs
53   end