Skip to content

Commit

Permalink
Unify further
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed Jan 5, 2022
1 parent ef84ac7 commit 479f625
Show file tree
Hide file tree
Showing 6 changed files with 42 additions and 29 deletions.
4 changes: 4 additions & 0 deletions testsuite/tests/tool-toplevel/topeval.compilers.reference
Original file line number Diff line number Diff line change
Expand Up @@ -3,4 +3,8 @@ module A :
- : ('foo, 'a) A.t -> 'foo option = <fun>
val _bar : ('a, 'b) A.t -> 'a option = <fun>
- : int = 42
- : int = 42
- : int = 42
- : int = 42
- : int = 42

This comment has been minimized.

Copy link
@gasche

gasche Jan 5, 2022

Member

Nit: this test output would be easier to read (for example if one of the cases was to break later) if you used different literal values for each test.

This comment has been minimized.

Copy link
@dra27

dra27 Jan 5, 2022

Author Member

Oh yes, much better!


12 changes: 12 additions & 0 deletions testsuite/tests/tool-toplevel/topeval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,3 +33,15 @@ let _bar = A.get_foo
(* PR 10849 *)
let _ : int = 42
;;

let (_ : int) : int = 42
;;

let List.(_) = 42
;;

let List.(String.(_)) = 42
;;

let List.(_) : int = 42
;;
23 changes: 7 additions & 16 deletions toplevel/byte/topeval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -135,23 +135,14 @@ let execute_phrase print_outcome ppf phr =
if print_outcome then
Printtyp.wrap_printing_env ~error:false oldenv (fun () ->
match str.str_items with
| [ { str_desc =
(Tstr_eval (exp, _)
|Tstr_value
(Asttypes.Nonrecursive,
[{vb_pat = {pat_desc=Tpat_any};
vb_expr = exp}
]
)
)
}
] ->
let outv = outval_of_value newenv v exp.exp_type in
let ty = Printtyp.tree_of_type_scheme exp.exp_type in
Ophr_eval (outv, ty)

| [] -> Ophr_signature []
| _ -> Ophr_signature (pr_item oldenv sg'))
| _ ->
match find_eval_phrase str with
| Some (exp, _, _) ->
let outv = outval_of_value newenv v exp.exp_type in
let ty = Printtyp.tree_of_type_scheme exp.exp_type in
Ophr_eval (outv, ty)
| None -> Ophr_signature (pr_item oldenv sg'))
else Ophr_signature []
| Exception exn ->
toplevel_env := oldenv;
Expand Down
16 changes: 3 additions & 13 deletions toplevel/native/topeval.ml
Original file line number Diff line number Diff line change
Expand Up @@ -183,21 +183,11 @@ let execute_phrase print_outcome ppf phr =
can create observable differences (e.g. in type variable names, see
tool-toplevel/topeval.ml in the testsuite) *)
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 =
([] | [Tpat_constraint _, _, _])
; _ }
; vb_attributes = attrs }])
; str_loc = loc }
] ->
match find_eval_phrase str with
| Some (e, attrs, loc) ->
let str, sg' = name_expression ~loc ~attrs e in
str, sg', true
| _ -> str, sg', false
| None -> str, sg', false
in
let module_ident, res, required_globals, size =
if Config.flambda then
Expand Down
12 changes: 12 additions & 0 deletions toplevel/topcommon.ml
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,18 @@ let print_out_sig_item = Oprint.out_sig_item
let print_out_signature = Oprint.out_signature
let print_out_phrase = Oprint.out_phrase

let find_eval_phrase str =
let open Typedtree in
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; _ }
; vb_attributes = attrs }])
; str_loc = loc }
] ->
Some (e, attrs, loc)
| _ -> None

(* The current typing environment for the toplevel *)

Expand Down
4 changes: 4 additions & 0 deletions toplevel/topcommon.mli
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,10 @@ val print_out_signature :
(formatter -> Outcometree.out_sig_item list -> unit) ref
val print_out_phrase :
(formatter -> Outcometree.out_phrase -> unit) ref
val find_eval_phrase :
Typedtree.structure ->
(Typedtree.expression * Typedtree.attributes * Location.t) option

This comment has been minimized.

Copy link
@gasche

gasche Jan 5, 2022

Member

I don't like (the extra blank line and) the placement of this signature item. The block of non-separated functions above corresponds to the print_out_* functions for each grammatical category, they make sense together but the new function does not. It could go to the top of the "Printing of values" section, clearly separated from unrelated functions.

This comment has been minimized.

Copy link
@dra27

dra27 Jan 5, 2022

Author Member

Done



exception Undefined_global of string
Expand Down

0 comments on commit 479f625

Please sign in to comment.