]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/toplevel/topmain.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / toplevel / topmain.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: topmain.ml 6758 2005-01-28 17:52:58Z doligez $ *)
14
15 open Clflags
16
17 let usage = "Usage: ocaml <options> <object-files> [script-file]\noptions are:"
18
19 let preload_objects = ref []
20
21 let prepare ppf =
22   Toploop.set_paths ();
23   try
24     let res = 
25       List.for_all (Topdirs.load_file ppf) (List.rev !preload_objects) in
26     !Toploop.toplevel_startup_hook ();
27     res
28   with x ->
29     try Errors.report_error ppf x; false
30     with x ->
31       Format.fprintf ppf "Uncaught exception: %s\n" (Printexc.to_string x);
32       false
33
34 let file_argument name =
35   let ppf = Format.err_formatter in
36   if Filename.check_suffix name ".cmo" || Filename.check_suffix name ".cma"
37   then preload_objects := name :: !preload_objects
38   else
39     begin
40       let newargs = Array.sub Sys.argv !Arg.current
41                               (Array.length Sys.argv - !Arg.current)
42       in
43       if prepare ppf && Toploop.run_script ppf name newargs
44       then exit 0
45       else exit 2
46     end
47
48 let print_version () =
49   Printf.printf "The Objective Caml toplevel, version %s\n" Sys.ocaml_version;
50   exit 0;
51 ;;
52
53 let main () =
54   Arg.parse [
55      "-I", Arg.String(fun dir ->
56        let dir = Misc.expand_directory Config.standard_library dir in
57        include_dirs := dir :: !include_dirs),
58            "<dir>  Add <dir> to the list of include directories";
59      "-init", Arg.String (fun s -> init_file := Some s),
60            "<file>  Load <file> instead of default init file";
61      "-labels", Arg.Clear classic, " Labels commute (default)";
62      "-noassert", Arg.Set noassert, " Do not compile assertion checks";
63      "-nolabels", Arg.Set classic, " Ignore labels and do not commute";
64      "-noprompt", Arg.Set noprompt, " Suppress all prompts";
65      "-nostdlib", Arg.Set no_std_include,
66            " do not add default directory to the list of include directories";
67      "-principal", Arg.Set principal, " Check principality of type inference";
68      "-rectypes", Arg.Set recursive_types, " Allow arbitrary recursive types";
69      "-unsafe", Arg.Set fast, " No bound checking on array and string access";
70      "-version", Arg.Unit print_version, " Print version and exit";
71      "-w", Arg.String (Warnings.parse_options false),
72            "<flags>  Enable or disable warnings according to <flags>:\n\
73        \032    A/a enable/disable all warnings\n\
74        \032    C/c enable/disable suspicious comment\n\
75        \032    D/d enable/disable deprecated features\n\
76        \032    E/e enable/disable fragile match\n\
77        \032    F/f enable/disable partially applied function\n\
78        \032    L/l enable/disable labels omitted in application\n\
79        \032    M/m enable/disable overriden method\n\
80        \032    P/p enable/disable partial match\n\
81        \032    S/s enable/disable non-unit statement\n\
82        \032    U/u enable/disable unused match case\n\
83        \032    V/v enable/disable hidden instance variable\n\
84        \032    Y/y enable/disable suspicious unused variables\n\
85        \032    Z/z enable/disable all other unused variables\n\
86        \032    X/x enable/disable all other warnings\n\
87        \032    default setting is \"Aelz\"";
88      "-warn-error" , Arg.String (Warnings.parse_options true),
89        "<flags>  Treat the warnings of <flags> as errors, if they are enabled.\n\
90          \032    (see option -w for the list of flags)\n\
91          \032    default setting is a (all warnings are non-fatal)";
92
93      "-dparsetree", Arg.Set dump_parsetree, " (undocumented)";
94      "-drawlambda", Arg.Set dump_rawlambda, " (undocumented)";
95      "-dlambda", Arg.Set dump_lambda, " (undocumented)";
96      "-dinstr", Arg.Set dump_instr, " (undocumented)";
97     ] file_argument usage;
98   if not (prepare Format.err_formatter) then exit 2;
99   Toploop.loop Format.std_formatter
100