Skip to content

Commit 83d5562

Browse files
author
Hongbo Zhang
committed
revert come unnecessary changes in driver, add more info in {apply_status}
1 parent 67fb3a8 commit 83d5562

File tree

4 files changed

+9
-24
lines changed

4 files changed

+9
-24
lines changed

bytecomp/lambda.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -214,15 +214,15 @@ type meth_kind = Self | Public of public_info | Cached
214214
type shared_code = (int * int) list
215215

216216
type apply_status =
217-
| NA
218-
| Full
219-
217+
| App_na
218+
| App_ml_full
219+
| App_js_full
220220
type apply_info = {
221221
apply_loc : Location.t;
222222
apply_status : apply_status;
223223
}
224224
let default_apply_info ?(loc=Location.none) () =
225-
{apply_loc = loc; apply_status = NA}
225+
{apply_loc = loc; apply_status = App_na}
226226
type lambda =
227227
Lvar of Ident.t
228228
| Lconst of structured_constant

bytecomp/lambda.mli

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -223,8 +223,9 @@ type meth_kind = Self | Public of public_info | Cached
223223
type shared_code = (int * int) list (* stack size -> code label *)
224224

225225
type apply_status =
226-
| NA
227-
| Full
226+
| App_na
227+
| App_ml_full
228+
| App_js_full
228229

229230
type apply_info = {
230231
apply_loc : Location.t;

driver/compile.ml

Lines changed: 1 addition & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -55,24 +55,17 @@ let print_if ppf flag printer arg =
5555

5656
let (++) x f = f x
5757

58-
let serialize_raw_js =
59-
try ignore @@ Sys.getenv "OCAML_RAW_JS"; true with Not_found -> false
60-
61-
6258
let implementation ppf sourcefile outputprefix =
6359
Compmisc.init_path false;
6460
let modulename = module_of_filename ppf sourcefile outputprefix in
6561
Env.set_unit_name modulename;
6662
let env = Compmisc.initial_env() in
67-
let finalenv = ref Env.empty in
68-
let current_signature = ref [] in
6963
try
7064
let (typedtree, coercion) =
7165
Pparse.parse_implementation ~tool_name ppf sourcefile
7266
++ print_if ppf Clflags.dump_parsetree Printast.implementation
7367
++ print_if ppf Clflags.dump_source Pprintast.structure
74-
++ (fun x -> let (a,b,c,signature) = Typemod.type_implementation_more sourcefile outputprefix modulename env x in
75-
begin finalenv:=c; current_signature:= signature; a,b end)
68+
++ Typemod.type_implementation sourcefile outputprefix modulename env
7669
++ print_if ppf Clflags.dump_typedtree
7770
Printtyped.implementation_with_coercion
7871
in
@@ -84,15 +77,6 @@ let implementation ppf sourcefile outputprefix =
8477
(typedtree, coercion)
8578
++ Translmod.transl_implementation modulename
8679
++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda
87-
(* (Printlambda.env_lambda !finalenv) *)
88-
++ (fun lambda ->
89-
(if serialize_raw_js then
90-
!Printlambda.serialize_raw_js
91-
!finalenv !current_signature
92-
sourcefile lambda
93-
);
94-
lambda
95-
)
9680
++ Simplif.simplify_lambda
9781
++ print_if ppf Clflags.dump_lambda Printlambda.lambda
9882
++ Bytegen.compile_implementation modulename

driver/optcompile.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ let implementation ppf sourcefile outputprefix =
7070
ast
7171
++ print_if ppf Clflags.dump_parsetree Printast.implementation
7272
++ print_if ppf Clflags.dump_source Pprintast.structure
73-
++ ( fun x -> let (a,b,c,_) = Typemod.type_implementation_more sourcefile outputprefix modulename env x in (a,b))
73+
++ Typemod.type_implementation sourcefile outputprefix modulename env
7474
++ print_if ppf Clflags.dump_typedtree
7575
Printtyped.implementation_with_coercion
7676
in

0 commit comments

Comments
 (0)