Skip to content

Commit 68f4fcb

Browse files
authored
Introduce experimental project-wide renaming (#1431)
* Experiment: project-wide renaming * Add a changelog entry for #1431
1 parent a7ce29f commit 68f4fcb

File tree

4 files changed

+100
-71
lines changed

4 files changed

+100
-71
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,9 @@
1+
# Unreleased
2+
3+
## Features
4+
5+
- Enable experimental project-wide renaming of identifiers (#1431)
6+
17
# 1.21.0
28

39
## Features

ocaml-lsp-server/src/import.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,8 @@ include struct
130130
include Uri
131131

132132
let to_dyn t = Dyn.string (to_string t)
133+
134+
module Map = Stdlib.Map.Make (Uri)
133135
end
134136
end
135137

ocaml-lsp-server/src/rename.ml

Lines changed: 56 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -8,38 +8,55 @@ let rename (state : State.t) { RenameParams.textDocument = { uri }; position; ne
88
| `Other -> Fiber.return (WorkspaceEdit.create ())
99
| `Merlin merlin ->
1010
let command =
11-
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Buffer)
11+
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Renaming)
1212
in
1313
let+ locs, _desync = Document.Merlin.dispatch_exn ~name:"rename" merlin command in
1414
let version = Document.version doc in
15-
let source = Document.source doc in
15+
let uri = Document.uri doc in
1616
let edits =
17-
List.map locs ~f:(fun (loc : Warnings.loc) ->
17+
List.fold_left locs ~init:Uri.Map.empty ~f:(fun acc (loc : Warnings.loc) ->
1818
let range = Range.of_loc loc in
19-
let make_edit () = TextEdit.create ~range ~newText:newName in
20-
match
21-
let occur_start_pos =
22-
Position.of_lexical_position loc.loc_start |> Option.value_exn
23-
in
24-
occur_start_pos
25-
with
26-
| { character = 0; _ } -> make_edit ()
27-
| pos ->
28-
let mpos = Position.logical pos in
29-
let (`Offset index) = Msource.get_offset source mpos in
30-
assert (index > 0)
31-
(* [index = 0] if we pass [`Logical (1, 0)], but we handle the case
32-
when [character = 0] in a separate matching branch *);
33-
let source_txt = Msource.text source in
34-
(match source_txt.[index - 1] with
35-
| '~' (* the occurrence is a named argument *)
36-
| '?' (* is an optional argument *) ->
37-
let empty_range_at_occur_end =
38-
let occur_end_pos = range.Range.end_ in
39-
{ range with start = occur_end_pos }
40-
in
41-
TextEdit.create ~range:empty_range_at_occur_end ~newText:(":" ^ newName)
42-
| _ -> make_edit ()))
19+
let edit = TextEdit.create ~range ~newText:newName in
20+
let uri =
21+
match loc.loc_start.pos_fname with
22+
| "" -> uri
23+
| path -> Uri.of_path path
24+
in
25+
Uri.Map.add_to_list uri edit acc)
26+
in
27+
let edits =
28+
Uri.Map.mapi
29+
(fun doc_uri edits ->
30+
let source =
31+
match Document_store.get_opt state.store doc_uri with
32+
| Some doc when DocumentUri.equal doc_uri (Document.uri doc) ->
33+
Document.source doc
34+
| Some _ | None ->
35+
let source_path = Uri.to_path doc_uri in
36+
In_channel.with_open_text source_path In_channel.input_all |> Msource.make
37+
in
38+
List.map edits ~f:(fun (edit : TextEdit.t) ->
39+
let start_position = edit.range.start in
40+
match start_position with
41+
| { character = 0; _ } -> edit
42+
| pos ->
43+
let mpos = Position.logical pos in
44+
let (`Offset index) = Msource.get_offset source mpos in
45+
assert (index > 0)
46+
(* [index = 0] if we pass [`Logical (1, 0)], but we handle the case
47+
when [character = 0] in a separate matching branch *);
48+
let source_txt = Msource.text source in
49+
(* TODO: handle record field puning *)
50+
(match source_txt.[index - 1] with
51+
| '~' (* the occurrence is a named argument *)
52+
| '?' (* is an optional argument *) ->
53+
let empty_range_at_occur_end =
54+
let occur_end_pos = edit.range.end_ in
55+
{ edit.range with start = occur_end_pos }
56+
in
57+
TextEdit.create ~range:empty_range_at_occur_end ~newText:(":" ^ newName)
58+
| _ -> edit)))
59+
edits
4360
in
4461
let workspace_edits =
4562
let documentChanges =
@@ -53,15 +70,19 @@ let rename (state : State.t) { RenameParams.textDocument = { uri }; position; ne
5370
in
5471
if documentChanges
5572
then (
56-
let textDocument =
57-
OptionalVersionedTextDocumentIdentifier.create ~uri ~version ()
73+
let documentChanges =
74+
Uri.Map.to_list edits
75+
|> List.map ~f:(fun (uri, edits) ->
76+
let textDocument =
77+
OptionalVersionedTextDocumentIdentifier.create ~uri ~version ()
78+
in
79+
let edits = List.map edits ~f:(fun e -> `TextEdit e) in
80+
`TextDocumentEdit (TextDocumentEdit.create ~textDocument ~edits))
5881
in
59-
let edits = List.map edits ~f:(fun e -> `TextEdit e) in
60-
WorkspaceEdit.create
61-
~documentChanges:
62-
[ `TextDocumentEdit (TextDocumentEdit.create ~textDocument ~edits) ]
63-
())
64-
else WorkspaceEdit.create ~changes:[ uri, edits ] ()
82+
WorkspaceEdit.create ~documentChanges ())
83+
else (
84+
let changes = Uri.Map.to_list edits in
85+
WorkspaceEdit.create ~changes ())
6586
in
6687
workspace_edits
6788
;;

ocaml-lsp-server/test/e2e/__tests__/textDocument-rename.test.ts

Lines changed: 36 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -111,25 +111,25 @@ describe("textDocument/rename", () => {
111111
"newText": "new_num",
112112
"range": {
113113
"end": {
114-
"character": 7,
115-
"line": 0,
114+
"character": 13,
115+
"line": 1,
116116
},
117117
"start": {
118-
"character": 4,
119-
"line": 0,
118+
"character": 10,
119+
"line": 1,
120120
},
121121
},
122122
},
123123
{
124124
"newText": "new_num",
125125
"range": {
126126
"end": {
127-
"character": 13,
128-
"line": 1,
127+
"character": 7,
128+
"line": 0,
129129
},
130130
"start": {
131-
"character": 10,
132-
"line": 1,
131+
"character": 4,
132+
"line": 0,
133133
},
134134
},
135135
},
@@ -163,25 +163,25 @@ describe("textDocument/rename", () => {
163163
"newText": "new_num",
164164
"range": {
165165
"end": {
166-
"character": 7,
167-
"line": 0,
166+
"character": 13,
167+
"line": 1,
168168
},
169169
"start": {
170-
"character": 4,
171-
"line": 0,
170+
"character": 10,
171+
"line": 1,
172172
},
173173
},
174174
},
175175
{
176176
"newText": "new_num",
177177
"range": {
178178
"end": {
179-
"character": 13,
180-
"line": 1,
179+
"character": 7,
180+
"line": 0,
181181
},
182182
"start": {
183-
"character": 10,
184-
"line": 1,
183+
"character": 4,
184+
"line": 0,
185185
},
186186
},
187187
},
@@ -218,28 +218,28 @@ let () = bar ~foo
218218
"changes": {
219219
"file:///test.ml": [
220220
{
221-
"newText": "ident",
221+
"newText": ":ident",
222222
"range": {
223223
"end": {
224-
"character": 7,
225-
"line": 0,
224+
"character": 17,
225+
"line": 4,
226226
},
227227
"start": {
228-
"character": 4,
229-
"line": 0,
228+
"character": 17,
229+
"line": 4,
230230
},
231231
},
232232
},
233233
{
234-
"newText": ":ident",
234+
"newText": "ident",
235235
"range": {
236236
"end": {
237-
"character": 17,
238-
"line": 4,
237+
"character": 7,
238+
"line": 0,
239239
},
240240
"start": {
241-
"character": 17,
242-
"line": 4,
241+
"character": 4,
242+
"line": 0,
243243
},
244244
},
245245
},
@@ -272,28 +272,28 @@ ignore (bar ?foo ())
272272
"changes": {
273273
"file:///test.ml": [
274274
{
275-
"newText": "sunit",
275+
"newText": ":sunit",
276276
"range": {
277277
"end": {
278-
"character": 7,
279-
"line": 0,
278+
"character": 16,
279+
"line": 5,
280280
},
281281
"start": {
282-
"character": 4,
283-
"line": 0,
282+
"character": 16,
283+
"line": 5,
284284
},
285285
},
286286
},
287287
{
288-
"newText": ":sunit",
288+
"newText": "sunit",
289289
"range": {
290290
"end": {
291-
"character": 16,
292-
"line": 5,
291+
"character": 7,
292+
"line": 0,
293293
},
294294
"start": {
295-
"character": 16,
296-
"line": 5,
295+
"character": 4,
296+
"line": 0,
297297
},
298298
},
299299
},

0 commit comments

Comments
 (0)