1995-11-07 02:01:45 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-11-07 02:01:45 -08:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-11-07 02:01:45 -08:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-09-29 09:20:15 -07:00
|
|
|
(* Dynamic loading of .cmo files *)
|
|
|
|
|
|
|
|
open Emitcode
|
|
|
|
|
|
|
|
type error =
|
|
|
|
Not_a_bytecode_file of string
|
|
|
|
| Inconsistent_import of string
|
|
|
|
| Unavailable_unit of string
|
1995-10-09 06:37:11 -07:00
|
|
|
| Unsafe_file
|
1995-09-29 09:20:15 -07:00
|
|
|
| Linking_error of string
|
|
|
|
| Corrupted_interface of string
|
|
|
|
|
|
|
|
exception Error of error
|
|
|
|
|
|
|
|
(* Initialize the linker tables and everything *)
|
|
|
|
|
|
|
|
let init () =
|
|
|
|
Symtable.init_toplevel()
|
|
|
|
|
|
|
|
(* Check that the object file being loaded has been compiled against
|
|
|
|
the same interfaces as the program itself. In addition, check that
|
|
|
|
only authorized compilation units are referenced. *)
|
|
|
|
|
1996-04-22 04:15:41 -07:00
|
|
|
let crc_interfaces = (Hashtbl.create 17 : (string, Digest.t) Hashtbl.t)
|
1995-09-29 09:20:15 -07:00
|
|
|
|
|
|
|
let check_consistency file_name cu =
|
1995-10-09 06:37:11 -07:00
|
|
|
List.iter
|
|
|
|
(fun (name, crc) ->
|
|
|
|
try
|
|
|
|
let auth_crc = Hashtbl.find crc_interfaces name in
|
|
|
|
if crc <> auth_crc then
|
|
|
|
raise(Error(Inconsistent_import name))
|
|
|
|
with Not_found ->
|
|
|
|
raise(Error(Unavailable_unit name)))
|
|
|
|
cu.cu_imports;
|
|
|
|
Hashtbl.add crc_interfaces cu.cu_name cu.cu_interface
|
1995-09-29 09:20:15 -07:00
|
|
|
|
|
|
|
(* Reset the crc_interfaces table *)
|
|
|
|
|
|
|
|
let clear_available_units () =
|
|
|
|
Hashtbl.clear crc_interfaces
|
|
|
|
|
|
|
|
(* Initialize the crc_interfaces table with a list of units with fixed CRCs *)
|
|
|
|
|
|
|
|
let add_available_units units =
|
|
|
|
List.iter (fun (unit, crc) -> Hashtbl.add crc_interfaces unit crc) units
|
|
|
|
|
|
|
|
(* Read the CRC of an interface from its .cmi file *)
|
|
|
|
|
1995-11-07 02:01:45 -08:00
|
|
|
let digest_interface unit loadpath =
|
1995-09-29 09:20:15 -07:00
|
|
|
let filename = Misc.find_in_path loadpath (Misc.lowercase unit ^ ".cmi") in
|
|
|
|
let ic = open_in_bin filename in
|
|
|
|
try
|
|
|
|
let buffer = String.create (String.length Config.cmi_magic_number) in
|
|
|
|
really_input ic buffer 0 (String.length Config.cmi_magic_number);
|
|
|
|
if buffer <> Config.cmi_magic_number then begin
|
|
|
|
close_in ic;
|
|
|
|
raise(Error(Corrupted_interface filename))
|
|
|
|
end;
|
|
|
|
input_value ic;
|
1995-10-09 06:37:11 -07:00
|
|
|
let crc = Digest.input ic in
|
1995-09-29 09:20:15 -07:00
|
|
|
close_in ic;
|
|
|
|
crc
|
|
|
|
with End_of_file | Failure _ ->
|
|
|
|
close_in ic;
|
|
|
|
raise(Error(Corrupted_interface filename))
|
|
|
|
|
|
|
|
(* Initialize the crc_interfaces table with a list of units.
|
|
|
|
Their CRCs are read from their interfaces. *)
|
|
|
|
|
|
|
|
let add_interfaces units loadpath =
|
|
|
|
add_available_units
|
1995-11-07 02:01:45 -08:00
|
|
|
(List.map (fun unit -> (unit, digest_interface unit loadpath)) units)
|
1995-09-29 09:20:15 -07:00
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
(* Check whether the object file being loaded was compiled in unsafe mode *)
|
1995-09-29 09:20:15 -07:00
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
let unsafe_allowed = ref false
|
1995-09-29 09:20:15 -07:00
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
let allow_unsafe_modules b =
|
|
|
|
unsafe_allowed := b
|
1995-09-29 09:20:15 -07:00
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
let check_unsafe_module cu =
|
1995-11-05 09:32:12 -08:00
|
|
|
if (not !unsafe_allowed) & cu.cu_primitives <> []
|
1995-10-09 06:37:11 -07:00
|
|
|
then raise(Error(Unsafe_file))
|
1995-09-29 09:20:15 -07:00
|
|
|
|
|
|
|
(* Load in-core and execute a bytecode object file *)
|
|
|
|
|
1996-04-18 09:30:15 -07:00
|
|
|
let load_compunit ic file_name compunit =
|
1995-09-29 09:20:15 -07:00
|
|
|
check_consistency file_name compunit;
|
1995-10-09 06:37:11 -07:00
|
|
|
check_unsafe_module compunit;
|
1995-09-29 09:20:15 -07:00
|
|
|
seek_in ic compunit.cu_pos;
|
1996-05-28 05:42:51 -07:00
|
|
|
let code_size = compunit.cu_codesize + 8 in
|
1995-09-29 09:20:15 -07:00
|
|
|
let code = Meta.static_alloc code_size in
|
|
|
|
unsafe_really_input ic code 0 compunit.cu_codesize;
|
1996-05-28 05:42:51 -07:00
|
|
|
String.unsafe_set code compunit.cu_codesize (Char.chr Opcodes.opRETURN);
|
1995-09-29 09:20:15 -07:00
|
|
|
String.unsafe_set code (compunit.cu_codesize + 1) '\000';
|
|
|
|
String.unsafe_set code (compunit.cu_codesize + 2) '\000';
|
|
|
|
String.unsafe_set code (compunit.cu_codesize + 3) '\000';
|
1996-05-28 05:42:51 -07:00
|
|
|
String.unsafe_set code (compunit.cu_codesize + 4) '\001';
|
|
|
|
String.unsafe_set code (compunit.cu_codesize + 5) '\000';
|
|
|
|
String.unsafe_set code (compunit.cu_codesize + 6) '\000';
|
|
|
|
String.unsafe_set code (compunit.cu_codesize + 7) '\000';
|
1996-04-18 09:30:15 -07:00
|
|
|
let initial_symtable = Symtable.current_state() in
|
1995-09-29 09:20:15 -07:00
|
|
|
begin try
|
|
|
|
Symtable.patch_object code compunit.cu_reloc;
|
|
|
|
Symtable.update_global_table()
|
|
|
|
with Symtable.Error _ ->
|
|
|
|
raise(Error(Linking_error file_name))
|
|
|
|
end;
|
1996-04-18 09:30:15 -07:00
|
|
|
begin try
|
1996-05-28 05:42:51 -07:00
|
|
|
(Meta.reify_bytecode code code_size) (); ()
|
1996-04-18 09:30:15 -07:00
|
|
|
with exn ->
|
|
|
|
Symtable.restore_state initial_symtable;
|
|
|
|
raise exn
|
|
|
|
end
|
|
|
|
|
|
|
|
let loadfile file_name =
|
|
|
|
let ic = open_in_bin file_name in
|
1996-06-25 06:47:16 -07:00
|
|
|
try
|
|
|
|
let buffer = String.create (String.length Config.cmo_magic_number) in
|
|
|
|
really_input ic buffer 0 (String.length Config.cmo_magic_number);
|
|
|
|
if buffer = Config.cmo_magic_number then begin
|
|
|
|
let compunit_pos = input_binary_int ic in (* Go to descriptor *)
|
|
|
|
seek_in ic compunit_pos;
|
|
|
|
load_compunit ic file_name (input_value ic : compilation_unit)
|
|
|
|
end else
|
|
|
|
if buffer = Config.cma_magic_number then begin
|
|
|
|
let toc_pos = input_binary_int ic in (* Go to table of contents *)
|
|
|
|
seek_in ic toc_pos;
|
|
|
|
List.iter (load_compunit ic file_name)
|
|
|
|
(input_value ic : compilation_unit list)
|
|
|
|
end else
|
|
|
|
raise(Error(Not_a_bytecode_file file_name));
|
|
|
|
close_in ic
|
|
|
|
with exc ->
|
|
|
|
close_in ic; raise exc
|
1995-10-09 06:37:11 -07:00
|
|
|
|
|
|
|
(* Error report *)
|
|
|
|
|
|
|
|
let error_message = function
|
|
|
|
Not_a_bytecode_file name ->
|
|
|
|
name ^ " is not a bytecode object file"
|
|
|
|
| Inconsistent_import name ->
|
|
|
|
"interface mismatch on " ^ name
|
|
|
|
| Unavailable_unit name ->
|
|
|
|
"no implementation available for " ^ name
|
|
|
|
| Unsafe_file ->
|
|
|
|
"this object file uses unsafe features"
|
|
|
|
| Linking_error name ->
|
|
|
|
"error while linking " ^ name
|
|
|
|
| Corrupted_interface name ->
|
|
|
|
"corrupted interface file " ^ name
|
|
|
|
|