1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
2002-02-08 01:27:48 -08:00
|
|
|
(* Copyright 2002 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
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
1995-07-02 09:51:07 -07:00
|
|
|
(* The batch compiler *)
|
|
|
|
|
|
|
|
open Misc
|
|
|
|
open Config
|
2000-03-06 21:02:33 -08:00
|
|
|
open Format
|
2012-05-30 07:52:37 -07:00
|
|
|
open Typedtree
|
2013-06-05 09:34:40 -07:00
|
|
|
open Compenv
|
1995-07-02 09:51:07 -07:00
|
|
|
|
1996-04-25 09:06:43 -07:00
|
|
|
(* Compile a .mli file *)
|
|
|
|
|
2013-09-10 06:44:34 -07:00
|
|
|
(* Keep in sync with the copy in compile.ml *)
|
|
|
|
|
2014-08-07 02:46:34 -07:00
|
|
|
let tool_name = "ocamlopt"
|
|
|
|
|
2012-01-20 06:23:34 -08:00
|
|
|
let interface ppf sourcefile outputprefix =
|
2013-09-10 06:44:34 -07:00
|
|
|
Compmisc.init_path false;
|
2014-05-10 17:17:05 -07:00
|
|
|
let modulename = module_of_filename ppf sourcefile outputprefix in
|
2005-07-31 05:03:40 -07:00
|
|
|
Env.set_unit_name modulename;
|
2013-09-10 06:44:34 -07:00
|
|
|
let initial_env = Compmisc.initial_env () in
|
2014-08-07 02:46:34 -07:00
|
|
|
let ast = Pparse.parse_interface ~tool_name ppf sourcefile in
|
2013-09-10 06:48:43 -07:00
|
|
|
if !Clflags.dump_parsetree then fprintf ppf "%a@." Printast.interface ast;
|
|
|
|
if !Clflags.dump_source then fprintf ppf "%a@." Pprintast.signature ast;
|
2014-05-07 05:46:00 -07:00
|
|
|
let tsg = Typemod.type_interface initial_env ast in
|
2013-09-10 06:48:43 -07:00
|
|
|
if !Clflags.dump_typedtree then fprintf ppf "%a@." Printtyped.interface tsg;
|
|
|
|
let sg = tsg.sig_type in
|
|
|
|
if !Clflags.print_types then
|
|
|
|
Printtyp.wrap_printing_env initial_env (fun () ->
|
|
|
|
fprintf std_formatter "%a@."
|
|
|
|
Printtyp.signature (Typemod.simplify_signature sg));
|
|
|
|
ignore (Includemod.signatures initial_env sg sg);
|
|
|
|
Typecore.force_delayed_checks ();
|
|
|
|
Warnings.check_fatal ();
|
|
|
|
if not !Clflags.print_types then begin
|
|
|
|
let sg = Env.save_signature sg modulename (outputprefix ^ ".cmi") in
|
|
|
|
Typemod.save_signature modulename tsg outputprefix sourcefile
|
|
|
|
initial_env sg ;
|
|
|
|
end
|
1995-07-02 09:51:07 -07:00
|
|
|
|
|
|
|
(* Compile a .ml file *)
|
|
|
|
|
2012-01-20 06:23:34 -08:00
|
|
|
let print_if ppf flag printer arg =
|
|
|
|
if !flag then fprintf ppf "%a@." printer arg;
|
1995-07-02 09:51:07 -07:00
|
|
|
arg
|
|
|
|
|
1998-04-27 08:16:48 -07:00
|
|
|
let (++) x f = f x
|
|
|
|
let (+++) (x, y) f = (x, f y)
|
|
|
|
|
2012-01-20 06:23:34 -08:00
|
|
|
let implementation ppf sourcefile outputprefix =
|
2013-06-05 09:34:40 -07:00
|
|
|
Compmisc.init_path true;
|
2014-05-10 17:17:05 -07:00
|
|
|
let modulename = module_of_filename ppf sourcefile outputprefix in
|
2005-07-31 05:03:40 -07:00
|
|
|
Env.set_unit_name modulename;
|
2013-06-05 09:34:40 -07:00
|
|
|
let env = Compmisc.initial_env() in
|
2005-08-01 08:51:09 -07:00
|
|
|
Compilenv.reset ?packname:!Clflags.for_package modulename;
|
2008-10-08 06:09:39 -07:00
|
|
|
let cmxfile = outputprefix ^ ".cmx" in
|
|
|
|
let objfile = outputprefix ^ ext_obj in
|
2013-09-10 06:44:34 -07:00
|
|
|
let comp ast =
|
2015-07-17 07:31:05 -07:00
|
|
|
let (typedtree, coercion) =
|
2013-09-10 06:44:34 -07:00
|
|
|
ast
|
2012-01-20 06:23:34 -08:00
|
|
|
++ print_if ppf Clflags.dump_parsetree Printast.implementation
|
2012-10-17 09:09:38 -07:00
|
|
|
++ print_if ppf Clflags.dump_source Pprintast.structure
|
2012-12-18 09:19:53 -08:00
|
|
|
++ Typemod.type_implementation sourcefile outputprefix modulename env
|
2013-03-22 11:19:54 -07:00
|
|
|
++ print_if ppf Clflags.dump_typedtree
|
2015-07-17 07:31:05 -07:00
|
|
|
Printtyped.implementation_with_coercion
|
|
|
|
in
|
|
|
|
if not !Clflags.print_types then begin
|
|
|
|
(typedtree, coercion)
|
2003-06-23 06:22:09 -07:00
|
|
|
++ Translmod.transl_store_implementation modulename
|
2012-01-20 06:23:34 -08:00
|
|
|
+++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda
|
2003-06-23 06:22:09 -07:00
|
|
|
+++ Simplif.simplify_lambda
|
2012-01-20 06:23:34 -08:00
|
|
|
+++ print_if ppf Clflags.dump_lambda Printlambda.lambda
|
|
|
|
++ Asmgen.compile_implementation outputprefix ppf;
|
2008-10-08 06:09:39 -07:00
|
|
|
Compilenv.save_unit_info cmxfile;
|
2003-06-23 06:22:09 -07:00
|
|
|
end;
|
2002-02-08 02:14:31 -08:00
|
|
|
Warnings.check_fatal ();
|
2013-09-10 06:44:34 -07:00
|
|
|
Stypes.dump (Some (outputprefix ^ ".annot"))
|
|
|
|
in
|
2014-08-07 02:46:34 -07:00
|
|
|
try comp (Pparse.parse_implementation ~tool_name ppf sourcefile)
|
2002-02-08 02:14:31 -08:00
|
|
|
with x ->
|
2013-09-10 06:44:34 -07:00
|
|
|
Stypes.dump (Some (outputprefix ^ ".annot"));
|
2008-10-08 06:09:39 -07:00
|
|
|
remove_file objfile;
|
|
|
|
remove_file cmxfile;
|
2002-02-08 02:14:31 -08:00
|
|
|
raise x
|
1995-07-02 09:51:07 -07:00
|
|
|
|
|
|
|
let c_file name =
|
2014-12-21 04:18:10 -08:00
|
|
|
let output_name = !Clflags.output_name in
|
|
|
|
if Ccomp.compile_file ~output_name name <> 0 then exit 2
|