diff options
author | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 2002-02-08 02:56:04 +0000 |
---|---|---|
committer | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 2002-02-08 02:56:04 +0000 |
commit | 128824233b3fdcc4ab0bb1632fbf45d491836e38 (patch) | |
tree | 3d2c36e91b9bc56d308070c1b3bb80da39f86bb8 | |
parent | 7aa1ccc59e984cd753bcb06c733088061a30f6a7 (diff) |
add object loading from command-line
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4363 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | toplevel/topdirs.ml | 25 | ||||
-rw-r--r-- | toplevel/topdirs.mli | 2 | ||||
-rw-r--r-- | toplevel/toploop.ml | 14 | ||||
-rw-r--r-- | toplevel/toploop.mli | 4 | ||||
-rw-r--r-- | toplevel/topmain.ml | 21 |
5 files changed, 47 insertions, 19 deletions
diff --git a/toplevel/topdirs.ml b/toplevel/topdirs.ml index fa028ac82..a6b25ba5c 100644 --- a/toplevel/topdirs.ml +++ b/toplevel/topdirs.ml @@ -93,17 +93,18 @@ let load_compunit ic filename ppf compunit = raise Load_failed end -let dir_load ppf name = +let load_file ppf name = try let filename = find_in_path !Config.load_path name in let ic = open_in_bin filename in let buffer = String.create (String.length Config.cmo_magic_number) in really_input ic buffer 0 (String.length Config.cmo_magic_number); - begin try + let success = try if buffer = Config.cmo_magic_number then begin let compunit_pos = input_binary_int ic in (* Go to descriptor *) seek_in ic compunit_pos; - load_compunit ic filename ppf (input_value ic : compilation_unit) + load_compunit ic filename ppf (input_value ic : compilation_unit); + true end else if buffer = Config.cma_magic_number then begin let toc_pos = input_binary_int ic in (* Go to table of contents *) @@ -115,12 +116,18 @@ let dir_load ppf name = fprintf ppf "Cannot load required shared library: %s.@." reason; raise Load_failed end; - List.iter (load_compunit ic filename ppf) lib.lib_units - end else fprintf ppf "File %s is not a bytecode object file.@." name - with Load_failed -> () - end; - close_in ic - with Not_found -> fprintf ppf "Cannot find file %s.@." name + List.iter (load_compunit ic filename ppf) lib.lib_units; + true + end else begin + fprintf ppf "File %s is not a bytecode object file.@." name; + false + end + with Load_failed -> false in + close_in ic; + success + with Not_found -> fprintf ppf "Cannot find file %s.@." name; false + +let dir_load ppf name = ignore (load_file ppf name) let _ = Hashtbl.add directive_table "load" (Directive_string (dir_load std_out)) diff --git a/toplevel/topdirs.mli b/toplevel/topdirs.mli index b75228f03..36af2211b 100644 --- a/toplevel/topdirs.mli +++ b/toplevel/topdirs.mli @@ -30,3 +30,5 @@ val dir_untrace_all : formatter -> unit -> unit type 'a printer_type_new = Format.formatter -> 'a -> unit type 'a printer_type_old = 'a -> unit +(* For topmain.ml. Maybe shouldn't be there *) +val load_file : formatter -> string -> bool diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml index a3698137f..5fc8bb1bb 100644 --- a/toplevel/toploop.ml +++ b/toplevel/toploop.ml @@ -375,18 +375,20 @@ let _ = let load_ocamlinit ppf = if Sys.file_exists ".ocamlinit" then ignore(use_silently ppf ".ocamlinit") +let set_paths () = + (* Add whatever -I options have been specified on the command line, + but keep the directories that user code linked in with ocamlmktop + may have added to load_path. *) + load_path := !load_path @ [Filename.concat Config.standard_library "camlp4"]; + load_path := "" :: (List.rev !Clflags.include_dirs @ !load_path); + Dll.add_path !load_path + (* The interactive loop *) exception PPerror let loop ppf = fprintf ppf " Objective Caml version %s@.@." Config.version; - (* Add whatever -I options have been specified on the command line, - but keep the directories that user code linked in with ocamlmktop - may have added to load_path. *) - load_path := !load_path @ [Filename.concat Config.standard_library "camlp4"]; - load_path := "" :: (List.rev !Clflags.include_dirs @ !load_path); - Dll.add_path !load_path; toplevel_env := Compile.initial_env(); let lb = Lexing.from_function refill_lexbuf in Location.input_name := ""; diff --git a/toplevel/toploop.mli b/toplevel/toploop.mli index e14bbf64a..39b4784ee 100644 --- a/toplevel/toploop.mli +++ b/toplevel/toploop.mli @@ -20,6 +20,10 @@ open Format val getvalue : string -> Obj.t val setvalue : string -> Obj.t -> unit +(* Set the load paths, before running anything *) + +val set_paths : unit -> unit + (* The interactive toplevel loop *) val loop : formatter -> unit diff --git a/toplevel/topmain.ml b/toplevel/topmain.ml index 2044626a0..1f815da69 100644 --- a/toplevel/topmain.ml +++ b/toplevel/topmain.ml @@ -16,11 +16,23 @@ open Clflags let usage = "Usage: ocaml <options> [script-file]\noptions are:" -let file_argument name = - exit (if Toploop.run_script Format.err_formatter name Sys.argv then 0 else 2) +let preload_objects = ref [] + +let prepare ppf = + Toploop.set_paths (); + try List.for_all (Topdirs.load_file ppf) (List.rev !preload_objects) + with x -> + try Errors.report_error ppf x; false + with x -> + Format.fprintf ppf "Uncaught exception: %s\n" (Printexc.to_string x); + false -let object_argument name = - Topdirs.dir_load +let file_argument name = + let ppf = Format.err_formatter in + if Filename.check_suffix name ".cmo" || Filename.check_suffix name ".cma" + then preload_objects := name :: !preload_objects + else exit + (if prepare ppf && Toploop.run_script ppf name Sys.argv then 0 else 2) let main () = Arg.parse [ @@ -56,6 +68,7 @@ let main () = "-dlambda", Arg.Set dump_lambda, " (undocumented)"; "-dinstr", Arg.Set dump_instr, " (undocumented)"; ] file_argument usage; + if not (prepare Format.err_formatter) then exit 2; Toploop.loop Format.std_formatter let _ = Printexc.catch main () |