Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / camlp4 / Camlp4Bin.ml
blobc0edff4baeb0027e852ec3e9ec7206445ee578c1
1 (* camlp4r *)
2 (****************************************************************************)
3 (* *)
4 (* Objective Caml *)
5 (* *)
6 (* INRIA Rocquencourt *)
7 (* *)
8 (* Copyright 2006 Institut National de Recherche en Informatique et *)
9 (* en Automatique. All rights reserved. This file is distributed under *)
10 (* the terms of the GNU Library General Public License, with the special *)
11 (* exception on linking described in LICENSE at the top of the Objective *)
12 (* Caml source tree. *)
13 (* *)
14 (****************************************************************************)
16 (* Authors:
17 * - Daniel de Rauglaudre: initial version
18 * - Nicolas Pouillard: refactoring
21 (* $Id$ *)
23 open Camlp4;
24 open PreCast.Syntax;
25 open PreCast;
26 open Format;
27 module CleanAst = Camlp4.Struct.CleanAst.Make Ast;
28 module SSet = Set.Make String;
30 value pa_r = "Camlp4OCamlRevisedParser";
31 value pa_rr = "Camlp4OCamlReloadedParser";
32 value pa_o = "Camlp4OCamlParser";
33 value pa_rp = "Camlp4OCamlRevisedParserParser";
34 value pa_op = "Camlp4OCamlParserParser";
35 value pa_g = "Camlp4GrammarParser";
36 value pa_m = "Camlp4MacroParser";
37 value pa_qb = "Camlp4QuotationCommon";
38 value pa_q = "Camlp4QuotationExpander";
39 value pa_rq = "Camlp4OCamlRevisedQuotationExpander";
40 value pa_oq = "Camlp4OCamlOriginalQuotationExpander";
41 value pa_l = "Camlp4ListComprehension";
43 open Register;
45 value dyn_loader = ref (fun []);
46 value rcall_callback = ref (fun () -> ());
47 value loaded_modules = ref SSet.empty;
48 value add_to_loaded_modules name =
49 loaded_modules.val := SSet.add name loaded_modules.val;
51 value rewrite_and_load n x =
52 let dyn_loader = dyn_loader.val () in
53 let find_in_path = DynLoader.find_in_path dyn_loader in
54 let real_load name = do {
55 add_to_loaded_modules name;
56 DynLoader.load dyn_loader name
57 } in
58 let load = List.iter begin fun n ->
59 if SSet.mem n loaded_modules.val || List.mem n Register.loaded_modules.val then ()
60 else begin
61 add_to_loaded_modules n;
62 DynLoader.load dyn_loader (n ^ ".cmo");
63 end
64 end in
65 do {
66 match (n, String.lowercase x) with
67 [ ("Parsers"|"", "pa_r.cmo" | "r" | "ocamlr" | "ocamlrevised" | "camlp4ocamlrevisedparser.cmo") -> load [pa_r]
68 | ("Parsers"|"", "rr" | "reloaded" | "ocamlreloaded" | "camlp4ocamlreloadedparser.cmo") -> load [pa_rr]
69 | ("Parsers"|"", "pa_o.cmo" | "o" | "ocaml" | "camlp4ocamlparser.cmo") -> load [pa_r; pa_o]
70 | ("Parsers"|"", "pa_rp.cmo" | "rp" | "rparser" | "camlp4ocamlrevisedparserparser.cmo") -> load [pa_r; pa_o; pa_rp]
71 | ("Parsers"|"", "pa_op.cmo" | "op" | "parser" | "camlp4ocamlparserparser.cmo") -> load [pa_r; pa_o; pa_rp; pa_op]
72 | ("Parsers"|"", "pa_extend.cmo" | "pa_extend_m.cmo" | "g" | "grammar" | "camlp4grammarparser.cmo") -> load [pa_g]
73 | ("Parsers"|"", "pa_macro.cmo" | "m" | "macro" | "camlp4macroparser.cmo") -> load [pa_m]
74 | ("Parsers"|"", "q" | "camlp4quotationexpander.cmo") -> load [pa_qb; pa_q]
75 | ("Parsers"|"", "q_mlast.cmo" | "rq" | "camlp4ocamlrevisedquotationexpander.cmo") -> load [pa_qb; pa_rq]
76 | ("Parsers"|"", "oq" | "camlp4ocamloriginalquotationexpander.cmo") -> load [pa_r; pa_o; pa_qb; pa_oq]
77 | ("Parsers"|"", "rf") -> load [pa_r; pa_rp; pa_qb; pa_q; pa_g; pa_l; pa_m]
78 | ("Parsers"|"", "of") -> load [pa_r; pa_o; pa_rp; pa_op; pa_qb; pa_rq; pa_g; pa_l; pa_m]
79 | ("Parsers"|"", "comp" | "camlp4listcomprehension.cmo") -> load [pa_l]
80 | ("Filters"|"", "lift" | "camlp4astlifter.cmo") -> load ["Camlp4AstLifter"]
81 | ("Filters"|"", "exn" | "camlp4exceptiontracer.cmo") -> load ["Camlp4ExceptionTracer"]
82 | ("Filters"|"", "prof" | "camlp4profiler.cmo") -> load ["Camlp4Profiler"]
83 (* map is now an alias of fold since fold handles map too *)
84 | ("Filters"|"", "map" | "camlp4mapgenerator.cmo") -> load ["Camlp4FoldGenerator"]
85 | ("Filters"|"", "fold" | "camlp4foldgenerator.cmo") -> load ["Camlp4FoldGenerator"]
86 | ("Filters"|"", "meta" | "camlp4metagenerator.cmo") -> load ["Camlp4MetaGenerator"]
87 | ("Filters"|"", "trash" | "camlp4trashremover.cmo") -> load ["Camlp4TrashRemover"]
88 | ("Filters"|"", "striploc" | "camlp4locationstripper.cmo") -> load ["Camlp4LocationStripper"]
89 | ("Filters"|"", "tracer" | "camlp4tracer.cmo") -> load ["Camlp4Tracer"]
90 | ("Printers"|"", "pr_r.cmo" | "r" | "ocamlr" | "camlp4ocamlrevisedprinter.cmo") ->
91 Register.enable_ocamlr_printer ()
92 | ("Printers"|"", "pr_o.cmo" | "o" | "ocaml" | "camlp4ocamlprinter.cmo") ->
93 Register.enable_ocaml_printer ()
94 | ("Printers"|"", "pr_dump.cmo" | "p" | "dumpocaml" | "camlp4ocamlastdumper.cmo") ->
95 Register.enable_dump_ocaml_ast_printer ()
96 | ("Printers"|"", "d" | "dumpcamlp4" | "camlp4astdumper.cmo") ->
97 Register.enable_dump_camlp4_ast_printer ()
98 | ("Printers"|"", "a" | "auto" | "camlp4autoprinter.cmo") ->
99 load ["Camlp4AutoPrinter"]
100 | _ ->
101 let y = "Camlp4"^n^"/"^x^".cmo" in
102 real_load (try find_in_path y with [ Not_found -> x ]) ];
103 rcall_callback.val ();
106 value print_warning = eprintf "%a:\n%s@." Loc.print;
108 value rec parse_file dyn_loader name pa getdir =
109 let directive_handler = Some (fun ast ->
110 match getdir ast with
111 [ Some x ->
112 match x with
113 [ (_, "load", s) -> do { rewrite_and_load "" s; None }
114 | (_, "directory", s) -> do { DynLoader.include_dir dyn_loader s; None }
115 | (_, "use", s) -> Some (parse_file dyn_loader s pa getdir)
116 | (_, "default_quotation", s) -> do { Quotation.default.val := s; None }
117 | (loc, _, _) -> Loc.raise loc (Stream.Error "bad directive") ]
118 | None -> None ]) in
119 let loc = Loc.mk name
120 in do {
121 current_warning.val := print_warning;
122 let ic = if name = "-" then stdin else open_in_bin name;
123 let cs = Stream.of_channel ic;
124 let clear () = if name = "-" then () else close_in ic;
125 let phr =
126 try pa ?directive_handler loc cs
127 with x -> do { clear (); raise x };
128 clear ();
132 value output_file = ref None;
134 value process dyn_loader name pa pr clean fold_filters getdir =
135 let ast = parse_file dyn_loader name pa getdir in
136 let ast = fold_filters (fun t filter -> filter t) ast in
137 let ast = clean ast in
138 pr ?input_file:(Some name) ?output_file:output_file.val ast;
140 value gind =
142 [ <:sig_item@loc< # $n$ $str:s$ >> -> Some (loc, n, s)
143 | _ -> None ];
145 value gimd =
147 [ <:str_item@loc< # $n$ $str:s$ >> -> Some (loc, n, s)
148 | _ -> None ];
150 value process_intf dyn_loader name =
151 process dyn_loader name CurrentParser.parse_interf CurrentPrinter.print_interf
152 (new CleanAst.clean_ast)#sig_item
153 AstFilters.fold_interf_filters gind;
154 value process_impl dyn_loader name =
155 process dyn_loader name CurrentParser.parse_implem CurrentPrinter.print_implem
156 (new CleanAst.clean_ast)#str_item
157 AstFilters.fold_implem_filters gimd;
159 value just_print_the_version () =
160 do { printf "%s@." Camlp4_config.version; exit 0 };
162 value print_version () =
163 do { eprintf "Camlp4 version %s@." Camlp4_config.version; exit 0 };
165 value print_stdlib () =
166 do { printf "%s@." Camlp4_config.camlp4_standard_library; exit 0 };
168 value usage ini_sl ext_sl =
169 do {
170 eprintf "\
171 Usage: camlp4 [load-options] [--] [other-options]
172 Options:
173 <file>.ml Parse this implementation file
174 <file>.mli Parse this interface file
175 <file>.(cmo|cma) Load this module inside the Camlp4 core@.";
176 Options.print_usage_list ini_sl;
177 (* loop (ini_sl @ ext_sl) where rec loop =
179 [ [(y, _, _) :: _] when y = "-help" -> ()
180 | [_ :: sl] -> loop sl
181 | [] -> eprintf " -help Display this list of options.@." ]; *)
182 if ext_sl <> [] then do {
183 eprintf "Options added by loaded object files:@.";
184 Options.print_usage_list ext_sl;
186 else ();
189 value warn_noassert () =
190 do {
191 eprintf "\
192 camlp4 warning: option -noassert is obsolete
193 You should give the -noassert option to the ocaml compiler instead.@.";
196 type file_kind =
197 [ Intf of string
198 | Impl of string
199 | Str of string
200 | ModuleImpl of string
201 | IncludeDir of string ];
203 value search_stdlib = ref True;
204 value print_loaded_modules = ref False;
205 value (task, do_task) =
206 let t = ref None in
207 let task f x =
208 let () = Camlp4_config.current_input_file.val := x in
209 t.val := Some (if t.val = None then (fun _ -> f x)
210 else (fun usage -> usage ())) in
211 let do_task usage = match t.val with [ Some f -> f usage | None -> () ] in
212 (task, do_task);
213 value input_file x =
214 let dyn_loader = dyn_loader.val () in
215 do {
216 rcall_callback.val ();
217 match x with
218 [ Intf file_name -> task (process_intf dyn_loader) file_name
219 | Impl file_name -> task (process_impl dyn_loader) file_name
220 | Str s ->
221 begin
222 let (f, o) = Filename.open_temp_file "from_string" ".ml";
223 output_string o s;
224 close_out o;
225 task (process_impl dyn_loader) f;
226 at_exit (fun () -> Sys.remove f);
228 | ModuleImpl file_name -> rewrite_and_load "" file_name
229 | IncludeDir dir -> DynLoader.include_dir dyn_loader dir ];
230 rcall_callback.val ();
233 value initial_spec_list =
234 [("-I", Arg.String (fun x -> input_file (IncludeDir x)),
235 "<directory> Add directory in search patch for object files.");
236 ("-where", Arg.Unit print_stdlib,
237 "Print camlp4 library directory and exit.");
238 ("-nolib", Arg.Clear search_stdlib,
239 "No automatic search for object files in library directory.");
240 ("-intf", Arg.String (fun x -> input_file (Intf x)),
241 "<file> Parse <file> as an interface, whatever its extension.");
242 ("-impl", Arg.String (fun x -> input_file (Impl x)),
243 "<file> Parse <file> as an implementation, whatever its extension.");
244 ("-str", Arg.String (fun x -> input_file (Str x)),
245 "<string> Parse <string> as an implementation.");
246 ("-unsafe", Arg.Set Camlp4_config.unsafe,
247 "Generate unsafe accesses to array and strings.");
248 ("-noassert", Arg.Unit warn_noassert,
249 "Obsolete, do not use this option.");
250 ("-verbose", Arg.Set Camlp4_config.verbose,
251 "More verbose in parsing errors.");
252 ("-loc", Arg.Set_string Loc.name,
253 "<name> Name of the location variable (default: " ^ Loc.name.val ^ ").");
254 ("-QD", Arg.String (fun x -> Quotation.dump_file.val := Some x),
255 "<file> Dump quotation expander result in case of syntax error.");
256 ("-o", Arg.String (fun x -> output_file.val := Some x),
257 "<file> Output on <file> instead of standard output.");
258 ("-v", Arg.Unit print_version,
259 "Print Camlp4 version and exit.");
260 ("-version", Arg.Unit just_print_the_version,
261 "Print Camlp4 version number and exit.");
262 ("-no_quot", Arg.Clear Camlp4_config.quotations,
263 "Don't parse quotations, allowing to use, e.g. \"<:>\" as token.");
264 ("-loaded-modules", Arg.Set print_loaded_modules, "Print the list of loaded modules.");
265 ("-parser", Arg.String (rewrite_and_load "Parsers"),
266 "<name> Load the parser Camlp4Parsers/<name>.cmo");
267 ("-printer", Arg.String (rewrite_and_load "Printers"),
268 "<name> Load the printer Camlp4Printers/<name>.cmo");
269 ("-filter", Arg.String (rewrite_and_load "Filters"),
270 "<name> Load the filter Camlp4Filters/<name>.cmo");
271 ("-ignore", Arg.String ignore, "ignore the next argument");
272 ("--", Arg.Unit ignore, "Deprecated, does nothing")
275 Options.init initial_spec_list;
277 value anon_fun name =
278 input_file
279 (if Filename.check_suffix name ".mli" then Intf name
280 else if Filename.check_suffix name ".ml" then Impl name
281 else if Filename.check_suffix name ".cmo" then ModuleImpl name
282 else if Filename.check_suffix name ".cma" then ModuleImpl name
283 else raise (Arg.Bad ("don't know what to do with " ^ name)));
285 value main argv =
286 let usage () = do { usage initial_spec_list (Options.ext_spec_list ()); exit 0 } in
287 try do {
288 let dynloader = DynLoader.mk ~ocaml_stdlib:search_stdlib.val
289 ~camlp4_stdlib:search_stdlib.val ();
290 dyn_loader.val := fun () -> dynloader;
291 let call_callback () =
292 Register.iter_and_take_callbacks
293 (fun (name, module_callback) ->
294 let () = add_to_loaded_modules name in
295 module_callback ());
296 call_callback ();
297 rcall_callback.val := call_callback;
298 match Options.parse anon_fun argv with
299 [ [] -> ()
300 | ["-help"|"--help"|"-h"|"-?" :: _] -> usage ()
301 | [s :: _] ->
302 do { eprintf "%s: unknown or misused option\n" s;
303 eprintf "Use option -help for usage@.";
304 exit 2 } ];
305 do_task usage;
306 call_callback ();
307 if print_loaded_modules.val then do {
308 SSet.iter (eprintf "%s@.") loaded_modules.val;
309 } else ()
311 with
312 [ Arg.Bad s -> do { eprintf "Error: %s\n" s;
313 eprintf "Use option -help for usage@.";
314 exit 2 }
315 | Arg.Help _ -> usage ()
316 | exc -> do { eprintf "@[<v0>%a@]@." ErrorHandler.print exc; exit 2 } ];
318 main Sys.argv;