Skip to content

Commit

Permalink
Fix type variable naming in native toplevel
Browse files Browse the repository at this point in the history
This was written by @lpw25 . It makes the native toplevel preserve type variable
names in the same way as the bytecode toplevel.

This patch was originally submitted to flambda-backend

Signed-off-by: Nathan Rebours <nathan.p.rebours@gmail.com>
  • Loading branch information
NathanReb committed Nov 16, 2021
1 parent 93db249 commit 70af201
Show file tree
Hide file tree
Showing 4 changed files with 57 additions and 17 deletions.
2 changes: 0 additions & 2 deletions .depend
Original file line number Diff line number Diff line change
Expand Up @@ -6606,7 +6606,6 @@ toplevel/native/topeval.cmo : \
middle_end/compilenv.cmi \
utils/clflags.cmi \
parsing/asttypes.cmi \
parsing/ast_helper.cmi \
asmcomp/asmlink.cmi \
toplevel/native/topeval.cmi
toplevel/native/topeval.cmx : \
Expand Down Expand Up @@ -6638,7 +6637,6 @@ toplevel/native/topeval.cmx : \
middle_end/compilenv.cmx \
utils/clflags.cmx \
parsing/asttypes.cmi \
parsing/ast_helper.cmx \
asmcomp/asmlink.cmx \
toplevel/native/topeval.cmi
toplevel/native/topeval.cmi : \
Expand Down
2 changes: 2 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -414,6 +414,8 @@ OCaml 4.14.0
- #10735: Uncaught unify exception from `build_as_type`
(Jacques Garrigue, report and review by Leo White)

- #10712: Fix type variable naming in native toplevel
(Leo White)


OCaml 4.13 maintenance branch
Expand Down
2 changes: 2 additions & 0 deletions tools/.depend
Original file line number Diff line number Diff line change
Expand Up @@ -158,6 +158,8 @@ ocamlmklib.cmo : \
ocamlmklib.cmx : \
../utils/misc.cmx \
../utils/config.cmx
ocamlmklibconfig.cmo :
ocamlmklibconfig.cmx :
ocamlmktop.cmo : \
../utils/config.cmi \
../utils/ccomp.cmi
Expand Down
68 changes: 53 additions & 15 deletions toplevel/native/topeval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,44 @@ let pr_item =

let phrase_seqid = ref 0

let name_expression ~loc ~attrs exp =
let name = "_$" in
let id = Ident.create_local name in
let vd =
{ val_type = exp.exp_type;
val_kind = Val_reg;
val_loc = loc;
val_attributes = attrs;
val_uid = Uid.internal_not_actually_unique; }
in
let sg = [Sig_value(id, vd, Exported)] in
let pat =
{ pat_desc = Tpat_var(id, mknoloc name);
pat_loc = loc;
pat_extra = [];
pat_type = exp.exp_type;
pat_env = exp.exp_env;
pat_attributes = []; }
in
let vb =
{ vb_pat = pat;
vb_expr = exp;
vb_attributes = attrs;
vb_loc = loc; }
in
let item =
{ str_desc = Tstr_value(Nonrecursive, [vb]);
str_loc = loc;
str_env = exp.exp_env; }
in
let final_env = Env.add_value id vd exp.exp_env in
let str =
{ str_items = [item];
str_type = sg;
str_final_env = final_env }
in
str, sg

let execute_phrase print_outcome ppf phr =
match phr with
| Ptop_def sstr ->
Expand All @@ -123,21 +161,6 @@ let execute_phrase print_outcome ppf phr =
let phrase_name = "TOP" ^ string_of_int !phrase_seqid in
Compilenv.reset ?packname:None phrase_name;
Typecore.reset_delayed_checks ();
let sstr, rewritten =
match sstr with
| [ { pstr_desc = Pstr_eval (e, attrs) ; pstr_loc = loc } ]
| [ { pstr_desc = Pstr_value (Asttypes.Nonrecursive,
[{ pvb_expr = e
; pvb_pat = { ppat_desc = Ppat_any ; _ }
; pvb_attributes = attrs
; _ }])
; pstr_loc = loc }
] ->
let pat = Ast_helper.Pat.var (Location.mknoloc "_$") in
let vb = Ast_helper.Vb.mk ~loc ~attrs pat e in
[ Ast_helper.Str.value ~loc Asttypes.Nonrecursive [vb] ], true
| _ -> sstr, false
in
let (str, sg, names, shape, newenv) =
Typemod.type_toplevel_phrase oldenv sstr
in
Expand All @@ -146,6 +169,21 @@ let execute_phrase print_outcome ppf phr =
let sg' = Typemod.Signature_names.simplify newenv names sg in
ignore (Includemod.signatures oldenv ~mark:Mark_positive sg sg');
Typecore.force_delayed_checks ();
let str, sg', rewritten =
match str.str_items with
| [ { str_desc = Tstr_eval (e, attrs) ; str_loc = loc } ]
| [ { str_desc = Tstr_value (Asttypes.Nonrecursive,
[{ vb_expr = e
; vb_pat =
{ pat_desc = Tpat_any;
pat_extra = []; _ }
; vb_attributes = attrs }])
; str_loc = loc }
] ->
let str, sg' = name_expression ~loc ~attrs e in
str, sg', true
| _ -> str, sg', false
in
let module_ident, res, required_globals, size =
if Config.flambda then
let { Lambda.module_ident; main_module_block_size = size;
Expand Down

0 comments on commit 70af201

Please sign in to comment.