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