File tree Expand file tree Collapse file tree 5 files changed +85
-10
lines changed
tests/test-dirs/signature-help Expand file tree Collapse file tree 5 files changed +85
-10
lines changed Original file line number Diff line number Diff line change @@ -2,6 +2,7 @@ unreleased
22==========
33
44 + merlin library
5+ - Signature help should not appear on the function name (#1997 )
56 - Fix completion not working for inlined records labels (#1978 , fixes #1977 )
67 - Perform buffer indexing only if the query requires it (#1990 and #1991 )
78 - Stop unnecessarily forcing substitutions when initializing short-paths graph (#1988 )
Original file line number Diff line number Diff line change @@ -898,16 +898,20 @@ 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_position source position s.function_position < 0
902+ then None
903+ else (
904+ let prefix =
905+ let fun_name = Option. value ~default: " _" s.function_name in
906+ sprintf " %s : " fun_name
907+ in
908+ Some
909+ { label = prefix ^ s.signature;
910+ parameters = List. map ~f: (param (String. length prefix)) s.parameters;
911+ active_param = Option. value ~default: 0 s.active_param;
912+ active_signature = 0
913+ }
914+ )
911915 | None -> None )
912916 | Version ->
913917 Printf. sprintf " The Merlin toolkit version %s, for Ocaml %s\n "
Original file line number Diff line number Diff line change @@ -105,6 +105,11 @@ let get_logical { text } = function
105105 done ;
106106 `Logical (! line, offset - ! cnum)
107107
108+ let compare_position t x y =
109+ let `Offset ox = get_offset t x in
110+ let `Offset oy = get_offset t y in
111+ compare ox oy
112+
108113let get_lexing_pos t ~filename pos =
109114 let (`Offset o) = get_offset t pos in
110115 let (`Logical (line, col)) = get_logical t pos in
Original file line number Diff line number Diff line change @@ -27,6 +27,8 @@ val get_offset : t -> [< position ] -> [> `Offset of int ]
2727
2828val get_logical : t -> [< position ] -> [> `Logical of int * int ]
2929
30+ val compare_position : t -> position -> position -> int
31+
3032val get_lexing_pos : t -> filename :string -> [< position ] -> Lexing .position
3133
3234(* * {1 Managing content} *)
Original file line number Diff line number Diff line change 1+ $ cat > test. ml << ' EOF'
2+ > let v = List . map Fun. id []
3+ > EOF
4+
5+ Valid
6+ $ $ MERLIN single signature-help -position 1 : 4 -filename test < test. ml
7+ {
8+ " class" : " return" ,
9+ " value" : {},
10+ " notifications" : []
11+ }
12+
13+ $ $ MERLIN single signature-help -position 1 : 18 -filename test < test. ml \
14+ > | jq ' .value | {label: .signatures[0].label, activeParameter: .activeParameter}'
15+ {
16+ " label" : " List.map : ('a -> 'a) -> 'a list -> 'a list" ,
17+ " activeParameter" : 0
18+ }
19+
20+ $ $ MERLIN single signature-help -position 1 : 21 -filename test < test. ml \
21+ > | jq ' .value | {label: .signatures[0].label, activeParameter: .activeParameter}'
22+ {
23+ " label" : " List.map : ('a -> 'a) -> 'a list -> 'a list" ,
24+ " activeParameter" : 0
25+ }
26+
27+ $ $ MERLIN single signature-help -position 1 : 24 -filename test < test. ml \
28+ > | jq ' .value | {label: .signatures[0].label, activeParameter: .activeParameter}'
29+ {
30+ " label" : " List.map : ('a -> 'a) -> 'a list -> 'a list" ,
31+ " activeParameter" : 1
32+ }
33+
34+ $ $ MERLIN single signature-help -position 1 : 9 -filename test < test. ml
35+ {
36+ " class" : " return" ,
37+ " value" : {},
38+ " notifications" : []
39+ }
40+
41+ $ $ MERLIN single signature-help -position 1 : 14 -filename test < test. ml
42+ {
43+ " class" : " return" ,
44+ " value" : {},
45+ " notifications" : []
46+ }
47+
48+ $ cat > test2. ml << ' EOF'
49+ > module M : sig
50+ > val f : int -> unit
51+ > end = struct
52+ > let f (_ : int ) = ()
53+ > end
54+ >
55+ > let () = M. f (* keep whitespace * )
56+ > EOF
57+
58+ $ $ MERLIN single signature-help -position 7 : 13 -filename test < test2. ml \
59+ > | jq ' .value | {label: .signatures[0].label, activeParameter: .activeParameter}'
60+ {
61+ " label" : " M.f : int -> unit" ,
62+ " activeParameter" : 0
63+ }
You can’t perform that action at this time.
0 commit comments