#5741: make Pprintast available from the command-line (-dsource).

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13025 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2012-10-17 16:09:38 +00:00
parent 3ffcd66100
commit dfa500533a
16 changed files with 36 additions and 2 deletions

View File

@ -82,6 +82,7 @@ let interface ppf sourcefile outputprefix =
let ast =
Pparse.file ppf inputfile Parse.interface ast_intf_magic_number in
if !Clflags.dump_parsetree then fprintf ppf "%a@." Printast.interface ast;
if !Clflags.dump_source then fprintf ppf "%a@." Pprintast.signature ast;
let tsg = Typemod.transl_signature initial_env ast in
let sg = tsg.sig_type in
if !Clflags.print_types then
@ -121,6 +122,7 @@ let implementation ppf sourcefile outputprefix =
try ignore(
Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
++ print_if ppf Clflags.dump_parsetree Printast.implementation
++ print_if ppf Clflags.dump_source Pprintast.structure
++ Typemod.type_implementation sourcefile outputprefix modulename env);
Warnings.check_fatal ();
Pparse.remove_preprocessed inputfile;
@ -135,6 +137,7 @@ let implementation ppf sourcefile outputprefix =
try
Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
++ print_if ppf Clflags.dump_parsetree Printast.implementation
++ print_if ppf Clflags.dump_source Pprintast.structure
++ Typemod.type_implementation sourcefile outputprefix modulename env
++ Translmod.transl_implementation modulename
++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda

View File

@ -138,6 +138,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _where = print_standard_library
let _verbose = set verbose
let _nopervasives = set nopervasives
let _dsource = set dump_source
let _dparsetree = set dump_parsetree
let _drawlambda = set dump_rawlambda
let _dlambda = set dump_lambda

View File

@ -330,6 +330,10 @@ let mk_drawlambda f =
"-drawlambda", Arg.Unit f, " (undocumented)"
;;
let mk_dsource f =
"-dsource", Arg.Unit f, " (undocumented)"
;;
let mk_dlambda f =
"-dlambda", Arg.Unit f, " (undocumented)"
;;
@ -450,6 +454,7 @@ module type Bytecomp_options = sig
val _nopervasives : unit -> unit
val _use_prims : string -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -480,6 +485,7 @@ module type Bytetop_options = sig
val _warn_error : string -> unit
val _warn_help : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -539,6 +545,7 @@ module type Optcomp_options = sig
val _where : unit -> unit
val _nopervasives : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -585,6 +592,7 @@ module type Opttop_options = sig
val _warn_error : string -> unit
val _warn_help : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -669,6 +677,7 @@ struct
mk_nopervasives F._nopervasives;
mk_use_prims F._use_prims;
mk_dsource F._dsource;
mk_dparsetree F._dparsetree;
mk_drawlambda F._drawlambda;
mk_dlambda F._dlambda;
@ -702,6 +711,7 @@ struct
mk_warn_error F._warn_error;
mk_warn_help F._warn_help;
mk_dsource F._dsource;
mk_dparsetree F._dparsetree;
mk_drawlambda F._drawlambda;
mk_dlambda F._dlambda;
@ -765,6 +775,7 @@ struct
mk_where F._where;
mk_nopervasives F._nopervasives;
mk_dsource F._dsource;
mk_dparsetree F._dparsetree;
mk_drawlambda F._drawlambda;
mk_dlambda F._dlambda;
@ -813,6 +824,7 @@ module Make_opttop_options (F : Opttop_options) = struct
mk_warn_error F._warn_error;
mk_warn_help F._warn_help;
mk_dsource F._dsource;
mk_dparsetree F._dparsetree;
mk_drawlambda F._drawlambda;
mk_dclambda F._dclambda;

View File

@ -62,6 +62,7 @@ module type Bytecomp_options =
val _nopervasives : unit -> unit
val _use_prims : string -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -93,6 +94,7 @@ module type Bytetop_options = sig
val _warn_error : string -> unit
val _warn_help : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -152,6 +154,7 @@ module type Optcomp_options = sig
val _where : unit -> unit
val _nopervasives : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit
@ -198,6 +201,7 @@ module type Opttop_options = sig
val _warn_error : string -> unit
val _warn_help : unit -> unit
val _dsource : unit -> unit
val _dparsetree : unit -> unit
val _drawlambda : unit -> unit
val _dlambda : unit -> unit

View File

@ -79,6 +79,7 @@ let interface ppf sourcefile outputprefix =
let ast =
Pparse.file ppf inputfile Parse.interface ast_intf_magic_number in
if !Clflags.dump_parsetree then fprintf ppf "%a@." Printast.interface ast;
if !Clflags.dump_source then fprintf ppf "%a@." Pprintast.signature ast;
let tsg = Typemod.transl_signature initial_env ast in
let sg = tsg.sig_type in
if !Clflags.print_types then
@ -123,10 +124,12 @@ let implementation ppf sourcefile outputprefix =
if !Clflags.print_types then ignore(
Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
++ print_if ppf Clflags.dump_parsetree Printast.implementation
++ print_if ppf Clflags.dump_source Pprintast.structure
++ Typemod.type_implementation sourcefile outputprefix modulename env)
else begin
Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
++ print_if ppf Clflags.dump_parsetree Printast.implementation
++ print_if ppf Clflags.dump_source Pprintast.structure
++ Typemod.type_implementation sourcefile outputprefix modulename env
++ Translmod.transl_store_implementation modulename
+++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda

