Skip to content

Commit

Permalink
Refactor from_reconstructed
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed May 28, 2020
1 parent bc2c5e2 commit 47ed91a
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 14 deletions.
11 changes: 10 additions & 1 deletion src/analysis/type_enclosing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,9 @@ let from_nodes ~path =
in
List.filter_map ~f:aux path

let from_reconstructed ~get_context ~verbosity env node exprs =
let from_reconstructed ~nodes ~cursor ~verbosity exprs =
let open Browse_raw in
let env, node = Mbrowse.leaf_node nodes in
log ~title:"from_reconstructed" "node = %s\nexprs = [%s]"
(Browse_raw.string_of_node node)
(String.concat ~sep:";" (List.map exprs ~f:(fun l ->
Expand All @@ -58,6 +59,14 @@ let from_reconstructed ~get_context ~verbosity env node exprs =
-> false
| _ -> true
in

let get_context lident =
Context.inspect_browse_tree
~cursor
(Longident.parse lident)
[nodes]
in

let f =
fun {Location. txt = source; loc} ->
let context = get_context source in
Expand Down
5 changes: 2 additions & 3 deletions src/analysis/type_enclosing.mli
Original file line number Diff line number Diff line change
Expand Up @@ -48,9 +48,8 @@ val from_nodes :
typed_enclosings

val from_reconstructed :
get_context:(string -> Context.t option) ->
nodes:(Env.t * Browse_raw.node) list ->
cursor:Lexing.position ->
verbosity:int ->
Env.t ->
Mbrowse.node ->
string Location.loc list ->
typed_enclosings
13 changes: 3 additions & 10 deletions src/frontend/query_commands.ml
Original file line number Diff line number Diff line change
Expand Up @@ -298,17 +298,10 @@ let dispatch pipeline (type a) : a Query_protocol.t -> a =
`List lst
)
in
let env, node = Mbrowse.leaf_node (Mtyper.node_at typer pos) in
let get_context lident =
Context.inspect_browse_tree
~cursor:pos
(Longident.parse lident)
[Mtyper.node_at typer pos]
in
let nodes = Mtyper.node_at typer pos in
let small_enclosings =
Type_enclosing.from_reconstructed
~get_context ~verbosity
env node exprs
Type_enclosing.from_reconstructed exprs
~nodes ~cursor:pos ~verbosity
in
Logger.log ~section:Type_enclosing.log_section ~title:"small enclosing" "%a"
Logger.fmt (fun fmt ->
Expand Down

0 comments on commit 47ed91a

Please sign in to comment.