File tree Expand file tree Collapse file tree 2 files changed +69
-6
lines changed
Expand file tree Collapse file tree 2 files changed +69
-6
lines changed Original file line number Diff line number Diff line change @@ -31,7 +31,7 @@ let completion_kind kind : CompletionItemKind.t option =
3131let prefix_of_position ~short_path source position =
3232 match Msource. text source with
3333 | "" -> " "
34- | text -> (
34+ | text ->
3535 let from =
3636 let (`Offset index) = Msource. get_offset source position in
3737 min (String. length text - 1 ) (index - 1 )
@@ -89,13 +89,17 @@ let prefix_of_position ~short_path source position =
8989 in
9090 let len = from - pos + 1 in
9191 let reconstructed_prefix = String. sub text ~pos ~len in
92- (* if we reconstructed [~f:ignore], we should take only [ignore], so: *)
93- if not (String. is_prefix reconstructed_prefix ~prefix: " ~" ) then
94- reconstructed_prefix
95- else
92+ (* if we reconstructed [~f:ignore] or [?f:ignore], we should take only
93+ [ignore], so: *)
94+ if
95+ String. is_prefix reconstructed_prefix ~prefix: " ~"
96+ || String. is_prefix reconstructed_prefix ~prefix: " ?"
97+ then
9698 match String. lsplit2 reconstructed_prefix ~on: ':' with
9799 | Some (_ , s ) -> s
98- | None -> reconstructed_prefix)
100+ | None -> reconstructed_prefix
101+ else
102+ reconstructed_prefix
99103
100104let suffix_of_position source position =
101105 match Msource. text source with
Original file line number Diff line number Diff line change @@ -136,6 +136,65 @@ g ~f:M.ig
136136 ` ) ;
137137 } ) ;
138138
139+ it ( "can complete symbol passed as an optional argument" , async ( ) => {
140+ await openDocument ( outdent `
141+ let g ?f = f in
142+ g ?f:ig
143+ ` ) ;
144+
145+ let items = await queryCompletion ( Types . Position . create ( 1 , 7 ) ) ;
146+ expect ( items ) . toMatchInlineSnapshot ( `
147+ Array [
148+ Object {
149+ "label": "ignore",
150+ "textEdit": Object {
151+ "newText": "ignore",
152+ "range": Object {
153+ "end": Object {
154+ "character": 7,
155+ "line": 1,
156+ },
157+ "start": Object {
158+ "character": 5,
159+ "line": 1,
160+ },
161+ },
162+ },
163+ },
164+ ]
165+ ` ) ;
166+ } ) ;
167+
168+ it ( "can complete symbol passed as a optional argument - 2" , async ( ) => {
169+ await openDocument ( outdent `
170+ module M = struct let igfoo _x = () end
171+ let g ?f = f in
172+ g ?f:M.ig
173+ ` ) ;
174+
175+ let items = await queryCompletion ( Types . Position . create ( 2 , 9 ) ) ;
176+ expect ( items ) . toMatchInlineSnapshot ( `
177+ Array [
178+ Object {
179+ "label": "igfoo",
180+ "textEdit": Object {
181+ "newText": "igfoo",
182+ "range": Object {
183+ "end": Object {
184+ "character": 9,
185+ "line": 2,
186+ },
187+ "start": Object {
188+ "character": 7,
189+ "line": 2,
190+ },
191+ },
192+ },
193+ },
194+ ]
195+ ` ) ;
196+ } ) ;
197+
139198 it ( "completes identifier at top level" , async ( ) => {
140199 await openDocument ( outdent `
141200 let somenum = 42
You can’t perform that action at this time.
0 commit comments