File: ocamlmklib.ml

package info (click to toggle)
ocaml 4.02.3-9
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 22,076 kB
  • ctags: 30,429
  • sloc: ml: 154,213; ansic: 38,324; sh: 5,236; makefile: 4,569; asm: 4,283; lisp: 4,224; awk: 88; perl: 87; fortran: 21; cs: 9; sed: 9
file content (310 lines) | stat: -rw-r--r-- 11,944 bytes parent folder | download
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
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
(***********************************************************************)
(*                                                                     *)
(*                                OCaml                                *)
(*                                                                     *)
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 2001 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.               *)
(*                                                                     *)
(***********************************************************************)

open Printf
open Ocamlmklibconfig

(* PR#4783: under Windows, don't use absolute paths because we do
   not know where the binary distribution will be installed. *)
let compiler_path name =
  if Sys.os_type = "Win32" then name else Filename.concat bindir name

let bytecode_objs = ref []  (* .cmo,.cma,.ml,.mli files to pass to ocamlc *)
and native_objs = ref []    (* .cmx,.cmxa,.ml,.mli files to pass to ocamlopt *)
and c_objs = ref []         (* .o, .a, .obj, .lib, .dll files to pass
                               to mksharedlib and ar *)
and caml_libs = ref []      (* -cclib to pass to ocamlc, ocamlopt *)
and caml_opts = ref []      (* -ccopt to pass to ocamlc, ocamlopt *)
and dynlink = ref supports_shared_libraries
and failsafe = ref false    (* whether to fall back on static build only *)
and c_libs = ref []         (* libs to pass to mksharedlib and ocamlc -cclib *)
and c_Lopts = ref []        (* options to pass to mksharedlib and ocamlc -cclib *)
and c_opts = ref []         (* options to pass to mksharedlib and ocamlc -ccopt *)
and ld_opts = ref []        (* options to pass only to the linker *)
and ocamlc = ref (compiler_path "ocamlc")
and ocamlc_opts = ref []    (* options to pass only to ocamlc *)
and ocamlopt = ref (compiler_path "ocamlopt")
and ocamlopt_opts = ref []  (* options to pass only to ocamlc *)
and output = ref "a"        (* Output name for OCaml part of library *)
and output_c = ref ""       (* Output name for C part of library *)
and rpath = ref []          (* rpath options *)
and debug = ref false       (* -g option *)
and verbose = ref false

(* Debian specific: inhibit rpath *)
let byteccrpath = ""
and nativeccrpath = ""
and mksharedlibrpath = ""

let starts_with s pref =
  String.length s >= String.length pref &&
  String.sub s 0 (String.length pref) = pref
let ends_with = Filename.check_suffix
let chop_prefix s pref =
  String.sub s (String.length pref) (String.length s - String.length pref)
let chop_suffix = Filename.chop_suffix

exception Bad_argument of string

let print_version () =
  printf "ocamlmklib, version %s\n" Sys.ocaml_version;
  exit 0;
;;

let print_version_num () =
  printf "%s\n" Sys.ocaml_version;
  exit 0;
;;

