@@ -2458,12 +2458,9 @@ and type_structure ?(toplevel = false) funct_body anchor env sstr =
24582458 if toplevel then run ()
24592459 else Builtin_attributes. warning_scope [] run
24602460
2461- let type_toplevel_phrase env s =
2462- Env. reset_required_globals () ;
2463- let (str, sg, to_remove_from_sg, env) =
2464- type_structure ~toplevel: true false None env s in
2465- remove_mode_variables env sg;
2466- begin match str.str_items with
2461+ (* The toplevel will print some types not present in the signature *)
2462+ let remove_mode_variables_for_toplevel str =
2463+ match str.str_items with
24672464 | [{ str_desc =
24682465 ( Tstr_eval (exp, _)
24692466 | Tstr_value (Nonrecursive ,
@@ -2473,7 +2470,15 @@ let type_toplevel_phrase env s =
24732470 even though they do not appear in sg *)
24742471 Ctype. remove_mode_variables exp.exp_type
24752472 | _ -> ()
2476- end ;
2473+
2474+ let type_toplevel_phrase env s =
2475+ Env. reset_required_globals () ;
2476+ Typecore. reset_allocations () ;
2477+ let (str, sg, to_remove_from_sg, env) =
2478+ type_structure ~toplevel: true false None env s in
2479+ remove_mode_variables env sg;
2480+ remove_mode_variables_for_toplevel str;
2481+ Typecore. optimise_allocations () ;
24772482 (str, sg, to_remove_from_sg, env)
24782483
24792484let type_module_alias = type_module ~alias: true true false None
@@ -2649,6 +2654,7 @@ let type_implementation sourcefile outputprefix modulename initial_env ast =
26492654 Cmt_format. clear () ;
26502655 Misc. try_finally (fun () ->
26512656 Typecore. reset_delayed_checks () ;
2657+ Typecore. reset_allocations () ;
26522658 Env. reset_required_globals () ;
26532659 if ! Clflags. print_types then (* #7656 *)
26542660 Warnings. parse_options false " -32-34-37-38-60" ;
@@ -2657,6 +2663,7 @@ let type_implementation sourcefile outputprefix modulename initial_env ast =
26572663 let simple_sg = Signature_names. simplify finalenv names sg in
26582664 if ! Clflags. print_types then begin
26592665 Typecore. force_delayed_checks () ;
2666+ Typecore. optimise_allocations () ;
26602667 Printtyp. wrap_printing_env ~error: false initial_env
26612668 (fun () -> fprintf std_formatter " %a@."
26622669 (Printtyp. printed_signature sourcefile) simple_sg
@@ -2679,6 +2686,7 @@ let type_implementation sourcefile outputprefix modulename initial_env ast =
26792686 sourcefile sg intf_file dclsig
26802687 in
26812688 Typecore. force_delayed_checks () ;
2689+ Typecore. optimise_allocations () ;
26822690 (* It is important to run these checks after the inclusion test above,
26832691 so that value declarations which are not used internally but
26842692 exported are not reported as being unused. *)
@@ -2695,6 +2703,7 @@ let type_implementation sourcefile outputprefix modulename initial_env ast =
26952703 check_nongen_schemes finalenv simple_sg;
26962704 normalize_signature simple_sg;
26972705 Typecore. force_delayed_checks () ;
2706+ Typecore. optimise_allocations () ;
26982707 (* See comment above. Here the target signature contains all
26992708 the value being exported. We can still capture unused
27002709 declarations like "let x = true;; let x = 1;;", because in this
0 commit comments