forked from colinbenner/ocaml-llvm
-
Notifications
You must be signed in to change notification settings - Fork 16
/
Copy pathocamlcp.ml
133 lines (122 loc) · 4.89 KB
/
ocamlcp.ml
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
(***********************************************************************)
(* *)
(* Objective Caml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1998 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. *)
(* *)
(***********************************************************************)
(* $Id$ *)
open Printf
let compargs = ref ([] : string list)
let profargs = ref ([] : string list)
let toremove = ref ([] : string list)
let option opt () = compargs := opt :: !compargs
let option_with_arg opt arg =
compargs := (Filename.quote arg) :: opt :: !compargs
;;
let make_archive = ref false;;
let with_impl = ref false;;
let with_intf = ref false;;
let with_mli = ref false;;
let with_ml = ref false;;
let process_file filename =
if Filename.check_suffix filename ".ml" then with_ml := true;
if Filename.check_suffix filename ".mli" then with_mli := true;
compargs := (Filename.quote filename) :: !compargs
;;
let usage = "Usage: ocamlcp <options> <files>\noptions are:"
let incompatible o =
fprintf stderr "ocamlcp: profiling is incompatible with the %s option\n" o;
exit 2
module Options = Main_args.Make_options (struct
let _a () = make_archive := true; option "-a" ()
let _annot = option "-annot"
let _c = option "-c"
let _cc s = option_with_arg "-cc" s
let _cclib s = option_with_arg "-cclib" s
let _ccopt s = option_with_arg "-ccopt" s
let _config = option "-config"
let _custom = option "-custom"
let _dllib = option_with_arg "-dllib"
let _dllpath = option_with_arg "-dllpath"
let _dtypes = option "-dtypes"
let _g = option "-g"
let _i = option "-i"
let _I s = option_with_arg "-I" s
let _impl s = with_impl := true; option_with_arg "-impl" s
let _intf s = with_intf := true; option_with_arg "-intf" s
let _intf_suffix s = option_with_arg "-intf-suffix" s
let _labels = option "-labels"
let _linkall = option "-linkall"
let _make_runtime = option "-make-runtime"
let _noassert = option "-noassert"
let _nolabels = option "-nolabels"
let _noautolink = option "-noautolink"
let _nostdlib = option "-nostdlib"
let _o s = option_with_arg "-o" s
let _output_obj = option "-output-obj"
let _pack = option "-pack"
let _pp s = incompatible "-pp"
let _principal = option "-principal"
let _rectypes = option "-rectypes"
let _thread () = option "-thread" ()
let _vmthread () = option "-vmthread" ()
let _unsafe = option "-unsafe"
let _use_prims s = option_with_arg "-use-prims" s
let _use_runtime s = option_with_arg "-use-runtime" s
let _v = option "-v"
let _version = option "-version"
let _verbose = option "-verbose"
let _w = option_with_arg "-w"
let _warn_error = option_with_arg "-warn-error"
let _where = option "-where"
let _nopervasives = option "-nopervasives"
let _dparsetree = option "-dparsetree"
let _drawlambda = option "-drawlambda"
let _dlambda = option "-dlambda"
let _dinstr = option "-dinstr"
let anonymous = process_file
end);;
let add_profarg s =
profargs := (Filename.quote s) :: "-m" :: !profargs
;;
let optlist =
("-p", Arg.String add_profarg,
"[afilmt] Profile constructs specified by argument (default fm):\n\
\032 a Everything\n\
\032 f Function calls and method calls\n\
\032 i if ... then ... else\n\
\032 l while and for loops\n\
\032 m match ... with\n\
\032 t try ... with")
:: Options.list
in
Arg.parse optlist process_file usage;
if !with_impl && !with_intf then begin
fprintf stderr "ocamlcp cannot deal with both \"-impl\" and \"-intf\"\n";
fprintf stderr "please compile interfaces and implementations separately\n";
exit 2;
end else if !with_impl && !with_mli then begin
fprintf stderr "ocamlcp cannot deal with both \"-impl\" and .mli files\n";
fprintf stderr "please compile interfaces and implementations separately\n";
exit 2;
end else if !with_intf && !with_ml then begin
fprintf stderr "ocamlcp cannot deal with both \"-intf\" and .ml files\n";
fprintf stderr "please compile interfaces and implementations separately\n";
exit 2;
end;
if !with_impl then profargs := "-impl" :: !profargs;
if !with_intf then profargs := "-intf" :: !profargs;
let status =
Sys.command
(Printf.sprintf "ocamlc -pp \"ocamlprof -instrument %s\" %s %s"
(String.concat " " (List.rev !profargs))
(if !make_archive then "" else "profiling.cmo")
(String.concat " " (List.rev !compargs)))
in
exit status
;;