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
|
|
|
(* Toplevel directives *)
|
|
|
|
|
1999-11-08 09:06:33 -08:00
|
|
|
open Formatmsg
|
1995-05-04 03:15:53 -07:00
|
|
|
open Misc
|
|
|
|
open Longident
|
|
|
|
open Path
|
1996-09-23 04:32:19 -07:00
|
|
|
open Types
|
1995-05-04 03:15:53 -07:00
|
|
|
open Emitcode
|
|
|
|
open Printval
|
1995-09-14 04:53:55 -07:00
|
|
|
open Trace
|
1995-05-04 03:15:53 -07:00
|
|
|
open Toploop
|
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
(* Return the value referred to by a path *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let rec eval_path = function
|
|
|
|
Pident id -> Symtable.get_global_value id
|
|
|
|
| Pdot(p, s, pos) -> Obj.field (eval_path p) pos
|
1995-08-24 06:24:43 -07:00
|
|
|
| Papply(p1, p2) -> fatal_error "Topdirs.eval_path"
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To quit *)
|
|
|
|
|
|
|
|
let dir_quit () = exit 0; ()
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "quit" (Directive_none dir_quit)
|
|
|
|
|
|
|
|
(* To add a directory to the load path *)
|
|
|
|
|
|
|
|
let dir_directory s =
|
|
|
|
Config.load_path := s :: !Config.load_path;
|
|
|
|
Env.reset_cache()
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "directory" (Directive_string dir_directory)
|
|
|
|
|
|
|
|
(* To change the current directory *)
|
|
|
|
|
|
|
|
let dir_cd s =
|
|
|
|
Sys.chdir s
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "cd" (Directive_string dir_cd)
|
|
|
|
|
|
|
|
(* Load in-core a .cmo file *)
|
|
|
|
|
1996-02-18 06:46:22 -08:00
|
|
|
exception Load_failed
|
|
|
|
|
|
|
|
let load_compunit ic filename compunit =
|
|
|
|
Bytelink.check_consistency filename compunit;
|
|
|
|
seek_in ic compunit.cu_pos;
|
1996-05-28 05:43:41 -07:00
|
|
|
let code_size = compunit.cu_codesize + 8 in
|
1996-02-18 06:46:22 -08:00
|
|
|
let code = Meta.static_alloc code_size in
|
|
|
|
unsafe_really_input ic code 0 compunit.cu_codesize;
|
1996-05-28 05:43:41 -07:00
|
|
|
String.unsafe_set code compunit.cu_codesize (Char.chr Opcodes.opRETURN);
|
1997-07-03 07:32:35 -07:00
|
|
|
String.unsafe_blit "\000\000\000\001\000\000\000" 0
|
|
|
|
code (compunit.cu_codesize + 1) 7;
|
1996-02-18 06:46:22 -08:00
|
|
|
let initial_symtable = Symtable.current_state() in
|
|
|
|
Symtable.patch_object code compunit.cu_reloc;
|
|
|
|
Symtable.update_global_table();
|
|
|
|
begin try
|
1999-02-24 07:21:50 -08:00
|
|
|
ignore((Meta.reify_bytecode code code_size) ())
|
1996-02-18 06:46:22 -08:00
|
|
|
with exn ->
|
|
|
|
Symtable.restore_state initial_symtable;
|
|
|
|
print_exception_outcome exn;
|
|
|
|
raise Load_failed
|
|
|
|
end
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let dir_load 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);
|
1996-02-18 06:46:22 -08:00
|
|
|
begin 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 (input_value ic : compilation_unit)
|
|
|
|
end else
|
|
|
|
if buffer = Config.cma_magic_number then begin
|
|
|
|
let toc_pos = input_binary_int ic in (* Go to table of contents *)
|
|
|
|
seek_in ic toc_pos;
|
|
|
|
List.iter (load_compunit ic filename)
|
|
|
|
(input_value ic : compilation_unit list)
|
|
|
|
end else begin
|
|
|
|
print_string "File "; print_string name;
|
|
|
|
print_string " is not a bytecode object file."; print_newline()
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
1996-02-18 06:46:22 -08:00
|
|
|
with Load_failed -> ()
|
1995-05-04 03:15:53 -07:00
|
|
|
end;
|
|
|
|
close_in ic
|
|
|
|
with Not_found ->
|
1996-02-18 06:46:22 -08:00
|
|
|
print_string "Cannot find file "; print_string name; print_newline()
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "load" (Directive_string dir_load)
|
|
|
|
|
|
|
|
(* Load commands from a file *)
|
|
|
|
|
1999-02-24 07:21:50 -08:00
|
|
|
let dir_use name = ignore(Toploop.use_file name)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "use" (Directive_string dir_use)
|
|
|
|
|
|
|
|
(* Install, remove a printer *)
|
|
|
|
|
|
|
|
let find_printer_type lid =
|
|
|
|
try
|
|
|
|
let (path, desc) = Env.lookup_value lid !toplevel_env in
|
1996-10-02 04:11:23 -07:00
|
|
|
Ctype.init_def(Ident.current_time());
|
1995-05-04 03:15:53 -07:00
|
|
|
Ctype.begin_def();
|
|
|
|
let ty_arg = Ctype.newvar() in
|
1996-10-01 06:23:13 -07:00
|
|
|
Ctype.unify !toplevel_env
|
1999-11-30 08:07:38 -08:00
|
|
|
(Ctype.newty (Tarrow("", ty_arg, Ctype.instance Predef.type_unit)))
|
1996-10-01 06:23:13 -07:00
|
|
|
(Ctype.instance desc.val_type);
|
1995-05-04 03:15:53 -07:00
|
|
|
Ctype.end_def();
|
|
|
|
Ctype.generalize ty_arg;
|
|
|
|
(ty_arg, path)
|
|
|
|
with
|
|
|
|
Not_found ->
|
1995-05-05 03:05:18 -07:00
|
|
|
print_string "Unbound value "; Printtyp.longident lid;
|
1995-05-04 03:15:53 -07:00
|
|
|
print_newline(); raise Exit
|
1996-05-20 09:43:29 -07:00
|
|
|
| Ctype.Unify _ ->
|
1995-05-04 03:15:53 -07:00
|
|
|
Printtyp.longident lid;
|
|
|
|
print_string " has the wrong type for a printing function";
|
|
|
|
print_newline(); raise Exit
|
|
|
|
|
|
|
|
let dir_install_printer lid =
|
|
|
|
try
|
|
|
|
let (ty_arg, path) = find_printer_type lid in
|
1997-03-22 12:16:52 -08:00
|
|
|
let v = (Obj.obj (eval_path path) : 'a -> unit) in
|
|
|
|
Printval.install_printer path ty_arg (fun repr -> v (Obj.obj repr))
|
1995-05-04 03:15:53 -07:00
|
|
|
with Exit ->
|
|
|
|
()
|
|
|
|
|
|
|
|
let dir_remove_printer lid =
|
|
|
|
try
|
|
|
|
let (ty_arg, path) = find_printer_type lid in
|
1997-03-22 12:16:52 -08:00
|
|
|
begin try
|
|
|
|
Printval.remove_printer path
|
|
|
|
with Not_found ->
|
|
|
|
print_string "No printer named "; Printtyp.longident lid;
|
|
|
|
print_newline()
|
|
|
|
end
|
1995-05-04 03:15:53 -07:00
|
|
|
with Exit ->
|
|
|
|
()
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "install_printer"
|
|
|
|
(Directive_ident dir_install_printer)
|
|
|
|
let _ = Hashtbl.add directive_table "remove_printer"
|
|
|
|
(Directive_ident dir_remove_printer)
|
|
|
|
|
|
|
|
(* The trace *)
|
|
|
|
|
1995-09-14 04:53:55 -07:00
|
|
|
external current_environment: unit -> Obj.t = "get_current_environment"
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1998-09-07 00:55:38 -07:00
|
|
|
let tracing_function_ptr =
|
|
|
|
get_code_pointer
|
|
|
|
(Obj.repr (fun arg -> Trace.print_trace (current_environment()) arg))
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
let dir_trace lid =
|
|
|
|
try
|
|
|
|
let (path, desc) = Env.lookup_value lid !toplevel_env in
|
1996-05-22 09:21:53 -07:00
|
|
|
(* Check if this is a primitive *)
|
|
|
|
match desc.val_kind with
|
|
|
|
Val_prim p ->
|
|
|
|
Printtyp.longident lid;
|
|
|
|
print_string " is an external function and cannot be traced.";
|
1996-04-29 06:24:01 -07:00
|
|
|
print_newline()
|
1996-05-22 09:21:53 -07:00
|
|
|
| _ ->
|
|
|
|
let clos = eval_path path in
|
|
|
|
(* Nothing to do if it's not a closure *)
|
1998-09-07 00:55:38 -07:00
|
|
|
if Obj.is_block clos &&
|
|
|
|
(Obj.tag clos = 250 || Obj.tag clos = 249) then begin
|
1996-05-22 09:21:53 -07:00
|
|
|
match is_traced clos with
|
|
|
|
Some opath ->
|
|
|
|
Printtyp.path path;
|
|
|
|
print_string " is already traced (under the name ";
|
|
|
|
Printtyp.path opath; print_string ")";
|
|
|
|
print_newline()
|
|
|
|
| None ->
|
|
|
|
(* Instrument the old closure *)
|
|
|
|
traced_functions :=
|
|
|
|
{ path = path;
|
|
|
|
closure = clos;
|
1998-09-07 00:55:38 -07:00
|
|
|
actual_code = get_code_pointer clos;
|
1996-05-22 09:21:53 -07:00
|
|
|
instrumented_fun =
|
1998-09-07 00:55:38 -07:00
|
|
|
instrument_closure !toplevel_env lid desc.val_type }
|
1996-05-22 09:21:53 -07:00
|
|
|
:: !traced_functions;
|
1998-09-07 00:55:38 -07:00
|
|
|
(* Redirect the code field of the closure to point
|
|
|
|
to the instrumentation function *)
|
|
|
|
set_code_pointer clos tracing_function_ptr;
|
1996-04-22 04:15:41 -07:00
|
|
|
Printtyp.longident lid; print_string " is now traced.";
|
|
|
|
print_newline()
|
1996-05-22 09:21:53 -07:00
|
|
|
end else begin
|
|
|
|
Printtyp.longident lid; print_string " is not a function.";
|
|
|
|
print_newline()
|
|
|
|
end
|
1995-05-04 03:15:53 -07:00
|
|
|
with Not_found ->
|
1995-05-05 03:05:18 -07:00
|
|
|
print_string "Unbound value "; Printtyp.longident lid;
|
1995-05-04 03:15:53 -07:00
|
|
|
print_newline()
|
|
|
|
|
|
|
|
let dir_untrace lid =
|
|
|
|
try
|
|
|
|
let (path, desc) = Env.lookup_value lid !toplevel_env in
|
|
|
|
let rec remove = function
|
|
|
|
[] ->
|
|
|
|
Printtyp.longident lid; print_string " was not traced.";
|
|
|
|
print_newline();
|
|
|
|
[]
|
1995-09-14 04:53:55 -07:00
|
|
|
| f :: rem ->
|
|
|
|
if Path.same f.path path then begin
|
1998-09-07 00:55:38 -07:00
|
|
|
set_code_pointer (eval_path path) f.actual_code;
|
1995-05-04 03:15:53 -07:00
|
|
|
Printtyp.longident lid; print_string " is no longer traced.";
|
|
|
|
print_newline();
|
|
|
|
rem
|
1995-09-14 04:53:55 -07:00
|
|
|
end else f :: remove rem in
|
|
|
|
traced_functions := remove !traced_functions
|
1995-05-04 03:15:53 -07:00
|
|
|
with Not_found ->
|
1995-05-05 03:05:18 -07:00
|
|
|
print_string "Unbound value "; Printtyp.longident lid;
|
1995-05-04 03:15:53 -07:00
|
|
|
print_newline()
|
|
|
|
|
|
|
|
let dir_untrace_all () =
|
|
|
|
List.iter
|
1995-09-14 04:53:55 -07:00
|
|
|
(fun f ->
|
1998-09-07 00:55:38 -07:00
|
|
|
set_code_pointer (eval_path f.path) f.actual_code;
|
|
|
|
Printtyp.path f.path; print_string " is no longer traced.";
|
|
|
|
print_newline())
|
1995-09-14 04:53:55 -07:00
|
|
|
!traced_functions;
|
|
|
|
traced_functions := []
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "trace" (Directive_ident dir_trace)
|
|
|
|
let _ = Hashtbl.add directive_table "untrace" (Directive_ident dir_untrace)
|
|
|
|
let _ = Hashtbl.add directive_table "untrace_all" (Directive_none dir_untrace_all)
|
|
|
|
|
|
|
|
(* Control the printing of values *)
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "print_depth"
|
|
|
|
(Directive_int(fun n -> max_printer_depth := n))
|
|
|
|
let _ = Hashtbl.add directive_table "print_length"
|
|
|
|
(Directive_int(fun n -> max_printer_steps := n))
|
1999-12-03 02:26:08 -08:00
|
|
|
|
|
|
|
(* Set various compiler flags *)
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "modern"
|
|
|
|
(Directive_bool(fun b -> Clflags.classic := not b))
|
|
|
|
|
|
|
|
let parse_warnings s =
|
|
|
|
try Warnings.parse_options s
|
|
|
|
with Arg.Bad err -> printf "%s." err
|
|
|
|
|
|
|
|
let _ = Hashtbl.add directive_table "warnings"
|
|
|
|
(Directive_string parse_warnings)
|