Skip to content

Commit

Permalink
More logging
Browse files Browse the repository at this point in the history
  • Loading branch information
voodoos committed Apr 9, 2020
1 parent 7dad443 commit ed294fa
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 2 deletions.
6 changes: 5 additions & 1 deletion src/analysis/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -125,6 +125,10 @@ let inspect_expression ~cursor ~lid e : t =
Expr

let inspect_browse_tree ~cursor lid browse : t option =
log ~title:"inspect_context" "current node is: [%s]"
(String.concat ~sep:"|" (
List.map ~f:(Mbrowse.print ()) browse
));
match Mbrowse.enclosing cursor browse with
| [] ->
log ~title:"inspect_context"
Expand All @@ -133,7 +137,7 @@ let inspect_browse_tree ~cursor lid browse : t option =
| enclosings ->
let open Browse_raw in
let node = Browse_tree.of_browse enclosings in
log ~title:"inspect_context" "current node is: %s"
log ~title:"inspect_context" "current enclosing node is: %s"
(string_of_node node.Browse_tree.t_node);
match node.Browse_tree.t_node with
| Pattern p -> inspect_pattern ~cursor ~lid p
Expand Down
6 changes: 5 additions & 1 deletion src/kernel/mtyper.ml
Original file line number Diff line number Diff line change
Expand Up @@ -187,6 +187,7 @@ let get_typedtree t =

let node_at ?(skip_recovered=false) t pos_cursor =
let node = Mbrowse.of_typedtree (get_typedtree t) in
log ~title:"node_at" "Node: %s" (Mbrowse.print () node);
let rec select = function
(* If recovery happens, the incorrect node is kept and a recovery node
is introduced, so the node to check for recovery is the second one. *)
Expand All @@ -197,4 +198,7 @@ let node_at ?(skip_recovered=false) t pos_cursor =
match Mbrowse.deepest_before pos_cursor [node] with
| [] -> [get_env t, Browse_raw.Dummy]
| path when skip_recovered -> select path
| path -> path
| path ->
log ~title:"node_at" "Deepest before %s"
(Mbrowse.print () path);
path

0 comments on commit ed294fa

Please sign in to comment.