1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07: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-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-07-02 09:41:48 -07:00
|
|
|
(* Compilation environments for compilation units *)
|
|
|
|
|
|
|
|
open Config
|
|
|
|
open Misc
|
|
|
|
open Clambda
|
|
|
|
|
|
|
|
type error =
|
|
|
|
Not_a_unit_info of string
|
|
|
|
| Corrupted_unit_info of string
|
|
|
|
| Illegal_renaming of string * string
|
|
|
|
|
|
|
|
exception Error of error
|
|
|
|
|
|
|
|
(* Each .o file has a matching .cmx file that provides the following infos
|
|
|
|
on the compilation unit:
|
|
|
|
- list of other units imported, with CRCs of their .cmx files
|
|
|
|
- approximation of the structure implemented
|
|
|
|
(includes descriptions of known functions: arity and direct entry
|
|
|
|
points)
|
|
|
|
- list of currying functions and application functions needed
|
|
|
|
The .cmx file contains these infos (as an externed record) plus a CRC
|
|
|
|
of these infos *)
|
|
|
|
|
|
|
|
type unit_infos =
|
1995-10-09 06:37:11 -07:00
|
|
|
{ mutable ui_name: string; (* Name of unit implemented *)
|
|
|
|
mutable ui_imports_cmi: (string * Digest.t) list; (* Interfaces imported *)
|
|
|
|
mutable ui_imports_cmx: (string * Digest.t) list; (* Infos imported *)
|
|
|
|
mutable ui_approx: value_approximation; (* Approx of the structure *)
|
|
|
|
mutable ui_curry_fun: int list; (* Currying functions needed *)
|
1996-04-18 09:26:54 -07:00
|
|
|
mutable ui_apply_fun: int list; (* Apply functions needed *)
|
|
|
|
mutable ui_force_link: bool } (* Always linked *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
let global_approx_table =
|
1996-04-22 04:15:41 -07:00
|
|
|
(Hashtbl.create 17 : (string, value_approximation) Hashtbl.t)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
let current_unit =
|
|
|
|
{ ui_name = "";
|
1995-10-09 06:37:11 -07:00
|
|
|
ui_imports_cmi = [];
|
|
|
|
ui_imports_cmx = [];
|
1995-07-02 09:41:48 -07:00
|
|
|
ui_approx = Value_unknown;
|
|
|
|
ui_curry_fun = [];
|
1996-04-18 09:26:54 -07:00
|
|
|
ui_apply_fun = [];
|
|
|
|
ui_force_link = false }
|
1995-07-02 09:41:48 -07:00
|
|
|
|
1997-05-15 06:22:08 -07:00
|
|
|
let reset name =
|
1995-07-02 09:41:48 -07:00
|
|
|
Hashtbl.clear global_approx_table;
|
|
|
|
current_unit.ui_name <- name;
|
1995-10-09 06:37:11 -07:00
|
|
|
current_unit.ui_imports_cmi <- [];
|
|
|
|
current_unit.ui_imports_cmx <- [];
|
1995-07-02 09:41:48 -07:00
|
|
|
current_unit.ui_curry_fun <- [];
|
1996-04-18 09:26:54 -07:00
|
|
|
current_unit.ui_apply_fun <- [];
|
|
|
|
current_unit.ui_force_link <- false
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
let current_unit_name () =
|
|
|
|
current_unit.ui_name
|
|
|
|
|
1995-07-11 11:03:29 -07:00
|
|
|
let read_unit_info filename =
|
1995-07-02 09:41:48 -07:00
|
|
|
let ic = open_in_bin filename in
|
|
|
|
try
|
|
|
|
let buffer = String.create (String.length cmx_magic_number) in
|
|
|
|
really_input ic buffer 0 (String.length cmx_magic_number);
|
|
|
|
if buffer <> cmx_magic_number then begin
|
|
|
|
close_in ic;
|
|
|
|
raise(Error(Not_a_unit_info filename))
|
|
|
|
end;
|
|
|
|
let ui = (input_value ic : unit_infos) in
|
1995-10-09 06:37:11 -07:00
|
|
|
let crc = Digest.input ic in
|
1995-07-02 09:41:48 -07:00
|
|
|
close_in ic;
|
1995-07-11 11:03:29 -07:00
|
|
|
(ui, crc)
|
1995-07-02 09:41:48 -07:00
|
|
|
with End_of_file | Failure _ ->
|
|
|
|
close_in ic;
|
|
|
|
raise(Error(Corrupted_unit_info(filename)))
|
|
|
|
|
|
|
|
(* Return the approximation of a global identifier *)
|
|
|
|
|
1995-11-09 05:21:49 -08:00
|
|
|
let cmx_not_found_crc =
|
|
|
|
"\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000"
|
|
|
|
|
1995-07-02 09:41:48 -07:00
|
|
|
let global_approx global_ident =
|
|
|
|
let modname = Ident.name global_ident in
|
|
|
|
try
|
|
|
|
Hashtbl.find global_approx_table modname
|
|
|
|
with Not_found ->
|
1995-11-09 05:21:49 -08:00
|
|
|
let (approx, crc) =
|
1995-07-02 09:41:48 -07:00
|
|
|
try
|
1995-07-11 11:03:29 -07:00
|
|
|
let filename =
|
1996-10-31 08:03:27 -08:00
|
|
|
find_in_path !load_path (String.uncapitalize modname ^ ".cmx") in
|
1995-07-11 11:03:29 -07:00
|
|
|
let (ui, crc) = read_unit_info filename in
|
|
|
|
if ui.ui_name <> modname then
|
|
|
|
raise(Error(Illegal_renaming(modname, filename)));
|
1995-11-09 05:21:49 -08:00
|
|
|
(ui.ui_approx, crc)
|
1995-07-11 11:03:29 -07:00
|
|
|
with Not_found ->
|
1995-11-09 05:21:49 -08:00
|
|
|
(Value_unknown, cmx_not_found_crc) in
|
|
|
|
current_unit.ui_imports_cmx <-
|
|
|
|
(modname, crc) :: current_unit.ui_imports_cmx;
|
1995-07-02 09:41:48 -07:00
|
|
|
Hashtbl.add global_approx_table modname approx;
|
|
|
|
approx
|
|
|
|
|
|
|
|
(* Register the approximation of the module being compiled *)
|
|
|
|
|
|
|
|
let set_global_approx approx =
|
|
|
|
current_unit.ui_approx <- approx
|
|
|
|
|
|
|
|
(* Record that a currying function or application function is needed *)
|
|
|
|
|
|
|
|
let need_curry_fun n =
|
|
|
|
if not (List.mem n current_unit.ui_curry_fun) then
|
|
|
|
current_unit.ui_curry_fun <- n :: current_unit.ui_curry_fun
|
|
|
|
|
|
|
|
let need_apply_fun n =
|
|
|
|
if not (List.mem n current_unit.ui_apply_fun) then
|
|
|
|
current_unit.ui_apply_fun <- n :: current_unit.ui_apply_fun
|
|
|
|
|
|
|
|
(* Write the description of the current unit *)
|
|
|
|
|
|
|
|
let save_unit_info filename =
|
1995-10-09 06:37:11 -07:00
|
|
|
current_unit.ui_imports_cmi <- Env.imported_units();
|
1995-07-02 09:41:48 -07:00
|
|
|
let oc = open_out_bin filename in
|
|
|
|
output_string oc cmx_magic_number;
|
|
|
|
output_value oc current_unit;
|
|
|
|
flush oc;
|
1995-10-09 06:37:11 -07:00
|
|
|
let crc = Digest.file filename in
|
|
|
|
Digest.output oc crc;
|
1995-07-02 09:41:48 -07:00
|
|
|
close_out oc
|
|
|
|
|
|
|
|
(* Error report *)
|
|
|
|
|
|
|
|
open Format
|
|
|
|
|
|
|
|
let report_error = function
|
|
|
|
Not_a_unit_info filename ->
|
|
|
|
print_string filename; print_space();
|
|
|
|
print_string "is not a compilation unit description."
|
|
|
|
| Corrupted_unit_info filename ->
|
|
|
|
print_string "Corrupted compilation unit description"; print_space();
|
|
|
|
print_string filename
|
|
|
|
| Illegal_renaming(modname, filename) ->
|
|
|
|
print_string filename; print_space();
|
|
|
|
print_string "contains the description for unit"; print_space();
|
|
|
|
print_string modname
|
|
|
|
|