Skip to content

Commit 740d244

Browse files
committed
Perform better longident parsing.
This fixes locate when a prefix is given, but reconstruct_identifier is still not giving the correct answer. This also fix another issue with infix operators.
1 parent 7cdcc44 commit 740d244

File tree

6 files changed

+118
-77
lines changed

6 files changed

+118
-77
lines changed

src/analysis/locate.ml

Lines changed: 50 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -715,7 +715,10 @@ end = struct
715715
end
716716

717717
let uid_from_longident ~config ~env nss ml_or_mli ident =
718-
let str_ident = String.concat ~sep:"." (Longident.flatten ident) in
718+
let str_ident =
719+
try String.concat ~sep:"." (Longident.flatten ident)
720+
with _-> "Not a flat longident"
721+
in
719722
match Env_lookup.in_namespaces nss ident env with
720723
| None -> `Not_in_env str_ident
721724
| Some (path, namespace, decl_uid, loc) ->
@@ -746,51 +749,55 @@ let from_path ~config ~env ~namespace ml_or_mli path =
746749
| `Found (file, loc) -> `Found (uid, file, loc)
747750
| `File_not_found _ as otherwise -> otherwise
748751

752+
let infer_namespace ?namespaces ~pos lid browse is_label =
753+
match namespaces with
754+
| Some nss ->
755+
if not is_label
756+
then `Ok (nss :> Namespace.inferred list)
757+
else if List.mem `Labels ~set:nss then (
758+
log ~title:"from_string" "restricting namespaces to labels";
759+
`Ok [ `Labels ]
760+
) else (
761+
log ~title:"from_string"
762+
"input is clearly a label, but the given namespaces don't cover that";
763+
`Error `Missing_labels_namespace
764+
)
765+
| None ->
766+
match Context.inspect_browse_tree ~cursor:pos lid [browse], is_label with
767+
| None, _ ->
768+
log ~title:"from_string" "already at origin, doing nothing" ;
769+
`Error `At_origin
770+
| Some (Label _ as ctxt), true
771+
| Some ctxt, false ->
772+
log ~title:"from_string"
773+
"inferred context: %s" (Context.to_string ctxt);
774+
`Ok (Namespace.from_context ctxt)
775+
| _, true ->
776+
log ~title:"from_string"
777+
"dropping inferred context, it is not precise enough";
778+
`Ok [ `Labels ]
779+
749780
let from_string ~config ~env ~local_defs ~pos ?namespaces switch path =
750781
File_switching.reset ();
751782
let browse = Mbrowse.of_typedtree local_defs in
752-
let lid = Longident.parse path in
753-
let ident, is_label = Longident.keep_suffix lid in
754-
match
755-
match namespaces with
756-
| Some nss ->
757-
if not is_label
758-
then `Ok (nss :> Namespace.inferred list)
759-
else if List.mem `Labels ~set:nss then (
760-
log ~title:"from_string" "restricting namespaces to labels";
761-
`Ok [ `Labels ]
762-
) else (
763-
log ~title:"from_string"
764-
"input is clearly a label, but the given namespaces don't cover that";
765-
`Error `Missing_labels_namespace
766-
)
767-
| None ->
768-
match Context.inspect_browse_tree ~cursor:pos lid [browse], is_label with
769-
| None, _ ->
770-
log ~title:"from_string" "already at origin, doing nothing" ;
771-
`Error `At_origin
772-
| Some (Label _ as ctxt), true
773-
| Some ctxt, false ->
774-
log ~title:"from_string"
775-
"inferred context: %s" (Context.to_string ctxt);
776-
`Ok (Namespace.from_context ctxt)
777-
| _, true ->
778-
log ~title:"from_string"
779-
"dropping inferred context, it is not precise enough";
780-
`Ok [ `Labels ]
781-
with
782-
| `Error e -> e
783-
| `Ok nss ->
784-
log ~title:"from_string"
785-
"looking for the source of '%s' (prioritizing %s files)"
786-
path (match switch with `ML -> ".ml" | `MLI -> ".mli");
787-
match from_longident ~config ~env nss switch ident with
788-
| `File_not_found _ | `Not_found _ | `Not_in_env _ as err -> err
789-
| `Builtin -> `Builtin path
790-
| `Found (uid, loc) ->
791-
match find_source ~config loc path with
792-
| `Found (file, loc) -> `Found (uid, file, loc)
793-
| `File_not_found _ as otherwise -> otherwise
783+
let lid = Type_utils.parse_longident path in
784+
let from_lid lid =
785+
let ident, is_label = Longident.keep_suffix lid in
786+
match infer_namespace ?namespaces ~pos lid browse is_label with
787+
| `Error e -> e
788+
| `Ok nss ->
789+
log ~title:"from_string"
790+
"looking for the source of '%s' (prioritizing %s files)"
791+
path (match switch with `ML -> ".ml" | `MLI -> ".mli");
792+
match from_longident ~config ~env nss switch ident with
793+
| `File_not_found _ | `Not_found _ | `Not_in_env _ as err -> err
794+
| `Builtin -> `Builtin path
795+
| `Found (uid, loc) ->
796+
match find_source ~config loc path with
797+
| `Found (file, loc) -> `Found (uid, file, loc)
798+
| `File_not_found _ as otherwise -> otherwise
799+
in
800+
Option.value_map ~f:from_lid ~default:(`Not_found (path, None)) lid
794801

795802
(** When we look for docstring in external compilation unit we can perform
796803
a uid-based search and return the attached comment in the attributes.

src/analysis/type_utils.ml

Lines changed: 30 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,23 @@ let parse_expr ?(keywords=Lexer_raw.keywords []) expr =
4141
let lexer lexbuf = lexer (Lexer_raw.token_without_comments state lexbuf) in
4242
Parser_raw.parse_expression lexer lexbuf
4343

44+
45+
let parse_longident lid =
46+
let protected_lid =
47+
Pprintast.protect_ident (Format.str_formatter) lid;
48+
Format.flush_str_formatter ()
49+
in
50+
let lexbuf = Lexing.from_string protected_lid in
51+
let state = Lexer_raw.make @@ Lexer_raw.keywords [] in
52+
let rec lexer = function
53+
| Lexer_raw.Fail (e,l) -> raise (Lexer_raw.Error (e,l))
54+
| Lexer_raw.Return token -> token
55+
| Lexer_raw.Refill k -> lexer (k ())
56+
in
57+
let lexer lexbuf = lexer (Lexer_raw.token_without_comments state lexbuf) in
58+
try Some (Parser_raw.parse_any_longident lexer lexbuf)
59+
with Parser_raw.Error -> None
60+
4461
let lookup_module name env =
4562
let path, md = Env.find_module_by_name name env in
4663
path, md.Types.md_type, md.Types.md_attributes
@@ -52,7 +69,7 @@ module Printtyp = struct
5269

5370
let expand_type env ty =
5471
Env.with_cmis @@ fun () -> (* ?? Not sure *)
55-
match !verbosity with
72+
match !verbosity with
5673
| Smart | Lvl 0 -> ty
5774
| Lvl (_ : int) ->
5875
(* Fresh copy of the type to mutilate *)
@@ -102,32 +119,32 @@ module Printtyp = struct
102119
let verbose_modtype env ppf t =
103120
Printtyp.modtype ppf (expand_sig env t)
104121

105-
let select_by_verbosity ~default ?(smart=default) ~verbose =
122+
let select_by_verbosity ~default ?(smart=default) ~verbose =
106123
match !verbosity with
107124
| Smart -> smart
108125
| Lvl 0 -> default
109126
| Lvl _ -> verbose
110127

111-
let type_scheme env ppf ty =
112-
(select_by_verbosity
113-
~default:type_scheme
128+
let type_scheme env ppf ty =
129+
(select_by_verbosity
130+
~default:type_scheme
114131
~verbose:(verbose_type_scheme env)) ppf ty
115132

116-
let type_declaration env id ppf =
117-
(select_by_verbosity
118-
~default:type_declaration
133+
let type_declaration env id ppf =
134+
(select_by_verbosity
135+
~default:type_declaration
119136
~verbose:(verbose_type_declaration env)) id ppf
120137

121138
let modtype env ppf mty =
122-
let smart ppf = function
139+
let smart ppf = function
123140
| Types.Mty_ident _ | Mty_alias _ -> verbose_modtype env ppf mty
124-
| _ -> modtype ppf mty
125-
in
126-
(select_by_verbosity
141+
| _ -> modtype ppf mty
142+
in
143+
(select_by_verbosity
127144
~default:modtype
128145
~verbose:(verbose_modtype env)
129146
~smart) ppf mty
130-
147+
131148
let wrap_printing_env env ~verbosity:v f =
132149
let_ref verbosity v (fun () -> wrap_printing_env env f)
133150
end

src/analysis/type_utils.mli

Lines changed: 19 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -49,22 +49,22 @@ val mod_smallerthan : int -> Types.module_type -> int option
4949
otherwise (module is bigger than threshold).
5050
Used to skip printing big modules in completion. *)
5151

52-
val type_in_env :
53-
?verbosity:Mconfig.Verbosity.t
54-
-> ?keywords:Lexer_raw.keywords
55-
-> context: Context.t
56-
-> Env.t
57-
-> Format.formatter
58-
-> string
52+
val type_in_env :
53+
?verbosity:Mconfig.Verbosity.t
54+
-> ?keywords:Lexer_raw.keywords
55+
-> context: Context.t
56+
-> Env.t
57+
-> Format.formatter
58+
-> string
5959
-> bool
6060
(** [type_in_env env ppf input] parses [input] and prints its type on [ppf].
6161
Returning true if it printed a type, false otherwise. *)
6262

63-
val print_type_with_decl :
64-
verbosity:Mconfig.Verbosity.t
65-
-> Env.t
66-
-> Format.formatter
67-
-> Types.type_expr
63+
val print_type_with_decl :
64+
verbosity:Mconfig.Verbosity.t
65+
-> Env.t
66+
-> Format.formatter
67+
-> Types.type_expr
6868
-> unit
6969
(** [print_type_or_decl] behaves like [Printtyp.type_scheme], it prints the
7070
type expression, except if it is a type constructor and verbosity is set then
@@ -80,9 +80,11 @@ val read_doc_attributes : Parsetree.attributes -> (string * Location.t) option
8080

8181
val is_deprecated : Parsetree.attributes -> bool
8282

83-
val print_constr :
84-
verbosity:Mconfig.Verbosity.t
85-
-> Env.t
86-
-> Format.formatter
87-
-> Types.constructor_description
83+
val print_constr :
84+
verbosity:Mconfig.Verbosity.t
85+
-> Env.t
86+
-> Format.formatter
87+
-> Types.constructor_description
8888
-> unit
89+
90+
val parse_longident : string -> Longident.t option

src/ocaml/parsing/pprintast.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,3 +56,4 @@ val tyvar: Format.formatter -> string -> unit
5656

5757
(* merlin *)
5858
val case_list : Format.formatter -> Parsetree.case list -> unit
59+
val protect_ident : Format.formatter -> string -> unit

tests/test-dirs/locate/issue1610.t

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313
> EOF
1414

1515
FIXME: we should jump to the functor's body, not the current definition
16+
This is due to an issue with identifier-reconstruction
1617
$ $MERLIN single locate -look-for ml -position 11:15 \
1718
> -filename main.ml <main.ml
1819
{
@@ -27,11 +28,17 @@ FIXME: we should jump to the functor's body, not the current definition
2728
"notifications": []
2829
}
2930

30-
FIXME: same when the user inputs the expression manually
31+
It works as expected when the user inputs the expression manually
3132
$ $MERLIN single locate -prefix 'M(T).t' -look-for ml -position 11:15 \
3233
> -filename main.ml <main.ml
3334
{
3435
"class": "return",
35-
"value": "Not in environment 'M(T).t'",
36+
"value": {
37+
"file": "$TESTCASE_ROOT/main.ml",
38+
"pos": {
39+
"line": 6,
40+
"col": 2
41+
}
42+
},
3643
"notifications": []
3744
}
Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,15 @@
11
This test is for testing the behavior of identifiers with a . in them:
22

3-
$ $MERLIN single locate -look-for ml -position 2:16 ./issue949.ml < ./issue949.ml
3+
$ $MERLIN single locate -look-for ml -position 2:16 \
4+
> -filename ./issue949.ml < ./issue949.ml
45
{
56
"class": "return",
6-
"value": "Not in environment ''",
7+
"value": {
8+
"file": "$TESTCASE_ROOT/issue949.ml",
9+
"pos": {
10+
"line": 1,
11+
"col": 22
12+
}
13+
},
714
"notifications": []
815
}

0 commit comments

Comments
 (0)