Skip to content

Commit afd3a00

Browse files
committed
Allow the signature help only after the function name
1 parent 92551aa commit afd3a00

File tree

4 files changed

+25
-56
lines changed

4 files changed

+25
-56
lines changed

src/frontend/query_commands.ml

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -898,16 +898,19 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a = function
898898
in
899899
match application_signature with
900900
| Some s ->
901-
let prefix =
902-
let fun_name = Option.value ~default:"_" s.function_name in
903-
sprintf "%s : " fun_name
904-
in
905-
Some
906-
{ label = prefix ^ s.signature;
907-
parameters = List.map ~f:(param (String.length prefix)) s.parameters;
908-
active_param = Option.value ~default:0 s.active_param;
909-
active_signature = 0
910-
}
901+
if (Msource.compare_logical (Msource.get_logical source position) (Msource.get_logical source s.function_position)) < 0 then None
902+
else (
903+
let prefix =
904+
let fun_name = Option.value ~default:"_" s.function_name in
905+
sprintf "%s : " fun_name
906+
in
907+
Some
908+
{ label = prefix ^ s.signature;
909+
parameters = List.map ~f:(param (String.length prefix)) s.parameters;
910+
active_param = Option.value ~default:0 s.active_param;
911+
active_signature = 0
912+
}
913+
)
911914
| None -> None)
912915
| Version ->
913916
Printf.sprintf "The Merlin toolkit version %s, for Ocaml %s\n"

src/kernel/msource.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,14 @@ let get_logical { text } = function
105105
done;
106106
`Logical (!line, offset - !cnum)
107107

108+
let compare_logical x y : int =
109+
match x, y with
110+
| `Logical (row_x, col_x),
111+
`Logical (row_y, col_y) ->
112+
let delta_row = row_x - row_y in
113+
if delta_row = 0 then col_x - col_y else delta_row
114+
| _ -> failwith "Only `Logical expected."
115+
108116
let get_lexing_pos t ~filename pos =
109117
let (`Offset o) = get_offset t pos in
110118
let (`Logical (line, col)) = get_logical t pos in

src/kernel/msource.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@ val get_offset : t -> [< position ] -> [> `Offset of int ]
2727

2828
val get_logical : t -> [< position ] -> [> `Logical of int * int ]
2929

30+
val compare_logical : [> `Logical of int * int ] -> [> `Logical of int * int ] -> int
31+
3032
val get_lexing_pos : t -> filename:string -> [< position ] -> Lexing.position
3133

3234
(** {1 Managing content} *)

tests/test-dirs/signature-help/issue_fun_name.t

Lines changed: 2 additions & 46 deletions
Original file line numberDiff line numberDiff line change
@@ -135,57 +135,13 @@ FIXME: Signature help should not appear on the name of the function:
135135
$ $MERLIN single signature-help -position 1:9 -filename test < test.ml
136136
{
137137
"class": "return",
138-
"value": {
139-
"signatures": [
140-
{
141-
"label": "List.map : ('a -> 'a) -> 'a list -> 'a list",
142-
"parameters": [
143-
{
144-
"label": [
145-
11,
146-
21
147-
]
148-
},
149-
{
150-
"label": [
151-
25,
152-
32
153-
]
154-
}
155-
]
156-
}
157-
],
158-
"activeParameter": 0,
159-
"activeSignature": 0
160-
},
138+
"value": {},
161139
"notifications": []
162140
}
163141

164142
$ $MERLIN single signature-help -position 1:14 -filename test < test.ml
165143
{
166144
"class": "return",
167-
"value": {
168-
"signatures": [
169-
{
170-
"label": "List.map : ('a -> 'a) -> 'a list -> 'a list",
171-
"parameters": [
172-
{
173-
"label": [
174-
11,
175-
21
176-
]
177-
},
178-
{
179-
"label": [
180-
25,
181-
32
182-
]
183-
}
184-
]
185-
}
186-
],
187-
"activeParameter": 0,
188-
"activeSignature": 0
189-
},
145+
"value": {},
190146
"notifications": []
191147
}

0 commit comments

Comments
 (0)