]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/utils/ccomp.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / utils / ccomp.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: ccomp.ml 9093 2008-10-16 15:57:00Z doligez $ *)
14
15 (* Compiling C files and building C libraries *)
16
17 let command cmdline =
18   if !Clflags.verbose then begin
19     prerr_string "+ ";
20     prerr_string cmdline;
21     prerr_newline()
22   end;
23   Sys.command cmdline
24
25 let run_command cmdline = ignore(command cmdline)
26
27 (* Build @responsefile to work around Windows limitations on 
28    command-line length *)
29 let build_diversion lst =
30   let (responsefile, oc) = Filename.open_temp_file "camlresp" "" in
31   List.iter (fun f -> Printf.fprintf oc "%s\n" f) lst;
32   close_out oc;
33   at_exit (fun () -> Misc.remove_file responsefile);
34   "@" ^ responsefile
35
36 let quote_files lst =
37   let lst = List.filter (fun f -> f <> "") lst in
38   let quoted = List.map Filename.quote lst in
39   let s = String.concat " " quoted in
40   if String.length s >= 4096 && Sys.os_type = "Win32"
41   then build_diversion quoted
42   else s
43
44 let quote_prefixed pr lst =
45   let lst = List.filter (fun f -> f <> "") lst in
46   let lst = List.map (fun f -> pr ^ f) lst in
47   quote_files lst
48
49 let quote_optfile = function
50   | None -> ""
51   | Some f -> Filename.quote f
52
53 let compile_file name =
54   command
55     (Printf.sprintf
56        "%s -c %s %s %s %s"
57        (match !Clflags.c_compiler with
58         | Some cc -> cc
59         | None ->
60             if !Clflags.native_code
61             then Config.native_c_compiler
62             else Config.bytecomp_c_compiler)
63        (String.concat " " (List.rev !Clflags.ccopts))
64        (quote_prefixed "-I" (List.rev !Clflags.include_dirs))
65        (Clflags.std_include_flag "-I")
66        (Filename.quote name))
67
68 let create_archive archive file_list =
69   Misc.remove_file archive;
70   let quoted_archive = Filename.quote archive in
71   match Config.ccomp_type with
72     "msvc" ->
73       command(Printf.sprintf "link /lib /nologo /out:%s %s"
74                              quoted_archive (quote_files file_list))
75   | _ ->
76       let r1 =
77         command(Printf.sprintf "ar rc %s %s"
78                 quoted_archive (quote_files file_list)) in
79       if r1 <> 0 || String.length Config.ranlib = 0
80       then r1
81       else command(Config.ranlib ^ " " ^ quoted_archive)
82
83 let expand_libname name =
84   if String.length name < 2 || String.sub name 0 2 <> "-l"
85   then name
86   else begin
87     let libname =
88       "lib" ^ String.sub name 2 (String.length name - 2) ^ Config.ext_lib in
89     try
90       Misc.find_in_path !Config.load_path libname
91     with Not_found ->
92       libname
93   end
94
95 type link_mode =
96   | Exe
97   | Dll
98   | MainDll
99   | Partial
100
101 let call_linker mode output_name files extra =
102   let files = quote_files files in
103   let cmd =
104     if mode = Partial then
105       Printf.sprintf "%s%s %s %s"
106         Config.native_pack_linker
107         (Filename.quote output_name)
108         files
109         extra
110     else
111       Printf.sprintf "%s -o %s %s %s %s %s %s %s"
112         (match !Clflags.c_compiler, mode with
113         | Some cc, _ -> cc
114         | None, Exe -> Config.mkexe
115         | None, Dll -> Config.mkdll
116         | None, MainDll -> Config.mkmaindll
117         | None, Partial -> assert false
118         )
119         (Filename.quote output_name)
120         (if !Clflags.gprofile then Config.cc_profile else "")
121         ""  (*(Clflags.std_include_flag "-I")*)
122         (quote_prefixed "-L" !Config.load_path)
123         files
124         extra
125         (String.concat " " (List.rev !Clflags.ccopts))
126   in
127   command cmd = 0