Skip to content

Commit 14a7f73

Browse files
committed
Fix more display differences between ocamlnat/ocaml (PR#10849)
Unites the toplevels still further. Previously, the native toplevel did not display output for: let _ : <type> = <expr> and related cases. The `match` for wildcard bindings is now shared between bytecode and native, so the native toplevel should always display values when the bytecode would.
1 parent 6c5910a commit 14a7f73

File tree

8 files changed

+61
-32
lines changed

8 files changed

+61
-32
lines changed

.depend

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6270,6 +6270,7 @@ toplevel/genprintval.cmi : \
62706270
typing/outcometree.cmi \
62716271
typing/env.cmi
62726272
toplevel/topcommon.cmo : \
6273+
typing/typedtree.cmi \
62736274
parsing/printast.cmi \
62746275
typing/predef.cmi \
62756276
parsing/pprintast.cmi \
@@ -6292,9 +6293,11 @@ toplevel/topcommon.cmo : \
62926293
driver/compmisc.cmi \
62936294
driver/compenv.cmi \
62946295
utils/clflags.cmi \
6296+
parsing/asttypes.cmi \
62956297
parsing/ast_helper.cmi \
62966298
toplevel/topcommon.cmi
62976299
toplevel/topcommon.cmx : \
6300+
typing/typedtree.cmx \
62986301
parsing/printast.cmx \
62996302
typing/predef.cmx \
63006303
parsing/pprintast.cmx \
@@ -6317,11 +6320,13 @@ toplevel/topcommon.cmx : \
63176320
driver/compmisc.cmx \
63186321
driver/compenv.cmx \
63196322
utils/clflags.cmx \
6323+
parsing/asttypes.cmi \
63206324
parsing/ast_helper.cmx \
63216325
toplevel/topcommon.cmi
63226326
toplevel/topcommon.cmi : \
63236327
utils/warnings.cmi \
63246328
typing/types.cmi \
6329+
typing/typedtree.cmi \
63256330
typing/path.cmi \
63266331
parsing/parsetree.cmi \
63276332
typing/outcometree.cmi \
@@ -6468,7 +6473,6 @@ toplevel/byte/topeval.cmo : \
64686473
file_formats/cmo_format.cmi \
64696474
utils/clflags.cmi \
64706475
bytecomp/bytegen.cmi \
6471-
parsing/asttypes.cmi \
64726476
toplevel/byte/topeval.cmi
64736477
toplevel/byte/topeval.cmx : \
64746478
utils/warnings.cmx \
@@ -6504,7 +6508,6 @@ toplevel/byte/topeval.cmx : \
65046508
file_formats/cmo_format.cmi \
65056509
utils/clflags.cmx \
65066510
bytecomp/bytegen.cmx \
6507-
parsing/asttypes.cmi \
65086511
toplevel/byte/topeval.cmi
65096512
toplevel/byte/topeval.cmi : \
65106513
toplevel/topcommon.cmi \
@@ -6605,7 +6608,6 @@ toplevel/native/topeval.cmo : \
66056608
driver/compmisc.cmi \
66066609
middle_end/compilenv.cmi \
66076610
utils/clflags.cmi \
6608-
parsing/asttypes.cmi \
66096611
asmcomp/asmlink.cmi \
66106612
toplevel/native/topeval.cmi
66116613
toplevel/native/topeval.cmx : \
@@ -6636,7 +6638,6 @@ toplevel/native/topeval.cmx : \
66366638
driver/compmisc.cmx \
66376639
middle_end/compilenv.cmx \
66386640
utils/clflags.cmx \
6639-
parsing/asttypes.cmi \
66406641
asmcomp/asmlink.cmx \
66416642
toplevel/native/topeval.cmi
66426643
toplevel/native/topeval.cmi : \

Changes

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -427,6 +427,10 @@ OCaml 4.14.0
427427
- #10822, #10823: Bad interaction between ambivalent types and subtyping
428428
coercions (Jacques Garrigue, report and review by Frédéric Bour)
429429

430+
- #10849: Display the result of `let _ : <type> = <expr>` in the native
431+
toplevel, as in the bytecode toplevel.
432+
(David Allsopp, report by Nathan Rebours, review by Gabriel Scherer)
433+
430434

431435
OCaml 4.13 maintenance branch
432436
-----------------------------

testsuite/tests/tool-toplevel/pr10712.compilers.reference renamed to testsuite/tests/tool-toplevel/topeval.compilers.reference

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,4 +2,9 @@ module A :
22
sig type ('foo, 'bar) t val get_foo : ('foo, 'a) t -> 'foo option end
33
- : ('foo, 'a) A.t -> 'foo option = <fun>
44
val _bar : ('a, 'b) A.t -> 'a option = <fun>
5+
- : int = 42
6+
- : bool = false
7+
- : string = ""
8+
- : char = 'd'
9+
- : float = 42.
510

testsuite/tests/tool-toplevel/pr10712.ml renamed to testsuite/tests/tool-toplevel/topeval.ml

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,10 @@
33
* toplevel.opt
44
*)
55

