]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/asmcomp/asmlibrarian.ml
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / asmcomp / asmlibrarian.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: asmlibrarian.ml 7079 2005-09-24 16:45:56Z xleroy $ *)
14
15 (* Build libraries of .cmx files *)
16
17 open Misc
18 open Config
19 open Compilenv
20
21 type error =
22     File_not_found of string
23   | Archiver_error of string
24
25 exception Error of error
26
27 let read_info name =
28   let filename =
29     try
30       find_in_path !load_path name
31     with Not_found ->
32       raise(Error(File_not_found name)) in
33   let (info, crc) = Compilenv.read_unit_info filename in
34   info.ui_force_link <- !Clflags.link_everything;
35   (* There is no need to keep the approximation in the .cmxa file,
36      since the compiler will go looking directly for .cmx files.
37      The linker, which is the only one that reads .cmxa files, does not
38      need the approximation. *)
39   info.ui_approx <- Clambda.Value_unknown;
40   (Filename.chop_suffix filename ".cmx" ^ ext_obj, (info, crc))
41
42 let create_archive file_list lib_name =
43   let archive_name = chop_extension_if_any lib_name ^ ext_lib in
44   let outchan = open_out_bin lib_name in
45   try
46     output_string outchan cmxa_magic_number;
47     let (objfile_list, descr_list) =
48       List.split (List.map read_info file_list) in
49     List.iter2
50       (fun file_name (unit, crc) ->
51         Asmlink.check_consistency file_name unit crc)
52       file_list descr_list;
53     let infos =
54       { lib_units = descr_list;
55         lib_ccobjs = !Clflags.ccobjs;
56         lib_ccopts = !Clflags.ccopts } in
57     output_value outchan infos;
58     if Ccomp.create_archive archive_name objfile_list <> 0
59     then raise(Error(Archiver_error archive_name));
60     close_out outchan
61   with x ->
62     close_out outchan;
63     remove_file lib_name;
64     remove_file archive_name;
65     raise x
66
67 open Format
68
69 let report_error ppf = function
70   | File_not_found name ->
71       fprintf ppf "Cannot find file %s" name
72   | Archiver_error name ->
73       fprintf ppf "Error while creating the library %s" name
74