Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ unreleased
==========

+ merlin library
- Signature help should not appear on the function name (#1997)
- Fix completion not working for inlined records labels (#1978, fixes #1977)
- Perform buffer indexing only if the query requires it (#1990 and #1991)
- Stop unnecessarily forcing substitutions when initializing short-paths graph (#1988)
Expand Down
24 changes: 14 additions & 10 deletions src/frontend/query_commands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -898,16 +898,20 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a = function
in
match application_signature with
| Some s ->
let prefix =
let fun_name = Option.value ~default:"_" s.function_name in
sprintf "%s : " fun_name
in
Some
{ label = prefix ^ s.signature;
parameters = List.map ~f:(param (String.length prefix)) s.parameters;
active_param = Option.value ~default:0 s.active_param;
active_signature = 0
}
if Msource.compare_position source position s.function_position < 0
then None
else (
let prefix =
let fun_name = Option.value ~default:"_" s.function_name in
sprintf "%s : " fun_name
in
Some
{ label = prefix ^ s.signature;
parameters = List.map ~f:(param (String.length prefix)) s.parameters;
active_param = Option.value ~default:0 s.active_param;
active_signature = 0
}
)
| None -> None)
| Version ->
Printf.sprintf "The Merlin toolkit version %s, for Ocaml %s\n"
Expand Down
5 changes: 5 additions & 0 deletions src/kernel/msource.ml
Original file line number Diff line number Diff line change
Expand Up @@ -105,6 +105,11 @@ let get_logical { text } = function
done;
`Logical (!line, offset - !cnum)

let compare_position t x y =
let `Offset ox = get_offset t x in
let `Offset oy = get_offset t y in
compare ox oy

let get_lexing_pos t ~filename pos =
let (`Offset o) = get_offset t pos in
let (`Logical (line, col)) = get_logical t pos in
Expand Down
2 changes: 2 additions & 0 deletions src/kernel/msource.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,8 @@ val get_offset : t -> [< position ] -> [> `Offset of int ]

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

val compare_position : t -> position -> position -> int

val get_lexing_pos : t -> filename:string -> [< position ] -> Lexing.position

(** {1 Managing content} *)
Expand Down
63 changes: 63 additions & 0 deletions tests/test-dirs/signature-help/issue_fun_name.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,63 @@
$ cat > test.ml <<'EOF'
> let v = List.map Fun.id []
> EOF

Valid
$ $MERLIN single signature-help -position 1:4 -filename test < test.ml
{
"class": "return",
"value": {},
"notifications": []
}

$ $MERLIN single signature-help -position 1:18 -filename test < test.ml \
> | jq '.value | {label: .signatures[0].label, activeParameter: .activeParameter}'
{
"label": "List.map : ('a -> 'a) -> 'a list -> 'a list",
"activeParameter": 0
}

$ $MERLIN single signature-help -position 1:21 -filename test < test.ml \
> | jq '.value | {label: .signatures[0].label, activeParameter: .activeParameter}'
{
"label": "List.map : ('a -> 'a) -> 'a list -> 'a list",
"activeParameter": 0
}

$ $MERLIN single signature-help -position 1:24 -filename test < test.ml \
> | jq '.value | {label: .signatures[0].label, activeParameter: .activeParameter}'
{
"label": "List.map : ('a -> 'a) -> 'a list -> 'a list",
"activeParameter": 1
}

$ $MERLIN single signature-help -position 1:9 -filename test < test.ml
{
"class": "return",
"value": {},
"notifications": []
}

$ $MERLIN single signature-help -position 1:14 -filename test < test.ml
{
"class": "return",
"value": {},
"notifications": []
}

$ cat > test2.ml <<'EOF'
> module M : sig
> val f : int -> unit
> end = struct
> let f (_ : int) = ()
> end
>
> let () = M.f (* keep whitespace *)
> EOF

$ $MERLIN single signature-help -position 7:13 -filename test < test2.ml \
> | jq '.value | {label: .signatures[0].label, activeParameter: .activeParameter}'
{
"label": "M.f : int -> unit",
"activeParameter": 0
}
Loading