]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/toplevel/opttopmain.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / toplevel / opttopmain.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: opttopmain.ml 8477 2007-11-06 15:16:56Z frisch $ *)
14
15 open Clflags
16
17 let usage = "Usage: ocamlnat <options> <object-files> [script-file]\noptions are:"
18
19 let preload_objects = ref []
20
21 let prepare ppf =
22   Opttoploop.set_paths ();
23   try
24     let res =
25       List.for_all (Opttopdirs.load_file ppf) (List.rev !preload_objects)
26     in
27     !Opttoploop.toplevel_startup_hook ();
28     res
29   with x ->
30     try Opterrors.report_error ppf x; false
31     with x ->
32       Format.fprintf ppf "Uncaught exception: %s\n" (Printexc.to_string x);
33       false
34
35 let file_argument name =
36   let ppf = Format.err_formatter in
37   if Filename.check_suffix name ".cmxs"
38     || Filename.check_suffix name ".cmx"
39     || Filename.check_suffix name ".cmxa"
40   then preload_objects := name :: !preload_objects
41   else
42     begin
43       let newargs = Array.sub Sys.argv !Arg.current
44                               (Array.length Sys.argv - !Arg.current)
45       in
46       if prepare ppf && Opttoploop.run_script ppf name newargs
47       then exit 0
48       else exit 2
49     end
50
51 let print_version () =
52   Printf.printf "The Objective Caml toplevel, version %s\n" Sys.ocaml_version;
53   exit 0;
54 ;;
55
56 let main () =
57   Arg.parse (Arch.command_line_options @ [
58      "-compact", Arg.Clear optimize_for_speed, " Optimize code size rather than speed";
59        "-inline", Arg.Int(fun n -> inline_threshold := n * 8),
60              "<n>  Set aggressiveness of inlining to <n>";
61      "-I", Arg.String(fun dir ->
62        let dir = Misc.expand_directory Config.standard_library dir in
63        include_dirs := dir :: !include_dirs),
64            "<dir>  Add <dir> to the list of include directories";
65      "-init", Arg.String (fun s -> init_file := Some s),
66            "<file>  Load <file> instead of default init file";
67      "-labels", Arg.Clear classic, " Labels commute (default)";
68      "-noassert", Arg.Set noassert, " Do not compile assertion checks";
69      "-nolabels", Arg.Set classic, " Ignore labels and do not commute";
70      "-noprompt", Arg.Set noprompt, " Suppress all prompts";
71      "-nostdlib", Arg.Set no_std_include,
72            " do not add default directory to the list of include directories";
73      "-principal", Arg.Set principal, " Check principality of type inference";
74      "-rectypes", Arg.Set recursive_types, " Allow arbitrary recursive types";
75      "-S", Arg.Set keep_asm_file, " Keep intermediate assembly file";
76      "-unsafe", Arg.Set fast, " No bound checking on array and string access";
77      "-version", Arg.Unit print_version, " Print version and exit";
78      "-w", Arg.String (Warnings.parse_options false),
79            "<flags>  Enable or disable warnings according to <flags>:\n\
80        \032    A/a enable/disable all warnings\n\
81        \032    C/c enable/disable suspicious comment\n\
82        \032    D/d enable/disable deprecated features\n\
83        \032    E/e enable/disable fragile match\n\
84        \032    F/f enable/disable partially applied function\n\
85        \032    L/l enable/disable labels omitted in application\n\
86        \032    M/m enable/disable overriden method\n\
87        \032    P/p enable/disable partial match\n\
88        \032    S/s enable/disable non-unit statement\n\
89        \032    U/u enable/disable unused match case\n\
90        \032    V/v enable/disable hidden instance variable\n\
91        \032    Y/y enable/disable suspicious unused variables\n\
92        \032    Z/z enable/disable all other unused variables\n\
93        \032    X/x enable/disable all other warnings\n\
94        \032    default setting is \"Aelz\"";
95      "-warn-error" , Arg.String (Warnings.parse_options true),
96        "<flags>  Treat the warnings of <flags> as errors, if they are enabled.\n\
97          \032    (see option -w for the list of flags)\n\
98          \032    default setting is a (all warnings are non-fatal)";
99
100        "-dparsetree", Arg.Set dump_parsetree, " (undocumented)";
101        "-drawlambda", Arg.Set dump_rawlambda, " (undocumented)";
102        "-dlambda", Arg.Set dump_lambda, " (undocumented)";
103        "-dcmm", Arg.Set dump_cmm, " (undocumented)";
104        "-dsel", Arg.Set dump_selection, " (undocumented)";
105        "-dcombine", Arg.Set dump_combine, " (undocumented)";
106        "-dlive", Arg.Unit(fun () -> dump_live := true;
107                                     Printmach.print_live := true),
108              " (undocumented)";
109        "-dspill", Arg.Set dump_spill, " (undocumented)";
110        "-dsplit", Arg.Set dump_split, " (undocumented)";
111        "-dinterf", Arg.Set dump_interf, " (undocumented)";
112        "-dprefer", Arg.Set dump_prefer, " (undocumented)";
113        "-dalloc", Arg.Set dump_regalloc, " (undocumented)";
114        "-dreload", Arg.Set dump_reload, " (undocumented)";
115        "-dscheduling", Arg.Set dump_scheduling, " (undocumented)";
116        "-dlinear", Arg.Set dump_linear, " (undocumented)";
117        "-dstartup", Arg.Set keep_startup_file, " (undocumented)";
118     ]) file_argument usage;
119   if not (prepare Format.err_formatter) then exit 2;
120   Opttoploop.loop Format.std_formatter
121