Skip to content

Commit

Permalink
Fix the issue by preparing texp for printing
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Jan 10, 2025
1 parent 5e4c6bd commit 6b7ace8
Show file tree
Hide file tree
Showing 4 changed files with 11 additions and 4 deletions.
5 changes: 3 additions & 2 deletions src/analysis/completion.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,12 +57,13 @@ let raw_info_printer : raw_info -> _ = function
(Out_sig_item
(Out_type.tree_of_type_declaration id tdecl Types.Trec_first))
| `Type_scheme te ->
`Print (Out_type (Out_type.tree_of_typexp Type_scheme te))
`Print (Out_type (Type_utils.Printtyp.tree_of_typ_scheme te))
| `Variant (label, arg) -> begin
match arg with
| None -> `String label
| Some te ->
`Concat (label ^ " of ", Out_type (Out_type.tree_of_typexp Type_scheme te))
`Concat
(label ^ " of ", Out_type (Type_utils.Printtyp.tree_of_typ_scheme te))
end

(* List methods of an object.
Expand Down
4 changes: 4 additions & 0 deletions src/analysis/type_utils.ml
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,10 @@ module Printtyp = struct
(select_by_verbosity ~default:type_scheme ~verbose:(verbose_type_scheme env))
ppf ty

let tree_of_typ_scheme te =
Out_type.prepare_for_printing [ te ];
Out_type.tree_of_typexp Type_scheme te

let type_declaration env id ppf =
(select_by_verbosity ~default:type_declaration
~verbose:(verbose_type_declaration env))
Expand Down
2 changes: 2 additions & 0 deletions src/analysis/type_utils.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,8 @@ module Printtyp : sig

val type_scheme : Env.t -> Format.formatter -> Types.type_expr -> unit

val tree_of_typ_scheme : Types.type_expr -> Outcometree.out_type

val modtype : Env.t -> Format.formatter -> Types.module_type -> unit

val wrap_printing_env :
Expand Down
4 changes: 2 additions & 2 deletions tests/test-dirs/completion/issue-lsp-503.t
Original file line number Diff line number Diff line change
Expand Up @@ -14,14 +14,14 @@ We complete the name of the object
{
"name": "map",
"kind": "Value",
"desc": "('a1 -> 'b1) -> 'a1 list -> 'b1 list",
"desc": "('a -> 'b) -> 'a list -> 'b list",
"info": "",
"deprecated": false
},
{
"name": "mapi",
"kind": "Value",
"desc": "(int -> 'a0 -> 'b0) -> 'a0 list -> 'b0 list",
"desc": "(int -> 'a -> 'b) -> 'a list -> 'b list",
"info": "",
"deprecated": false
},
Expand Down

0 comments on commit 6b7ace8

Please sign in to comment.