let parse_arguments argv =
  let i = ref 1 in
  let next_arg () =
    if !i + 1 >= Array.length argv
    then raise (Bad_argument("Option " ^ argv.(!i) ^ " expects one argument"));
    incr i; argv.(!i) in
  while !i < Array.length argv do
    let s = argv.(!i) in
    if ends_with s ".cmo" || ends_with s ".cma" then
      bytecode_objs := s :: !bytecode_objs
    else if ends_with s ".cmx" || ends_with s ".cmxa" then
      native_objs := s :: !native_objs
    else if ends_with s ".ml" || ends_with s ".mli" then
     (bytecode_objs := s :: !bytecode_objs;
      native_objs := s :: !native_objs)
    else if List.exists (ends_with s) [".o"; ".a"; ".obj"; ".lib"; ".dll"] then
      c_objs := s :: !c_objs
    else if s = "-cclib" then
      caml_libs := next_arg () :: "-cclib" :: !caml_libs
    else if s = "-ccopt" then
      caml_opts := next_arg () :: "-ccopt" :: !caml_opts
    else if s = "-custom" then
      dynlink := false
    else if s = "-I" then
      caml_opts := next_arg () :: "-I" :: !caml_opts
    else if s = "-failsafe" then
      failsafe := true
    else if s = "-g" then
      debug := true
    else if s = "-h" || s = "-help" || s = "--help" then
      raise (Bad_argument "")
    else if s = "-ldopt" then
      ld_opts := next_arg () :: !ld_opts
    else if s = "-linkall" then
      caml_opts := s :: !caml_opts
    else if starts_with s "-l" then
      c_libs := s :: !c_libs
    else if starts_with s "-L" then
     (c_Lopts := s :: !c_Lopts;
      let l = chop_prefix s "-L" in
      if not (Filename.is_relative l) then rpath := l :: !rpath)
    else if s = "-ocamlcflags" then
      ocamlc_opts := next_arg () :: !ocamlc_opts
    else if s = "-ocamlc" then
      ocamlc := next_arg ()
    else if s = "-ocamlopt" then
      ocamlopt := next_arg ()
    else if s = "-ocamloptflags" then
      ocamlopt_opts := next_arg () :: !ocamlopt_opts
    else if s = "-o" then
      output := next_arg()
    else if s = "-oc" then
      output_c := next_arg()
    else if s = "-dllpath" || s = "-R" || s = "-rpath" then
      rpath := next_arg() :: !rpath
    else if starts_with s "-R" then
      rpath := chop_prefix s "-R" :: !rpath
    else if s = "-Wl,-rpath" then
     (let a = next_arg() in
      if starts_with a "-Wl,"
      then rpath := chop_prefix a "-Wl," :: !rpath
      else raise (Bad_argument("Option -Wl,-rpath expects a -Wl, argument")))
    else if starts_with s "-Wl,-rpath," then
      rpath := chop_prefix s "-Wl,-rpath," :: !rpath
    else if starts_with s "-Wl,-R" then
      rpath := chop_prefix s "-Wl,-R" :: !rpath
    else if s = "-v" || s = "-verbose" then
      verbose := true
    else if s = "-version" then
      print_version ()
    else if s = "-vnum" then
      print_version_num ()
    else if starts_with s "-F" then
      c_opts := s :: !c_opts
    else if s = "-framework" then
      (let a = next_arg() in c_opts := a :: s :: !c_opts)
    else if starts_with s "-" then
      prerr_endline ("Unknown option " ^ s)
    else
      raise (Bad_argument("Don't know what to do with " ^ s));
    incr i
  done;
  List.iter
    (fun r -> r := List.rev !r)
    [ bytecode_objs; native_objs; caml_libs; caml_opts;
      c_libs; c_objs; c_opts; ld_opts; rpath ];
(* Put -L options in front of -l options in -cclib to mimic -ccopt behavior *)
  c_libs := !c_Lopts @ !c_libs;

  if !output_c = "" then output_c := !output

let usage = "\
Usage: ocamlmklib [options] <.cmo|.cma|.cmx|.cmxa|.ml|.mli|.o|.a|.obj|.lib|\
                             .dll files>\
\nOptions are:\
\n  -cclib <lib>   C library passed to ocamlc -a or ocamlopt -a only\
\n  -ccopt <opt>   C option passed to ocamlc -a or ocamlopt -a only\
\n  -custom        Disable dynamic loading\
\n  -g             Build with debug information\
\n  -dllpath <dir> Add <dir> to the run-time search path for DLLs\
\n  -F<dir>        Specify a framework directory (MacOSX)\
\n  -framework <name>    Use framework <name> (MacOSX)\
\n  -help          Print this help message and exit\
\n  --help         Same as -help\
\n  -h             Same as -help\
\n  -I <dir>       Add <dir> to the path searched for OCaml object files\
\n  -failsafe      fall back to static linking if DLL construction failed\
\n  -ldopt <opt>   C option passed to the shared linker only\
\n  -linkall       Build OCaml archive with link-all behavior\
\n  -l<lib>        Specify a dependent C library\
\n  -L<dir>        Add <dir> to the path searched for C libraries\
\n  -ocamlc <cmd>  Use <cmd> in place of \"ocamlc\"\
\n  -ocamlcflags <opt>    Pass <opt> to ocamlc\
\n  -ocamlopt <cmd> Use <cmd> in place of \"ocamlopt\"\
\n  -ocamloptflags <opt>  Pass <opt> to ocamlopt\
\n  -o <name>      Generated OCaml library is named <name>.cma or <name>.cmxa\
\n  -oc <name>     Generated C library is named dll<name>.so or lib<name>.a\
\n  -rpath <dir>   Same as -dllpath <dir>\
\n  -R<dir>        Same as -rpath\
\n  -verbose       Print commands before executing them\
\n  -v             same as -verbose\
\n  -version       Print version and exit\
\n  -vnum          Print version number and exit\
\n  -Wl,-rpath,<dir>     Same as -dllpath <dir>\
\n  -Wl,-rpath -Wl,<dir> Same as -dllpath <dir>\
\n  -Wl,-R<dir>          Same as -dllpath <dir>\
\n"