View File

@ -149,6 +149,7 @@ module Options = Main_args.Make_optcomp_options (struct
let _where () = print_standard_library ()
let _nopervasives = set nopervasives
let _dsource = set dump_source
let _dparsetree = set dump_parsetree
let _drawlambda = set dump_rawlambda
let _dlambda = set dump_lambda

View File

@ -2198,7 +2198,7 @@ let string_of_expression x =
expression ppf x ;
flush_str_formatter () ;;
let toplevel_phrase ppf x =
let top_phrase ppf x =
pp_print_newline ppf () ;
toplevel_phrase ppf x;
fprintf ppf ";;" ;

View File

@ -15,4 +15,4 @@ val signature: Format.formatter -> Parsetree.signature -> unit
val expression: Format.formatter -> Parsetree.expression -> unit
val pattern: Format.formatter -> Parsetree.pattern -> unit
val core_type: Format.formatter -> Parsetree.core_type -> unit
val top_phrase: Format.formatter -> Parsetree.toplevel_phrase -> unit

View File

@ -90,6 +90,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _warn_help = option "-warn-help"
let _where = option "-where"
let _nopervasives = option "-nopervasives"
let _dsource = option "-dsource"
let _dparsetree = option "-dparsetree"
let _drawlambda = option "-drawlambda"
let _dlambda = option "-dlambda"

View File

@ -93,6 +93,7 @@ module Options = Main_args.Make_optcomp_options (struct
let _where = option "-where"
let _nopervasives = option "-nopervasives"
let _dsource = option "-dsource"
let _dparsetree = option "-dparsetree"
let _drawlambda = option "-drawlambda"
let _dlambda = option "-dlambda"

View File

@ -317,6 +317,7 @@ let use_file ppf name =
List.iter
(fun ph ->
if !Clflags.dump_parsetree then Printast.top_phrase ppf ph;
if !Clflags.dump_source then Pprintast.top_phrase ppf ph;
if not (execute_phrase !use_print_results ppf ph) then raise Exit)
(!parse_use_file lb);
true
@ -430,6 +431,7 @@ let loop ppf =
first_line := true;
let phr = try !parse_toplevel_phrase lb with Exit -> raise PPerror in
if !Clflags.dump_parsetree then Printast.top_phrase ppf phr;
if !Clflags.dump_source then Pprintast.top_phrase ppf ph;
ignore(execute_phrase true ppf phr)
with
| End_of_file -> exit 0

View File

@ -86,6 +86,7 @@ module Options = Main_args.Make_opttop_options (struct
let _warn_error s = Warnings.parse_options true s
let _warn_help = Warnings.help_warnings
let _dsource = set dump_source
let _dparsetree = set dump_parsetree
let _drawlambda = set dump_rawlambda
let _dlambda = set dump_lambda

View File

@ -305,6 +305,7 @@ let use_file ppf name =
List.iter
(fun ph ->
if !Clflags.dump_parsetree then Printast.top_phrase ppf ph;
if !Clflags.dump_source then Pprintast.top_phrase ppf ph;
if not (execute_phrase !use_print_results ppf ph) then raise Exit)
(!parse_use_file lb);
true
@ -420,6 +421,7 @@ let loop ppf =
first_line := true;
let phr = try !parse_toplevel_phrase lb with Exit -> raise PPerror in
if !Clflags.dump_parsetree then Printast.top_phrase ppf phr;
if !Clflags.dump_source then Pprintast.top_phrase ppf phr;
Env.reset_cache_toplevel ();
ignore(execute_phrase true ppf phr)
with

View File

@ -82,6 +82,7 @@ module Options = Main_args.Make_bytetop_options (struct
let _warn_error s = Warnings.parse_options true s
let _warn_help = Warnings.help_warnings
let _dparsetree = set dump_parsetree
let _dsource = set dump_source
let _drawlambda = set dump_rawlambda
let _dlambda = set dump_lambda
let _dinstr = set dump_instr

View File

@ -55,6 +55,7 @@ and dllpaths = ref ([] : string list) (* -dllpath *)
and make_package = ref false (* -pack *)
and for_package = ref (None: string option) (* -for-pack *)
and error_size = ref 500 (* -error-size *)
let dump_source = ref false (* -dsource *)
let dump_parsetree = ref false (* -dparsetree *)
and dump_rawlambda = ref false (* -drawlambda *)
and dump_lambda = ref false (* -dlambda *)

View File

@ -52,6 +52,7 @@ val dllpaths : string list ref
val make_package : bool ref
val for_package : string option ref
val error_size : int ref
val dump_source : bool ref
val dump_parsetree : bool ref
val dump_rawlambda : bool ref
val dump_lambda : bool ref