Skip to content

Commit 405ef19

Browse files
authored
chore: remove some pointless qualification (#1144)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 9e3a6ef commit 405ef19

File tree

1 file changed

+21
-25
lines changed

1 file changed

+21
-25
lines changed

ocaml-lsp-server/src/ocaml_lsp_server.ml

Lines changed: 21 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -366,20 +366,15 @@ let text_document_lens (state : State.t)
366366
| `Other -> Fiber.return []
367367
| `Merlin m when Document.Merlin.kind m = Intf -> Fiber.return []
368368
| `Merlin doc ->
369-
let+ outline =
370-
let command = Query_protocol.Outline in
371-
Document.Merlin.dispatch_exn doc command
372-
in
373-
let rec symbol_info_of_outline_item item =
369+
let+ outline = Document.Merlin.dispatch_exn doc Outline in
370+
let rec symbol_info_of_outline_item (item : Query_protocol.item) =
374371
let children =
375-
List.concat_map
376-
item.Query_protocol.children
377-
~f:symbol_info_of_outline_item
372+
List.concat_map item.children ~f:symbol_info_of_outline_item
378373
in
379-
match item.Query_protocol.outline_type with
374+
match item.outline_type with
380375
| None -> children
381376
| Some typ ->
382-
let loc = item.Query_protocol.location in
377+
let loc = item.location in
383378
let info =
384379
let range = Range.of_loc loc in
385380
let command = Command.create ~title:typ ~command:"" () in
@@ -397,12 +392,12 @@ let selection_range (state : State.t)
397392
| `Merlin merlin ->
398393
let selection_range_of_shapes (cursor_position : Position.t)
399394
(shapes : Query_protocol.shape list) : SelectionRange.t option =
400-
let rec ranges_of_shape parent s =
395+
let rec ranges_of_shape parent (s : Query_protocol.shape) =
401396
let selectionRange =
402-
let range = Range.of_loc s.Query_protocol.shape_loc in
397+
let range = Range.of_loc s.shape_loc in
403398
{ SelectionRange.range; parent }
404399
in
405-
match s.Query_protocol.shape_sub with
400+
match s.shape_sub with
406401
| [] -> [ selectionRange ]
407402
| xs -> List.concat_map xs ~f:(ranges_of_shape (Some selectionRange))
408403
in
@@ -424,8 +419,7 @@ let selection_range (state : State.t)
424419
let+ ranges =
425420
Fiber.sequential_map positions ~f:(fun x ->
426421
let+ shapes =
427-
let command = Query_protocol.Shape (Position.logical x) in
428-
Document.Merlin.dispatch_exn merlin command
422+
Document.Merlin.dispatch_exn merlin (Shape (Position.logical x))
429423
in
430424
selection_range_of_shapes x shapes)
431425
in
@@ -437,10 +431,11 @@ let references (state : State.t)
437431
match Document.kind doc with
438432
| `Other -> Fiber.return None
439433
| `Merlin doc ->
440-
let command =
441-
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Buffer)
434+
let+ locs =
435+
Document.Merlin.dispatch_exn
436+
doc
437+
(Occurrences (`Ident_at (Position.logical position), `Buffer))
442438
in
443-
let+ locs = Document.Merlin.dispatch_exn doc command in
444439
Some
445440
(List.map locs ~f:(fun loc ->
446441
let range = Range.of_loc loc in
@@ -454,10 +449,11 @@ let highlight (state : State.t)
454449
match Document.kind doc with
455450
| `Other -> Fiber.return None
456451
| `Merlin m ->
457-
let command =
458-
Query_protocol.Occurrences (`Ident_at (Position.logical position), `Buffer)
452+
let+ locs =
453+
Document.Merlin.dispatch_exn
454+
m
455+
(Occurrences (`Ident_at (Position.logical position), `Buffer))
459456
in
460-
let+ locs = Document.Merlin.dispatch_exn m command in
461457
let lsp_locs =
462458
List.map locs ~f:(fun loc ->
463459
let range = Range.of_loc loc in
@@ -629,11 +625,11 @@ let on_request :
629625
match Document.kind doc with
630626
| `Other -> Fiber.return None
631627
| `Merlin doc ->
632-
let command =
633-
Query_protocol.Occurrences
634-
(`Ident_at (Position.logical position), `Buffer)
628+
let+ locs =
629+
Document.Merlin.dispatch_exn
630+
doc
631+
(Occurrences (`Ident_at (Position.logical position), `Buffer))
635632
in
636-
let+ locs = Document.Merlin.dispatch_exn doc command in
637633
let loc =
638634
List.find_opt locs ~f:(fun loc ->
639635
let range = Range.of_loc loc in

0 commit comments

Comments
 (0)