let command cmd =
  if !verbose then (print_string "+ "; print_string cmd; print_newline());
  Sys.command cmd

let scommand cmd =
  if command cmd <> 0 then exit 2

let safe_remove s =
  try Sys.remove s with Sys_error _ -> ()

let make_set l =
  let rec merge l = function
    []     -> List.rev l
  | p :: r -> if List.mem p l then merge l r else merge (p::l) r
  in
  merge [] l

let make_rpath flag =
  if !rpath = [] || flag = ""
  then ""
  else flag ^ String.concat ":" (make_set !rpath)

let make_rpath_ccopt flag =
  if !rpath = [] || flag = ""
  then ""
  else "-ccopt " ^ flag ^ String.concat ":" (make_set !rpath)

let prefix_list pref l =
  List.map (fun s -> pref ^ s) l

let prepostfix pre name post =
  let base = Filename.basename name in
  let dir = Filename.dirname name in
  Filename.concat dir (pre ^ base ^ post)
;;

let transl_path s =
  match Sys.os_type with
    | "Win32" ->
        let s = Bytes.of_string s in
        let rec aux i =
          if i = Bytes.length s || Bytes.get s i = ' ' then s
          else begin
            if Bytes.get s i = '/' then Bytes.set s i '\\';
            aux (i + 1)
          end
        in Bytes.to_string (aux 0)
    | _ -> s

let build_libs () =
  if !c_objs <> [] then begin
    if !dynlink then begin
      let retcode = command
          (Printf.sprintf "%s %s -o %s %s %s %s %s %s"
             mkdll
             (if !debug then "-g" else "")
             (prepostfix "dll" !output_c ext_dll)
             (String.concat " " !c_objs)
             (String.concat " " !c_opts)
             (String.concat " " !ld_opts)
             (make_rpath mksharedlibrpath)
             (String.concat " " !c_libs)
          )
      in
      if retcode <> 0 then if !failsafe then dynlink := false else exit 2
    end;
    safe_remove (prepostfix "lib" !output_c ext_lib);
    scommand
      (mklib (prepostfix "lib" !output_c ext_lib)
             (String.concat " " !c_objs) "");
  end;
  if !bytecode_objs <> [] then
    scommand
      (sprintf "%s -a %s %s %s -o %s.cma %s %s -dllib -l%s -cclib -l%s %s %s %s %s"
                  (transl_path !ocamlc)
                  (if !debug then "-g" else "")
                  (if !dynlink then "" else "-custom")
                  (String.concat " " !ocamlc_opts)
                  !output
                  (String.concat " " !caml_opts)
                  (String.concat " " !bytecode_objs)
                  (Filename.basename !output_c)
                  (Filename.basename !output_c)
                  (String.concat " " (prefix_list "-ccopt " !c_opts))
                  (make_rpath_ccopt byteccrpath)
                  (String.concat " " (prefix_list "-cclib " !c_libs))
                  (String.concat " " !caml_libs));
  if !native_objs <> [] then
    scommand
      (sprintf "%s -a %s %s -o %s.cmxa %s %s -cclib -l%s %s %s %s %s"
                  (transl_path !ocamlopt)
                  (if !debug then "-g" else "")
                  (String.concat " " !ocamlopt_opts)
                  !output
                  (String.concat " " !caml_opts)
                  (String.concat " " !native_objs)
                  (Filename.basename !output_c)
                  (String.concat " " (prefix_list "-ccopt " !c_opts))
                  (make_rpath_ccopt nativeccrpath)
                  (String.concat " " (prefix_list "-cclib " !c_libs))
                  (String.concat " " !caml_libs))

let _ =
  try
    parse_arguments Sys.argv;
    build_libs()
  with
  | Bad_argument "" ->
      prerr_string usage; exit 0
  | Bad_argument s ->
      prerr_endline s; prerr_string usage; exit 4
  | Sys_error s ->
      prerr_string "System error: "; prerr_endline s; exit 4
  | x ->
      raise x