Skip to content

Commit

Permalink
wip: working renaming, but smart punning detection is disabled
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Jan 10, 2025
1 parent a7ce29f commit 4683e4b
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 14 deletions.
2 changes: 2 additions & 0 deletions ocaml-lsp-server/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,8 @@ include struct
include Uri

let to_dyn t = Dyn.string (to_string t)

module Map = Stdlib.Map.Make (Uri)
end
end

Expand Down
38 changes: 24 additions & 14 deletions ocaml-lsp-server/src/rename.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,16 +8,22 @@ let rename (state : State.t) { RenameParams.textDocument = { uri }; position; ne
| `Other -> Fiber.return (WorkspaceEdit.create ())
| `Merlin merlin ->
let command =
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Buffer)
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Renaming)
in
let+ locs, _desync = Document.Merlin.dispatch_exn ~name:"rename" merlin command in
let version = Document.version doc in
let source = Document.source doc in
(* let source = Document.source doc in *)
let edits =
List.map locs ~f:(fun (loc : Warnings.loc) ->
List.fold_left locs ~init:Uri.Map.empty ~f:(fun acc (loc : Warnings.loc) ->
let range = Range.of_loc loc in
let make_edit () = TextEdit.create ~range ~newText:newName in
match
let edit = TextEdit.create ~range ~newText:newName in
let uri =
match loc.loc_start.pos_fname with
| "" -> uri
| path -> Uri.of_path path
in
Uri.Map.add_to_list uri edit acc
(* match
let occur_start_pos =
Position.of_lexical_position loc.loc_start |> Option.value_exn
in
Expand All @@ -39,7 +45,7 @@ let rename (state : State.t) { RenameParams.textDocument = { uri }; position; ne
{ range with start = occur_end_pos }
in
TextEdit.create ~range:empty_range_at_occur_end ~newText:(":" ^ newName)
| _ -> make_edit ()))
| _ -> *))
in
let workspace_edits =
let documentChanges =
Expand All @@ -53,15 +59,19 @@ let rename (state : State.t) { RenameParams.textDocument = { uri }; position; ne
in
if documentChanges
then (
let textDocument =
OptionalVersionedTextDocumentIdentifier.create ~uri ~version ()
let documentChanges =
Uri.Map.to_list edits
|> List.map ~f:(fun (uri, edits) ->
let textDocument =
OptionalVersionedTextDocumentIdentifier.create ~uri ~version ()
in
let edits = List.map edits ~f:(fun e -> `TextEdit e) in
`TextDocumentEdit (TextDocumentEdit.create ~textDocument ~edits))
in
let edits = List.map edits ~f:(fun e -> `TextEdit e) in
WorkspaceEdit.create
~documentChanges:
[ `TextDocumentEdit (TextDocumentEdit.create ~textDocument ~edits) ]
())
else WorkspaceEdit.create ~changes:[ uri, edits ] ()
WorkspaceEdit.create ~documentChanges ())
else (
let changes = Uri.Map.to_list edits in
WorkspaceEdit.create ~changes ())
in
workspace_edits
;;

0 comments on commit 4683e4b

Please sign in to comment.