@@ -480,50 +480,7 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a =
480
480
| Refactor_open (mode , pos ) ->
481
481
let typer = Mpipeline. typer_result pipeline in
482
482
let pos = Mpipeline. get_lexing_pos pipeline pos in
483
- begin match Mbrowse. select_open_node (Mtyper. node_at typer pos) with
484
- | None | Some (_ , _ , [] ) -> []
485
- | Some (path , longident , ((_ , node ) :: _ )) ->
486
- let paths =
487
- Browse_tree. all_occurrences_of_prefix ~strict_prefix: true path node in
488
- let paths = List. concat_map ~f: snd paths in
489
- let leftmost_ident = Longident. flatten longident |> List. hd in
490
- let qual_or_unqual_path p =
491
- let rec aux acc (p : Path.t ) =
492
- match p with
493
- | Pident ident ->
494
- Ident. name ident :: acc
495
- | Pdot (path', s) when
496
- mode = `Unqualify && Path. same path path' ->
497
- s :: acc
498
- | Pdot (path', s) when
499
- mode = `Qualify && s = leftmost_ident ->
500
- s :: acc
501
- | Pdot (path' , s ) ->
502
- aux (s :: acc) path'
503
- | _ -> raise Not_found
504
- in
505
- aux [] p |> String. concat ~sep: " ."
506
- in
507
- (* checks if the (un)qualified longident has a different length, i.e., has changed
508
-
509
- XXX(Ulugbek): computes longident length using [loc_start] and [loc_end], hence
510
- it doesn't work for multiline longidents because we can't compute their length *)
511
- let same_longident new_lident { Location. loc_start; loc_end; _ } =
512
- let old_longident_len = Lexing. column loc_end - Lexing. column loc_start in
513
- loc_start.Lexing. pos_lnum = loc_end.Lexing. pos_lnum &&
514
- String. length new_lident = old_longident_len
515
- in
516
- List. filter_map paths ~f: (fun {Location. txt = path ; loc} ->
517
- if not loc.Location. loc_ghost &&
518
- Location_aux. compare_pos pos loc < = 0 then
519
- match qual_or_unqual_path path with
520
- | s when same_longident s loc -> None
521
- | s -> Some (s, loc)
522
- | exception Not_found -> None
523
- else None
524
- )
525
- |> List. sort_uniq ~cmp: (fun (_ ,l1 ) (_ ,l2 ) -> Location_aux. compare l1 l2)
526
- end
483
+ Refactor_open. get_rewrites ~mode typer pos
527
484
528
485
| Document (patho , pos ) ->
529
486
let typer = Mpipeline. typer_result pipeline in
0 commit comments