Skip to content

Commit a8fa9db

Browse files
committed
refactor_open: move to its own file
1 parent 172601c commit a8fa9db

File tree

3 files changed

+55
-44
lines changed

3 files changed

+55
-44
lines changed

src/analysis/refactor_open.ml

+48
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
open Std
2+
3+
let qual_or_unqual_path mode leftmost_ident path p =
4+
let rec aux acc (p : Path.t) =
5+
match p with
6+
| Pident ident ->
7+
Ident.name ident :: acc
8+
| Pdot (path', s) when
9+
mode = `Unqualify && Path.same path path' ->
10+
s :: acc
11+
| Pdot (path', s) when
12+
mode = `Qualify && s = leftmost_ident ->
13+
s :: acc
14+
| Pdot (path', s) ->
15+
aux (s :: acc) path'
16+
| _ -> raise Not_found
17+
in
18+
aux [] p |> String.concat ~sep:"."
19+
20+
(* checks if the (un)qualified longident has a different length, i.e., has changed
21+
22+
XXX(Ulugbek): computes longident length using [loc_start] and [loc_end], hence
23+
it doesn't work for multiline longidents because we can't compute their length *)
24+
let same_longident new_lident { Location. loc_start; loc_end; _ } =
25+
let old_longident_len = Lexing.column loc_end - Lexing.column loc_start in
26+
loc_start.Lexing.pos_lnum = loc_end.Lexing.pos_lnum &&
27+
String.length new_lident = old_longident_len
28+
29+
30+
let get_rewrites ~mode typer pos =
31+
match Mbrowse.select_open_node (Mtyper.node_at typer pos) with
32+
| None | Some (_, _, []) -> []
33+
| Some (orig_path, longident, ((_, node) :: _)) ->
34+
let paths =
35+
Browse_tree.all_occurrences_of_prefix ~strict_prefix:true orig_path node
36+
in
37+
let paths = List.concat_map ~f:snd paths in
38+
let leftmost_ident = Longident.flatten longident |> List.hd in
39+
List.filter_map paths ~f:(fun {Location. txt = path; loc} ->
40+
if loc.Location.loc_ghost || Location_aux.compare_pos pos loc > 0 then
41+
None
42+
else
43+
match qual_or_unqual_path mode leftmost_ident orig_path path with
44+
| s when same_longident s loc -> None
45+
| s -> Some (s, loc)
46+
| exception Not_found -> None
47+
)
48+
|> List.sort_uniq ~cmp:(fun (_,l1) (_,l2) -> Location_aux.compare l1 l2)

src/analysis/refactor_open.mli

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
2+
val get_rewrites
3+
: mode:[> `Qualify | `Unqualify ]
4+
-> Mtyper.result
5+
-> Lexing.position
6+
-> (string * Location.t) list

src/frontend/query_commands.ml

+1-44
Original file line numberDiff line numberDiff line change
@@ -480,50 +480,7 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a =
480480
| Refactor_open (mode, pos) ->
481481
let typer = Mpipeline.typer_result pipeline in
482482
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
527484

528485
| Document (patho, pos) ->
529486
let typer = Mpipeline.typer_result pipeline in

0 commit comments

Comments
 (0)