1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* The interactive toplevel loop *)
|
|
|
|
|
|
|
|
open Lexing
|
2000-03-06 14:12:09 -08:00
|
|
|
open Format
|
1996-04-18 09:35:43 -07:00
|
|
|
open Config
|
1995-05-04 03:15:53 -07:00
|
|
|
open Misc
|
|
|
|
open Parsetree
|
1996-09-23 04:32:19 -07:00
|
|
|
open Types
|
1995-05-04 03:15:53 -07:00
|
|
|
open Typedtree
|
|
|
|
open Printval
|
|
|
|
|
|
|
|
type directive_fun =
|
2000-03-06 14:12:09 -08:00
|
|
|
| Directive_none of (unit -> unit)
|
|
|
|
| Directive_string of (string -> unit)
|
|
|
|
| Directive_int of (int -> unit)
|
|
|
|
| Directive_ident of (Longident.t -> unit)
|
|
|
|
| Directive_bool of (bool -> unit)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2000-05-16 09:19:04 -07:00
|
|
|
(* The table of toplevel value bindings and its accessors *)
|
|
|
|
|
|
|
|
let toplevel_value_bindings =
|
|
|
|
(Hashtbl.create 37 : (string, Obj.t) Hashtbl.t)
|
|
|
|
|
|
|
|
let getvalue name =
|
|
|
|
try
|
|
|
|
Hashtbl.find toplevel_value_bindings name
|
|
|
|
with Not_found ->
|
|
|
|
fatal_error (name ^ " unbound at toplevel")
|
|
|
|
|
|
|
|
let setvalue name v =
|
2000-07-28 05:26:14 -07:00
|
|
|
Hashtbl.replace toplevel_value_bindings name v
|
2000-05-16 09:19:04 -07:00
|
|
|
|
1997-07-03 07:32:35 -07:00
|
|
|
(* Hooks for parsing functions *)
|
|
|
|
|
|
|
|
let parse_toplevel_phrase = ref Parse.toplevel_phrase
|
|
|
|
let parse_use_file = ref Parse.use_file
|
|
|
|
let print_location = Location.print
|
|
|
|
let print_warning = Location.print_warning
|
|
|
|
let input_name = Location.input_name
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Load in-core and execute a lambda term *)
|
|
|
|
|
|
|
|
type evaluation_outcome = Result of Obj.t | Exception of exn
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let load_lambda ppf lam =
|
|
|
|
if !Clflags.dump_rawlambda then fprintf ppf "%a@." Printlambda.lambda lam;
|
1995-12-15 02:21:43 -08:00
|
|
|
let slam = Simplif.simplify_lambda lam in
|
2000-03-06 14:12:09 -08:00
|
|
|
if !Clflags.dump_lambda then fprintf ppf "%a@." Printlambda.lambda slam;
|
1995-12-15 02:21:43 -08:00
|
|
|
let (init_code, fun_code) = Bytegen.compile_phrase slam in
|
2000-03-06 14:12:09 -08:00
|
|
|
if !Clflags.dump_instr then
|
|
|
|
fprintf ppf "%a%a@."
|
|
|
|
Printinstr.instrlist init_code
|
1995-05-04 03:15:53 -07:00
|
|
|
Printinstr.instrlist fun_code;
|
|
|
|
let (code, code_size, reloc) = Emitcode.to_memory init_code fun_code in
|
|
|
|
let can_free = (fun_code = []) in
|
|
|
|
let initial_symtable = Symtable.current_state() in
|
|
|
|
Symtable.patch_object code reloc;
|
|
|
|
Symtable.update_global_table();
|
|
|
|
try
|
1996-05-28 05:43:41 -07:00
|
|
|
let retval = (Meta.reify_bytecode code code_size) () in
|
1995-05-04 03:15:53 -07:00
|
|
|
if can_free then Meta.static_free code;
|
|
|
|
Result retval
|
|
|
|
with x ->
|
|
|
|
if can_free then Meta.static_free code;
|
|
|
|
Symtable.restore_state initial_symtable;
|
|
|
|
Exception x
|
|
|
|
|
|
|
|
(* Print the outcome of an evaluation *)
|
|
|
|
|
2000-03-09 08:52:57 -08:00
|
|
|
let pr_item env ppf = function
|
|
|
|
| Tsig_value(id, decl) :: rem ->
|
1996-04-22 04:15:41 -07:00
|
|
|
begin match decl.val_kind with
|
2000-03-09 08:52:57 -08:00
|
|
|
| Val_prim _ ->
|
|
|
|
fprintf ppf "@[<2>%a@]"
|
|
|
|
(Printtyp.value_description id) decl
|
1996-04-22 04:15:41 -07:00
|
|
|
| _ ->
|
2000-03-09 08:52:57 -08:00
|
|
|
fprintf ppf "@[<2>%a =@ %a@]"
|
|
|
|
(Printtyp.value_description id) decl
|
2000-06-12 07:22:37 -07:00
|
|
|
(print_value env (getvalue (Translmod.toplevel_name id)))
|
2000-03-06 14:12:09 -08:00
|
|
|
decl.val_type
|
1995-05-04 03:15:53 -07:00
|
|
|
end;
|
2000-03-09 08:52:57 -08:00
|
|
|
rem
|
|
|
|
| Tsig_type(id, decl) :: rem ->
|
|
|
|
fprintf ppf "@[%a@]"
|
|
|
|
(Printtyp.type_declaration id) decl;
|
|
|
|
rem
|
|
|
|
| Tsig_exception(id, decl) :: rem ->
|
|
|
|
fprintf ppf "@[%a@]"
|
|
|
|
(Printtyp.exception_declaration id) decl;
|
|
|
|
rem
|
|
|
|
| Tsig_module(id, mty) :: rem ->
|
|
|
|
fprintf ppf "@[<2>module %a :@ %a@]"
|
2000-03-06 14:12:09 -08:00
|
|
|
Printtyp.ident id
|
2000-03-09 08:52:57 -08:00
|
|
|
Printtyp.modtype mty;
|
|
|
|
rem
|
|
|
|
| Tsig_modtype(id, decl) :: rem ->
|
|
|
|
fprintf ppf "@[%a@]"
|
|
|
|
(Printtyp.modtype_declaration id) decl;
|
|
|
|
rem
|
|
|
|
| Tsig_class(id, decl) :: cltydecl :: tydecl1 :: tydecl2 :: rem ->
|
|
|
|
fprintf ppf "@[%a@]"
|
|
|
|
(Printtyp.class_declaration id) decl;
|
|
|
|
rem
|
|
|
|
| Tsig_cltype(id, decl) :: tydecl1 :: tydecl2 :: rem ->
|
|
|
|
fprintf ppf "@[%a@]"
|
|
|
|
(Printtyp.cltype_declaration id) decl;
|
|
|
|
rem
|
|
|
|
| _ -> []
|
|
|
|
|
2000-03-27 07:13:47 -08:00
|
|
|
let rec print_items env ppf = function
|
2000-03-09 08:52:57 -08:00
|
|
|
| [] -> ()
|
|
|
|
| items ->
|
2000-03-27 07:13:47 -08:00
|
|
|
match pr_item env ppf items with
|
|
|
|
| [] -> ()
|
|
|
|
| items -> fprintf ppf "@ %a" (print_items env) items;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2000-03-25 10:55:45 -08:00
|
|
|
(* The current typing environment for the toplevel *)
|
|
|
|
|
|
|
|
let toplevel_env = ref Env.empty
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Print an exception produced by an evaluation *)
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let print_exception_outcome ppf = function
|
|
|
|
| Sys.Break ->
|
|
|
|
fprintf ppf "Interrupted.@."
|
1995-05-04 03:15:53 -07:00
|
|
|
| Out_of_memory ->
|
|
|
|
Gc.full_major();
|
2000-03-06 14:12:09 -08:00
|
|
|
fprintf ppf "Out of memory during evaluation.@."
|
1997-07-03 07:32:35 -07:00
|
|
|
| Stack_overflow ->
|
2000-03-06 14:12:09 -08:00
|
|
|
fprintf ppf "Stack overflow during evaluation (looping recursion?).@."
|
1995-05-04 03:15:53 -07:00
|
|
|
| exn ->
|
2000-03-27 07:13:47 -08:00
|
|
|
fprintf ppf "@[Uncaught exception:@ %a.@]@."
|
2000-03-25 10:55:45 -08:00
|
|
|
(print_value !toplevel_env (Obj.repr exn)) Predef.type_exn
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* The table of toplevel directives.
|
|
|
|
Filled by functions from module topdirs. *)
|
|
|
|
|
1996-04-22 04:15:41 -07:00
|
|
|
let directive_table = (Hashtbl.create 13 : (string, directive_fun) Hashtbl.t)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Execute a toplevel phrase *)
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let execute_phrase print_outcome ppf phr =
|
1995-05-04 03:15:53 -07:00
|
|
|
match phr with
|
2000-03-06 14:12:09 -08:00
|
|
|
| Ptop_def sstr ->
|
1995-05-04 03:15:53 -07:00
|
|
|
let (str, sg, newenv) = Typemod.type_structure !toplevel_env sstr in
|
|
|
|
let lam = Translmod.transl_toplevel_definition str in
|
2000-03-06 14:12:09 -08:00
|
|
|
let res = load_lambda ppf lam in
|
1995-05-04 03:15:53 -07:00
|
|
|
begin match res with
|
2000-03-06 14:12:09 -08:00
|
|
|
| Result v ->
|
1997-07-03 07:32:35 -07:00
|
|
|
if print_outcome then begin
|
|
|
|
match str with
|
2000-03-06 14:12:09 -08:00
|
|
|
| [Tstr_eval exp] ->
|
|
|
|
fprintf ppf "@[- : %a@ =@ %a@]@."
|
|
|
|
Printtyp.type_scheme exp.exp_type
|
|
|
|
(print_value newenv v) exp.exp_type
|
2000-03-27 07:13:47 -08:00
|
|
|
| [] -> ()
|
1997-07-03 07:32:35 -07:00
|
|
|
| _ ->
|
2000-03-07 11:33:06 -08:00
|
|
|
fprintf ppf "@[<v>%a@]@."
|
2000-03-06 14:12:09 -08:00
|
|
|
(print_items newenv) sg
|
1995-05-04 03:15:53 -07:00
|
|
|
end;
|
1995-09-02 11:55:37 -07:00
|
|
|
toplevel_env := newenv;
|
|
|
|
true
|
1995-05-04 03:15:53 -07:00
|
|
|
| Exception exn ->
|
2000-03-06 14:12:09 -08:00
|
|
|
print_exception_outcome ppf exn;
|
1995-09-02 11:55:37 -07:00
|
|
|
false
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
| Ptop_dir(dir_name, dir_arg) ->
|
|
|
|
try
|
|
|
|
match (Hashtbl.find directive_table dir_name, dir_arg) with
|
2000-03-06 14:12:09 -08:00
|
|
|
| (Directive_none f, Pdir_none) -> f (); true
|
1995-09-02 11:55:37 -07:00
|
|
|
| (Directive_string f, Pdir_string s) -> f s; true
|
|
|
|
| (Directive_int f, Pdir_int n) -> f n; true
|
|
|
|
| (Directive_ident f, Pdir_ident lid) -> f lid; true
|
1999-12-03 02:26:08 -08:00
|
|
|
| (Directive_bool f, Pdir_bool b) -> f b; true
|
1995-05-04 03:15:53 -07:00
|
|
|
| (_, _) ->
|
2000-03-06 14:12:09 -08:00
|
|
|
fprintf ppf "Wrong type of argument for directive `%s'.@." dir_name;
|
1995-09-02 11:55:37 -07:00
|
|
|
false
|
1995-05-04 03:15:53 -07:00
|
|
|
with Not_found ->
|
2000-03-06 14:12:09 -08:00
|
|
|
fprintf ppf "Unknown directive `%s'.@." dir_name;
|
1995-09-02 11:55:37 -07:00
|
|
|
false
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-07-03 07:32:35 -07:00
|
|
|
(* Temporary assignment to a reference *)
|
|
|
|
|
|
|
|
let protect r newval body =
|
|
|
|
let oldval = !r in
|
|
|
|
try
|
|
|
|
r := newval;
|
|
|
|
let res = body() in
|
|
|
|
r := oldval;
|
|
|
|
res
|
|
|
|
with x ->
|
|
|
|
r := oldval;
|
|
|
|
raise x
|
|
|
|
|
|
|
|
(* Read and execute commands from a file *)
|
|
|
|
|
|
|
|
let use_print_results = ref true
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let use_file ppf name =
|
1997-07-03 07:32:35 -07:00
|
|
|
try
|
|
|
|
let filename = find_in_path !Config.load_path name in
|
|
|
|
let ic = open_in_bin filename in
|
|
|
|
let lb = Lexing.from_channel ic in
|
|
|
|
(* Skip initial #! line if any *)
|
|
|
|
let buffer = String.create 2 in
|
|
|
|
if input ic buffer 0 2 = 2 && buffer = "#!"
|
1999-02-24 07:21:50 -08:00
|
|
|
then ignore(input_line ic)
|
1997-07-03 07:32:35 -07:00
|
|
|
else seek_in ic 0;
|
|
|
|
let success =
|
|
|
|
protect Location.input_name filename (fun () ->
|
|
|
|
try
|
|
|
|
List.iter
|
|
|
|
(fun ph ->
|
2000-03-06 14:12:09 -08:00
|
|
|
if !Clflags.dump_parsetree then Printast.top_phrase ppf ph;
|
|
|
|
if not (execute_phrase !use_print_results ppf ph) then raise Exit)
|
1997-07-03 07:32:35 -07:00
|
|
|
(!parse_use_file lb);
|
|
|
|
true
|
|
|
|
with
|
2000-03-06 14:12:09 -08:00
|
|
|
| Exit -> false
|
|
|
|
| Sys.Break -> fprintf ppf "Interrupted.@."; false
|
|
|
|
| x -> Errors.report_error ppf x; false) in
|
1997-07-03 07:32:35 -07:00
|
|
|
close_in ic;
|
|
|
|
success
|
2000-03-06 14:12:09 -08:00
|
|
|
with Not_found -> fprintf ppf "Cannot find file %s.@." name; false
|
1997-07-03 07:32:35 -07:00
|
|
|
|
2000-03-07 19:38:05 -08:00
|
|
|
let use_silently ppf name =
|
|
|
|
protect use_print_results false (fun () -> use_file ppf name)
|
1997-07-03 07:32:35 -07:00
|
|
|
|
|
|
|
(* Reading function for interactive use *)
|
1995-09-08 01:56:21 -07:00
|
|
|
|
1996-07-25 06:18:36 -07:00
|
|
|
let first_line = ref true
|
1997-04-16 06:19:29 -07:00
|
|
|
let got_eof = ref false;;
|
1996-07-25 06:18:36 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let refill_lexbuf buffer len =
|
1997-04-16 06:19:29 -07:00
|
|
|
if !got_eof then (got_eof := false; 0) else begin
|
|
|
|
output_string stdout (if !first_line then "# " else " "); flush stdout;
|
|
|
|
first_line := false;
|
|
|
|
let i = ref 0 in
|
|
|
|
try
|
1999-12-30 09:09:59 -08:00
|
|
|
while true do
|
|
|
|
if !i >= len then raise Exit;
|
|
|
|
let c = input_char stdin in
|
|
|
|
buffer.[!i] <- c;
|
|
|
|
incr i;
|
|
|
|
if c = '\n' then raise Exit;
|
|
|
|
done;
|
|
|
|
!i
|
|
|
|
with
|
|
|
|
| End_of_file ->
|
|
|
|
Location.echo_eof ();
|
2000-03-06 14:12:09 -08:00
|
|
|
if !i > 0 then (got_eof := true; !i) else 0
|
1999-12-30 09:09:59 -08:00
|
|
|
| Exit -> !i
|
1997-04-16 06:19:29 -07:00
|
|
|
end
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Discard everything already in a lexer buffer *)
|
|
|
|
|
|
|
|
let empty_lexbuf lb =
|
|
|
|
let l = String.length lb.lex_buffer in
|
|
|
|
lb.lex_abs_pos <- (-l);
|
|
|
|
lb.lex_curr_pos <- l
|
|
|
|
|
1995-12-15 02:21:43 -08:00
|
|
|
(* Toplevel initialization. Performed here instead of at the
|
1997-04-08 08:18:38 -07:00
|
|
|
beginning of loop() so that user code linked in with ocamlmktop
|
1995-12-15 02:21:43 -08:00
|
|
|
can call directives from Topdirs. *)
|
|
|
|
|
|
|
|
let _ =
|
1998-10-20 05:58:23 -07:00
|
|
|
Sys.interactive := true;
|
1995-12-15 02:21:43 -08:00
|
|
|
Symtable.init_toplevel();
|
1997-04-08 08:18:38 -07:00
|
|
|
Clflags.thread_safe := true;
|
1997-07-03 07:32:35 -07:00
|
|
|
Compile.init_path()
|
1995-12-15 02:21:43 -08:00
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let load_ocamlinit ppf =
|
|
|
|
if Sys.file_exists ".ocamlinit" then ignore(use_silently ppf ".ocamlinit")
|
1998-11-12 06:53:46 -08:00
|
|
|
|
1997-07-03 07:32:35 -07:00
|
|
|
(* The interactive loop *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-06-16 08:34:13 -07:00
|
|
|
exception PPerror
|
1996-05-22 05:43:11 -07:00
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let loop ppf =
|
|
|
|
fprintf ppf " Objective Caml version %s@.@." Config.version;
|
1996-04-18 09:35:43 -07:00
|
|
|
(* Add whatever -I options have been specified on the command line,
|
1996-07-25 06:18:36 -07:00
|
|
|
but keep the directories that user code linked in with ocamlmktop
|
1996-04-18 09:35:43 -07:00
|
|
|
may have added to load_path. *)
|
|
|
|
load_path := "" :: (List.rev !Clflags.include_dirs @ !load_path);
|
1996-02-05 08:21:46 -08:00
|
|
|
toplevel_env := Compile.initial_env();
|
1995-05-04 03:15:53 -07:00
|
|
|
let lb = Lexing.from_function refill_lexbuf in
|
|
|
|
Location.input_name := "";
|
|
|
|
Location.input_lexbuf := Some lb;
|
|
|
|
Sys.catch_break true;
|
2000-03-06 14:12:09 -08:00
|
|
|
load_ocamlinit ppf;
|
1995-05-04 03:15:53 -07:00
|
|
|
while true do
|
|
|
|
try
|
|
|
|
empty_lexbuf lb;
|
1996-05-30 07:53:51 -07:00
|
|
|
Location.reset();
|
1996-07-25 06:18:36 -07:00
|
|
|
first_line := true;
|
1997-06-16 08:34:13 -07:00
|
|
|
let phr = try !parse_toplevel_phrase lb with Exit -> raise PPerror in
|
2000-03-06 14:12:09 -08:00
|
|
|
if !Clflags.dump_parsetree then Printast.top_phrase ppf phr;
|
|
|
|
ignore(execute_phrase true ppf phr)
|
1995-05-04 03:15:53 -07:00
|
|
|
with
|
2000-03-06 14:12:09 -08:00
|
|
|
| End_of_file -> exit 0
|
|
|
|
| Sys.Break -> fprintf ppf "Interrupted.@."
|
1997-06-16 08:34:13 -07:00
|
|
|
| PPerror -> ()
|
2000-03-06 14:12:09 -08:00
|
|
|
| x -> Errors.report_error ppf x
|
1995-05-04 03:15:53 -07:00
|
|
|
done
|
1997-07-03 07:32:35 -07:00
|
|
|
|
|
|
|
(* Execute a script *)
|
|
|
|
|
2000-03-06 14:12:09 -08:00
|
|
|
let run_script ppf name args =
|
2000-02-06 19:29:29 -08:00
|
|
|
let rec find n =
|
|
|
|
if n >= Array.length args then invalid_arg "Toploop.run_script";
|
|
|
|
if args.(n) = name then n else find (n+1)
|
|
|
|
in
|
|
|
|
let pos = find 0 in
|
|
|
|
let len = Array.length args - pos in
|
|
|
|
if Array.length Sys.argv < len then invalid_arg "Toploop.run_script";
|
|
|
|
Array.blit args pos Sys.argv 0 len;
|
|
|
|
Obj.truncate (Obj.repr Sys.argv) len;
|
2000-05-21 17:59:13 -07:00
|
|
|
Arg.current := 0;
|
1997-07-03 07:32:35 -07:00
|
|
|
Compile.init_path();
|
|
|
|
toplevel_env := Compile.initial_env();
|
2000-03-06 14:12:09 -08:00
|
|
|
use_silently ppf name
|