]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamlbuild/options.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamlbuild / options.ml
1 (***********************************************************************)
2 (*                             ocamlbuild                              *)
3 (*                                                                     *)
4 (*  Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
5 (*                                                                     *)
6 (*  Copyright 2007 Institut National de Recherche en Informatique et   *)
7 (*  en Automatique.  All rights reserved.  This file is distributed    *)
8 (*  under the terms of the Q Public License version 1.0.               *)
9 (*                                                                     *)
10 (***********************************************************************)
11
12
13 (* Original author: Nicolas Pouillard *)
14
15 let version = "ocamlbuild "^(Sys.ocaml_version);;
16
17 type command_spec = Command.spec
18
19 open My_std
20 open Arg
21 open Format
22 open Command
23
24 let entry = ref None
25 let build_dir = ref "_build"
26 let include_dirs = ref []
27 let exclude_dirs = ref []
28 let nothing_should_be_rebuilt = ref false
29 let sanitize = ref true
30 let sanitization_script = ref "sanitize.sh"
31 let hygiene = ref true
32 let ignore_auto = ref true
33 let plugin = ref true
34 let just_plugin = ref false
35 let native_plugin = ref true
36 let make_links = ref true
37 let nostdlib = ref false
38 let use_menhir = ref false
39 let catch_errors = ref true
40
41 let mk_virtual_solvers =
42   let dir = Ocamlbuild_where.bindir in
43   List.iter begin fun cmd ->
44     let opt = cmd ^ ".opt" in
45     let a_opt = A opt in
46     let a_cmd = A cmd in
47     let search_in_path = memo Command.search_in_path in
48     let solver () =
49       if sys_file_exists !dir then
50         let long = filename_concat !dir cmd in
51         let long_opt = long ^ ".opt" in
52         if sys_file_exists long_opt then A long_opt
53         else if sys_file_exists long then A long
54         else try let _ = search_in_path opt in a_opt
55         with Not_found -> a_cmd
56       else
57         try let _ = search_in_path opt in a_opt
58         with Not_found -> a_cmd
59     in Command.setup_virtual_command_solver (String.uppercase cmd) solver
60   end
61
62 let () =
63   mk_virtual_solvers
64     ["ocamlc"; "ocamlopt"; "ocamldep"; "ocamldoc";
65     "ocamlyacc"; "menhir"; "ocamllex"; "ocamlmklib"; "ocamlmktop"]
66 let ocamlc = ref (V"OCAMLC")
67 let ocamlopt = ref (V"OCAMLOPT")
68 let ocamldep = ref (V"OCAMLDEP")
69 let ocamldoc = ref (V"OCAMLDOC")
70 let ocamlyacc = ref N
71 let ocamllex = ref (V"OCAMLLEX")
72 let ocamlmklib = ref (V"OCAMLMKLIB")
73 let ocamlmktop = ref (V"OCAMLMKTOP")
74 let ocamlrun = ref N
75 let program_to_execute = ref false
76 let must_clean = ref false
77 let show_documentation = ref false
78 let recursive = ref false
79 let ext_lib = ref Ocamlbuild_Myocamlbuild_config.a
80 let ext_obj = ref Ocamlbuild_Myocamlbuild_config.o
81 let ext_dll = ref Ocamlbuild_Myocamlbuild_config.so
82 let exe = ref Ocamlbuild_Myocamlbuild_config.exe
83
84 let targets_internal = ref []
85 let ocaml_libs_internal = ref []
86 let ocaml_lflags_internal = ref []
87 let ocaml_cflags_internal = ref []
88 let ocaml_ppflags_internal = ref []
89 let ocaml_yaccflags_internal = ref []
90 let ocaml_lexflags_internal = ref []
91 let program_args_internal = ref []
92 let ignore_list_internal = ref []
93 let tags_internal = ref [["quiet"]]
94 let tag_lines_internal = ref []
95 let show_tags_internal = ref []
96 let log_file_internal = ref "_log"
97
98 let my_include_dirs = ref [[Filename.current_dir_name]]
99 let my_exclude_dirs = ref [[".svn"; "CVS"]]
100
101 let dummy = "*invalid-dummy-string*";; (* Dummy string for delimiting the latest argument *)
102
103 (* The JoCaml support will be in a plugin when the plugin system will support
104  * multiple/installed plugins *)
105 let use_jocaml () =
106   ocamlc := A "jocamlc";
107   ocamlopt := A "jocamlopt";
108   ocamldep := A "jocamldep";
109   ocamlyacc := A "jocamlyacc";
110   ocamllex := A "jocamllex";
111   ocamlmklib := A "jocamlmklib";
112   ocamlmktop := A "jocamlmktop";
113   ocamlrun := A "jocamlrun";
114 ;;
115
116 let add_to rxs x =
117   let xs = Lexers.comma_or_blank_sep_strings (Lexing.from_string x) in
118   rxs := xs :: !rxs
119 let add_to' rxs x =
120   if x <> dummy then
121     rxs := [x] :: !rxs
122   else
123     ()
124 let set_cmd rcmd = String (fun s -> rcmd := Sh s)
125 let set_build_dir s = make_links := false; build_dir := s
126 let spec =
127   Arg.align
128   [
129    "-version", Unit (fun () -> print_endline version; raise Exit_OK), " Display the version";
130    "-quiet", Unit (fun () -> Log.level := 0), " Make as quiet as possible";
131    "-verbose", Int (fun i -> Log.level := i + 2), "<level> Set the verbosity level";
132    "-documentation", Set show_documentation, " Show rules and flags";
133    "-log", Set_string log_file_internal, "<file> Set log file";
134    "-no-log", Unit (fun () -> log_file_internal := ""), " No log file";
135    "-clean", Set must_clean, " Remove build directory and other files, then exit"; 
136    "-r", Set recursive, " Traverse directories by default (true: traverse)"; 
137
138    "-I", String (add_to' my_include_dirs), "<path> Add to include directories";
139    "-Is", String (add_to my_include_dirs), "<path,...> (same as above, but accepts a (comma or blank)-separated list)";
140    "-X", String (add_to' my_exclude_dirs), "<path> Directory to ignore";
141    "-Xs", String (add_to my_exclude_dirs), "<path,...> (idem)";
142
143    "-lib", String (add_to' ocaml_libs_internal), "<flag> Link to this ocaml library";
144    "-libs", String (add_to ocaml_libs_internal), "<flag,...> (idem)";
145    "-lflag", String (add_to' ocaml_lflags_internal), "<flag> Add to ocamlc link flags";
146    "-lflags", String (add_to ocaml_lflags_internal), "<flag,...> (idem)";
147    "-cflag", String (add_to' ocaml_cflags_internal), "<flag> Add to ocamlc compile flags";
148    "-cflags", String (add_to ocaml_cflags_internal), "<flag,...> (idem)";
149    "-yaccflag", String (add_to' ocaml_yaccflags_internal), "<flag> Add to ocamlyacc flags";
150    "-yaccflags", String (add_to ocaml_yaccflags_internal), "<flag,...> (idem)";
151    "-lexflag", String (add_to' ocaml_lexflags_internal), "<flag> Add to ocamllex flags";
152    "-lexflags", String (add_to ocaml_lexflags_internal), "<flag,...> (idem)";
153    "-ppflag", String (add_to' ocaml_ppflags_internal), "<flag> Add to ocaml preprocessing flags";
154    "-pp", String (add_to ocaml_ppflags_internal), "<flag,...> (idem)";
155    "-tag", String (add_to' tags_internal), "<tag> Add to default tags";
156    "-tags", String (add_to tags_internal), "<tag,...> (idem)";
157    "-tag-line", String (add_to' tag_lines_internal), "<tag> Use this line of tags (as in _tags)";
158    "-show-tags", String (add_to' show_tags_internal), "<path> Show tags that applies on that pathname";
159
160    "-ignore", String (add_to ignore_list_internal), "<module,...> Don't try to build these modules";
161    "-no-links", Clear make_links, " Don't make links of produced final targets";
162    "-no-skip", Clear ignore_auto, " Don't skip modules that are requested by ocamldep but cannot be built";
163    "-no-hygiene", Clear hygiene, " Don't apply sanity-check rules";
164    "-no-plugin", Clear plugin, " Don't build myocamlbuild.ml";
165    "-no-stdlib", Set nostdlib, " Don't ignore stdlib modules";
166    "-dont-catch-errors", Clear catch_errors, " Don't catch and display exceptions (useful to display the call stack)";
167    "-just-plugin", Set just_plugin, " Just build myocamlbuild.ml";
168    "-byte-plugin", Clear native_plugin, " Don't use a native plugin but bytecode";
169    "-sanitization-script", Set_string sanitization_script, " Change the file name for the generated sanitization script";
170    "-no-sanitize", Clear sanitize, " Do not generate sanitization script";
171    "-nothing-should-be-rebuilt", Set nothing_should_be_rebuilt, " Fail if something needs to be rebuilt";
172    "-classic-display", Set Log.classic_display, " Display executed commands the old-fashioned way";
173    "-use-menhir", Set use_menhir, " Use menhir instead of ocamlyacc";
174    "-use-jocaml", Unit use_jocaml, " Use jocaml compilers instead of ocaml ones";
175
176    "-j", Set_int Command.jobs, "<N> Allow N jobs at once (0 for unlimited)";
177
178    "-build-dir", String set_build_dir, "<path> Set build directory (implies no-links)";
179    "-install-lib-dir", Set_string Ocamlbuild_where.libdir, "<path> Set the install library directory";
180    "-install-bin-dir", Set_string Ocamlbuild_where.bindir, "<path> Set the install binary directory";
181    "-where", Unit (fun () -> print_endline !Ocamlbuild_where.libdir; raise Exit_OK), " Display the install library directory";
182
183    "-ocamlc", set_cmd ocamlc, "<command> Set the OCaml bytecode compiler";
184    "-ocamlopt", set_cmd ocamlopt, "<command> Set the OCaml native compiler";
185    "-ocamldep", set_cmd ocamldep, "<command> Set the OCaml dependency tool";
186    "-ocamlyacc", set_cmd ocamlyacc, "<command> Set the ocamlyacc tool";
187    "-menhir", set_cmd ocamlyacc, "<command> Set the menhir tool (use it after -use-menhir)";
188    "-ocamllex", set_cmd ocamllex, "<command> Set the ocamllex tool";
189    (* Not set since we perhaps want to replace ocamlmklib *)
190    (* "-ocamlmklib", set_cmd ocamlmklib, "<command> Set the ocamlmklib tool"; *)
191    "-ocamlmktop", set_cmd ocamlmktop, "<command> Set the ocamlmktop tool";
192    "-ocamlrun", set_cmd ocamlrun, "<command> Set the ocamlrun tool";
193
194    "--", Rest (fun x -> program_to_execute := true; add_to' program_args_internal x),
195    " Stop argument processing, remaining arguments are given to the user program";
196   ]
197
198 let targets = ref []
199 let ocaml_libs = ref []
200 let ocaml_lflags = ref []
201 let ocaml_cflags = ref []
202 let ocaml_ppflags = ref []
203 let ocaml_yaccflags = ref []
204 let ocaml_lexflags = ref []
205 let program_args = ref []
206 let ignore_list = ref []
207 let tags = ref []
208 let tag_lines = ref []
209 let show_tags = ref []
210
211 let init () =
212   let anon_fun = add_to' targets_internal in
213   let usage_msg = sprintf "Usage %s [options] <target>" Sys.argv.(0) in
214   let argv' = Array.concat [Sys.argv; [|dummy|]] in
215   parse_argv argv' spec anon_fun usage_msg;
216   Shell.mkdir_p !build_dir;
217
218   let () =
219     let log = !log_file_internal in
220     if log = "" then Log.init None
221     else if not (Filename.is_implicit log) then
222       failwith
223         (sprintf "Bad log file name: the file name must be implicit (not %S)" log)
224     else
225       let log = filename_concat !build_dir log in
226       Shell.mkdir_p (Filename.dirname log);
227       Shell.rm_f log;
228       let log = if !Log.level > 0 then Some log else None in
229       Log.init log
230   in
231
232   let reorder x y = x := !x @ (List.concat (List.rev !y)) in
233   reorder targets targets_internal;
234   reorder ocaml_libs ocaml_libs_internal;
235   reorder ocaml_cflags ocaml_cflags_internal;
236   reorder ocaml_lflags ocaml_lflags_internal;
237   reorder ocaml_ppflags ocaml_ppflags_internal;
238   reorder ocaml_yaccflags ocaml_yaccflags_internal;
239   reorder ocaml_lexflags ocaml_lexflags_internal;
240   reorder program_args program_args_internal;
241   reorder tags tags_internal;
242   reorder tag_lines tag_lines_internal;
243   reorder ignore_list ignore_list_internal;
244   reorder show_tags show_tags_internal;
245
246   let check_dir dir =
247     if Filename.is_implicit dir then
248       sys_file_exists dir
249     else
250       failwith
251         (sprintf "Included or excluded directories must be implicit (not %S)" dir)
252   in
253   let dir_reorder my dir =
254     let d = !dir in
255     reorder dir my;
256     dir := List.filter check_dir (!dir @ d)
257   in
258   dir_reorder my_include_dirs include_dirs;
259   dir_reorder my_exclude_dirs exclude_dirs;
260
261   ignore_list := List.map String.capitalize !ignore_list
262 ;;