6+
(* Various test-cases ensuring that the native and bytecode toplevels produce
7+
the same output *)
8+
9+
(* PR 10712 *)
610
module A : sig
711
type ('foo, 'bar) t
812

@@ -25,3 +29,19 @@ A.get_foo
2529
(* Type variables be 'a and 'b (original names lost in let-binding) *)
2630
let _bar = A.get_foo
2731
;;
32+
33+
(* PR 10849 *)
34+
let _ : int = 42
35+
;;
36+
37+
let (_ : bool) : bool = false
38+
;;
39+
40+
let List.(_) = ""
41+
;;
42+
43+
let List.(String.(_)) = 'd'
44+
;;
45+
46+
let List.(_) : float = 42.0
47+
;;

toplevel/byte/topeval.ml

Lines changed: 7 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -135,23 +135,14 @@ let execute_phrase print_outcome ppf phr =
135135
if print_outcome then
136136
Printtyp.wrap_printing_env ~error:false oldenv (fun () ->
137137
match str.str_items with
138-
| [ { str_desc =
139-
(Tstr_eval (exp, _)
140-
|Tstr_value
141-
(Asttypes.Nonrecursive,
142-
[{vb_pat = {pat_desc=Tpat_any};
143-
vb_expr = exp}
144-
]
145-
)
146-
)
147-
}
148-
] ->
149-
let outv = outval_of_value newenv v exp.exp_type in
150-
let ty = Printtyp.tree_of_type_scheme exp.exp_type in
151-
Ophr_eval (outv, ty)
152-
153138
| [] -> Ophr_signature []
154-
| _ -> Ophr_signature (pr_item oldenv sg'))
139+
| _ ->
140+
match find_eval_phrase str with
141+
| Some (exp, _, _) ->
142+
let outv = outval_of_value newenv v exp.exp_type in
143+
let ty = Printtyp.tree_of_type_scheme exp.exp_type in
144+
Ophr_eval (outv, ty)
145+
| None -> Ophr_signature (pr_item oldenv sg'))
155146
else Ophr_signature []
156147
| Exception exn ->
157148
toplevel_env := oldenv;

toplevel/native/topeval.ml

Lines changed: 4 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -181,21 +181,13 @@ let execute_phrase print_outcome ppf phr =
181181
bytecode and native toplevels always type-check _exactly_ the same
182182
expression. Adding the binding at the parsetree level (before typing)
183183
can create observable differences (e.g. in type variable names, see
184-
tool-toplevel/pr10712.ml in the testsuite) *)
184+
tool-toplevel/topeval.ml in the testsuite) *)
185185
let str, sg', rewritten =
186-
match str.str_items with
187-
| [ { str_desc = Tstr_eval (e, attrs) ; str_loc = loc } ]
188-
| [ { str_desc = Tstr_value (Asttypes.Nonrecursive,
189-
[{ vb_expr = e
190-
; vb_pat =
191-
{ pat_desc = Tpat_any;
192-
pat_extra = []; _ }
193-
; vb_attributes = attrs }])
194-
; str_loc = loc }
195-
] ->
186+
match find_eval_phrase str with
187+
| Some (e, attrs, loc) ->
196188
let str, sg' = name_expression ~loc ~attrs e in
197189
str, sg', true
198-
| _ -> str, sg', false
190+
| None -> str, sg', false
199191
in
200192
let module_ident, res, required_globals, size =
201193
if Config.flambda then

toplevel/topcommon.ml

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,18 @@ let print_out_sig_item = Oprint.out_sig_item
6464
let print_out_signature = Oprint.out_signature
6565
let print_out_phrase = Oprint.out_phrase
6666

67+
let find_eval_phrase str =
68+
let open Typedtree in
69+
match str.str_items with
70+
| [ { str_desc = Tstr_eval (e, attrs) ; str_loc = loc } ]
71+
| [ { str_desc = Tstr_value (Asttypes.Nonrecursive,
72+
[{ vb_expr = e
73+
; vb_pat = { pat_desc = Tpat_any; _ }
74+
; vb_attributes = attrs }])
75+
; str_loc = loc }
76+
] ->
77+
Some (e, attrs, loc)
78+
| _ -> None
6779

6880
(* The current typing environment for the toplevel *)
6981

toplevel/topcommon.mli

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,10 @@ val record_backtrace : unit -> unit
4646

4747
(* Printing of values *)
4848

49+
val find_eval_phrase :
50+
Typedtree.structure ->
51+
(Typedtree.expression * Typedtree.attributes * Location.t) option
52+
4953
val max_printer_depth: int ref
5054
val max_printer_steps: int ref
5155

0 commit comments

Comments
 (0)