diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 2000-03-06 20:20:24 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 2000-03-06 20:20:24 +0000 |
commit | 12ec3de6fbe366a59f835d6b2c2147ecd7764cb4 (patch) | |
tree | 251ceebcadbb634e0d148a3e9dad2d17001681b2 | |
parent | 836c41cd32eeb63af260c4bf35c3d6437bbd619c (diff) |
Gestion des sections dans un executable bytecode
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2906 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | bytecomp/bytesections.ml | 85 | ||||
-rw-r--r-- | bytecomp/bytesections.mli | 48 |
2 files changed, 133 insertions, 0 deletions
diff --git a/bytecomp/bytesections.ml b/bytecomp/bytesections.ml new file mode 100644 index 000000000..084d6a043 --- /dev/null +++ b/bytecomp/bytesections.ml @@ -0,0 +1,85 @@ +(***********************************************************************) +(* *) +(* Objective Caml *) +(* *) +(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) +(* *) +(* Copyright 2000 Institut National de Recherche en Informatique et *) +(* en Automatique. All rights reserved. This file is distributed *) +(* under the terms of the Q Public License version 1.0. *) +(* *) +(***********************************************************************) + +(* $Id$ *) + +(* Handling of sections in bytecode executable files *) + +(* List of all sections, in reverse order *) + +let section_table = ref ([] : (string * int) list) + +(* Recording sections *) + +let section_beginning = ref 0 + +let init_record outchan = + section_beginning := pos_out outchan; + section_table := [] + +let record outchan name = + let pos = pos_out outchan in + section_table := (name, pos - !section_beginning) :: !section_table; + section_beginning := pos + +let write_toc_and_trailer outchan = + List.iter + (fun (name, len) -> + output_string outchan name; output_binary_int outchan len) + (List.rev !section_table); + output_binary_int outchan (List.length !section_table); + output_string outchan Config.exec_magic_number; + section_table := []; + +(* Read the table of sections from a bytecode executable *) + +exception Bad_magic_number + +let read_toc ic = + let pos_trailer = in_channel_length ic - 16 in + seek_in ic pos_trailer; + let num_sections = input_binary_int ic in + let header = String.create(String.length Config.exec_magic_number) in + really_input ic header 0 (String.length Config.exec_magic_number); + if header <> Config.exec_magic_number then raise Bad_magic_number; + seek_in ic (pos_trailer - 8 * num_sections); + section_table := []; + for i = 1 to num_sections do + let name = String.create 4 in + really_input ic name 0 4; + let len = input_binary_int ic in + section_table := (name, len) :: !section_table + done + +(* Return the current table of contents *) + +let toc () = List.rev !section_table + +(* Position ic at the beginning of the section named "name", + and return the length of that section. Raise Not_found if no + such section exists. *) + +let seek_section ic name = + let rec seek_sec curr_ofs = function + [] -> raise Not_found + | (n, len) :: rem -> + if n = name + then begin seek_in ic (curr_ofs - len); len end + else seek_sec (curr_ofs - len) rem in + seek_sec (in_channel_length ic - 16 - 8 * List.length !section_table) + !section_table + +(* Return the position of the beginning of the first section *) + +let pos_first_section ic = + in_channel_length ic - 16 - 8 * List.length !section_table - + List.fold_left (fun total (name, len) -> total + len) 0 !section_table diff --git a/bytecomp/bytesections.mli b/bytecomp/bytesections.mli new file mode 100644 index 000000000..9e1279609 --- /dev/null +++ b/bytecomp/bytesections.mli @@ -0,0 +1,48 @@ +(***********************************************************************) +(* *) +(* Objective Caml *) +(* *) +(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) +(* *) +(* Copyright 2000 Institut National de Recherche en Informatique et *) +(* en Automatique. All rights reserved. This file is distributed *) +(* under the terms of the Q Public License version 1.0. *) +(* *) +(***********************************************************************) + +(* $Id$ *) + +(* Handling of sections in bytecode executable files *) + +(** Recording sections written to a bytecode executable file *) + +val init_record: out_channel -> unit + (* Start recording sections from the current position in out_channel *) + +val record: out_channel -> string -> unit + (* Record the current position in the out_channel as the end of + the section with the given name *) + +val write_toc_and_trailer: out_channel -> unit + (* Write the table of contents and the standard trailer for bytecode + executable files *) + +(** Reading sections from a bytecode executable file *) + +val read_toc: in_channel -> unit + (* Read the table of sections from a bytecode executable *) + +exception Bad_magic_number + (* Raised by [read_toc] if magic number doesn't match *) + +val toc: unit -> (string * int) list + (* Return the current table of contents as a list of + (section name, section length) pairs. *) + +val seek_section: in_channel -> string -> int + (* Position the input channel at the beginning of the section named "name", + and return the length of that section. Raise Not_found if no + such section exists. *) + +val pos_first_section: in_channel -> int + (* Return the position of the beginning of the first section *) |