Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
32 changes: 11 additions & 21 deletions src/analysis/inlay_hints.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@ let { Logger.log } = Logger.for_section "inlay-hints"

module Iterator = Ocaml_typing.Tast_iterator

let is_ghost_location avoid_ghost loc = loc.Location.loc_ghost && avoid_ghost

let pattern_has_constraint (type a) (pattern : a Typedtree.general_pattern) =
List.exists
~f:(fun (extra, _, _) ->
Expand All @@ -16,8 +14,8 @@ let pattern_has_constraint (type a) (pattern : a Typedtree.general_pattern) =
| Typedtree.Tpat_unpack -> false)
pattern.pat_extra

let structure_iterator hint_let_binding hint_pattern_binding
avoid_ghost_location typedtree range callback =
let structure_iterator hint_let_binding hint_pattern_binding typedtree range
callback =
let case_iterator hint_lhs (iterator : Iterator.iterator) case =
let () = log ~title:"case" "on case" in
let () = if hint_lhs then iterator.pat iterator case.Typedtree.c_lhs in
Expand Down Expand Up @@ -77,10 +75,6 @@ let structure_iterator hint_let_binding hint_pattern_binding
let () = log ~title:"expression" "on function" in
let () = iterator.pat iterator vb_pat in
iterator.expr iterator body
| _ when is_ghost_location avoid_ghost_location expr.exp_loc ->
(* Stop iterating when we see a ghost location to avoid
annotating generated code *)
log ~title:"ghost" "ghost-location found"
| _ -> Iterator.default_iterator.expr iterator expr
in

Expand All @@ -92,10 +86,6 @@ let structure_iterator hint_let_binding hint_pattern_binding
List.iter
~f:(fun binding -> expr_iterator iterator binding.Typedtree.vb_expr)
bindings
| _ when is_ghost_location avoid_ghost_location item.str_loc ->
(* Stop iterating when we see a ghost location to avoid
annotating generated code *)
log ~title:"ghost" "ghost-location found"
| _ -> Iterator.default_iterator.structure_item iterator item
in

Expand All @@ -117,14 +107,14 @@ let structure_iterator hint_let_binding hint_pattern_binding
callback pattern.pat_env pattern.pat_type pattern.pat_loc
| _ -> log ~title:"pattern" "not a var"
in

let iterator =
{ Ocaml_typing.Tast_iterator.default_iterator with
expr = expr_iterator;
structure_item = structure_item_iterator;
pat = pattern_iterator;
value_binding = value_binding_iterator true
}
Ast_iterators.iter_only_visible
{ Ocaml_typing.Tast_iterator.default_iterator with
expr = expr_iterator;
structure_item = structure_item_iterator;
pat = pattern_iterator;
value_binding = value_binding_iterator true
}
in
iterator.structure iterator typedtree

Expand All @@ -151,8 +141,8 @@ let of_structure ~hint_let_binding ~hint_pattern_binding ~avoid_ghost_location
let range = (start, stop) in
let hints = ref [] in
let () =
structure_iterator hint_let_binding hint_pattern_binding
avoid_ghost_location structure range (fun env typ loc ->
structure_iterator hint_let_binding hint_pattern_binding structure range
(fun env typ loc ->
let () =
log ~title:"hint" "Find hint %a" Logger.fmt (fun fmt ->
Format.fprintf fmt "%s - %a"
Expand Down
16 changes: 8 additions & 8 deletions tests/test-dirs/inlay-hint/samples.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Optional argument

$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location true \
> -filename inlay.ml <<EOF
> let f ?x () = x ()
> EOF
Expand All @@ -20,7 +20,7 @@ Optional argument

Optional argument with value

$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location true \
> -filename inlay.ml <<EOF
> let f ?(x = 1) () = x
> EOF
Expand All @@ -40,7 +40,7 @@ Optional argument with value

Labeled argument

$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location true \
> -filename inlay.ml <<EOF
> let f ~x = x + 1
> EOF
Expand All @@ -60,7 +60,7 @@ Labeled argument

Case argument

$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 2:26 -avoid-ghost-location true \
> -filename inlay.ml <<EOF
> let f (Some x) = x + 1
> EOF
Expand All @@ -80,7 +80,7 @@ Case argument

Pattern variables without pattern-binding hint

$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location true \
> -filename inlay.ml <<EOF
> let f x =
> match x with
Expand All @@ -103,7 +103,7 @@ Pattern variables without pattern-binding hint

Pattern variables with pattern-binding hint

$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location true \
> -pattern-binding true \
> -filename inlay.ml <<EOF
> let f x =
Expand Down Expand Up @@ -135,7 +135,7 @@ Pattern variables with pattern-binding hint

Let bindings without let hinting

$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location true \
> -let-binding false \
> -filename inlay.ml <<EOF
> let f () = let y = 0 in y
Expand All @@ -149,7 +149,7 @@ Let bindings without let hinting

Let bindings with let hinting

$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location false \
$ $MERLIN single inlay-hints -start 1:0 -end 4:26 -avoid-ghost-location true \
> -let-binding true \
> -filename inlay.ml <<EOF
> let f () = let y = 0 in y
Expand Down
Loading