From a8fa9db9ce3ded131f32d7e97090e876fc4f50dd Mon Sep 17 00:00:00 2001 From: Thomas Refis Date: Tue, 13 Jul 2021 19:09:13 +0200 Subject: [PATCH] refactor_open: move to its own file --- src/analysis/refactor_open.ml | 48 ++++++++++++++++++++++++++++++++++ src/analysis/refactor_open.mli | 6 +++++ src/frontend/query_commands.ml | 45 +------------------------------ 3 files changed, 55 insertions(+), 44 deletions(-) create mode 100644 src/analysis/refactor_open.ml create mode 100644 src/analysis/refactor_open.mli diff --git a/src/analysis/refactor_open.ml b/src/analysis/refactor_open.ml new file mode 100644 index 0000000000..dbebd34525 --- /dev/null +++ b/src/analysis/refactor_open.ml @@ -0,0 +1,48 @@ +open Std + +let qual_or_unqual_path mode leftmost_ident path p = + let rec aux acc (p : Path.t) = + match p with + | Pident ident -> + Ident.name ident :: acc + | Pdot (path', s) when + mode = `Unqualify && Path.same path path' -> + s :: acc + | Pdot (path', s) when + mode = `Qualify && s = leftmost_ident -> + s :: acc + | Pdot (path', s) -> + aux (s :: acc) path' + | _ -> raise Not_found + in + aux [] p |> String.concat ~sep:"." + +(* checks if the (un)qualified longident has a different length, i.e., has changed + + XXX(Ulugbek): computes longident length using [loc_start] and [loc_end], hence + it doesn't work for multiline longidents because we can't compute their length *) +let same_longident new_lident { Location. loc_start; loc_end; _ } = + let old_longident_len = Lexing.column loc_end - Lexing.column loc_start in + loc_start.Lexing.pos_lnum = loc_end.Lexing.pos_lnum && + String.length new_lident = old_longident_len + + +let get_rewrites ~mode typer pos = + match Mbrowse.select_open_node (Mtyper.node_at typer pos) with + | None | Some (_, _, []) -> [] + | Some (orig_path, longident, ((_, node) :: _)) -> + let paths = + Browse_tree.all_occurrences_of_prefix ~strict_prefix:true orig_path node + in + let paths = List.concat_map ~f:snd paths in + let leftmost_ident = Longident.flatten longident |> List.hd in + List.filter_map paths ~f:(fun {Location. txt = path; loc} -> + if loc.Location.loc_ghost || Location_aux.compare_pos pos loc > 0 then + None + else + match qual_or_unqual_path mode leftmost_ident orig_path path with + | s when same_longident s loc -> None + | s -> Some (s, loc) + | exception Not_found -> None + ) + |> List.sort_uniq ~cmp:(fun (_,l1) (_,l2) -> Location_aux.compare l1 l2) diff --git a/src/analysis/refactor_open.mli b/src/analysis/refactor_open.mli new file mode 100644 index 0000000000..9a4f2cb43a --- /dev/null +++ b/src/analysis/refactor_open.mli @@ -0,0 +1,6 @@ + +val get_rewrites + : mode:[> `Qualify | `Unqualify ] + -> Mtyper.result + -> Lexing.position + -> (string * Location.t) list diff --git a/src/frontend/query_commands.ml b/src/frontend/query_commands.ml index 527540dee1..12636ea2d4 100644 --- a/src/frontend/query_commands.ml +++ b/src/frontend/query_commands.ml @@ -480,50 +480,7 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a = | Refactor_open (mode, pos) -> let typer = Mpipeline.typer_result pipeline in let pos = Mpipeline.get_lexing_pos pipeline pos in - begin match Mbrowse.select_open_node (Mtyper.node_at typer pos) with - | None | Some (_, _, []) -> [] - | Some (path, longident, ((_, node) :: _)) -> - let paths = - Browse_tree.all_occurrences_of_prefix ~strict_prefix:true path node in - let paths = List.concat_map ~f:snd paths in - let leftmost_ident = Longident.flatten longident |> List.hd in - let qual_or_unqual_path p = - let rec aux acc (p : Path.t) = - match p with - | Pident ident -> - Ident.name ident :: acc - | Pdot (path', s) when - mode = `Unqualify && Path.same path path' -> - s :: acc - | Pdot (path', s) when - mode = `Qualify && s = leftmost_ident -> - s :: acc - | Pdot (path', s) -> - aux (s :: acc) path' - | _ -> raise Not_found - in - aux [] p |> String.concat ~sep:"." - in - (* checks if the (un)qualified longident has a different length, i.e., has changed - - XXX(Ulugbek): computes longident length using [loc_start] and [loc_end], hence - it doesn't work for multiline longidents because we can't compute their length *) - let same_longident new_lident { Location. loc_start; loc_end; _ } = - let old_longident_len = Lexing.column loc_end - Lexing.column loc_start in - loc_start.Lexing.pos_lnum = loc_end.Lexing.pos_lnum && - String.length new_lident = old_longident_len - in - List.filter_map paths ~f:(fun {Location. txt = path; loc} -> - if not loc.Location.loc_ghost && - Location_aux.compare_pos pos loc <= 0 then - match qual_or_unqual_path path with - | s when same_longident s loc -> None - | s -> Some (s, loc) - | exception Not_found -> None - else None - ) - |> List.sort_uniq ~cmp:(fun (_,l1) (_,l2) -> Location_aux.compare l1 l2) - end + Refactor_open.get_rewrites ~mode typer pos | Document (patho, pos) -> let typer = Mpipeline.typer_result pipeline in