@@ -424,7 +424,7 @@ let references
424424 match Document. kind doc with
425425 | `Other -> Fiber. return None
426426 | `Merlin doc ->
427- let * locs , synced =
427+ let * occurrences , synced =
428428 Document.Merlin. dispatch_exn
429429 ~name: " occurrences"
430430 doc
@@ -445,20 +445,22 @@ let references
445445 | _ -> Fiber. return ()
446446 in
447447 Some
448- (List. map locs ~f: (fun loc ->
449- let range = Range. of_loc loc in
450- let uri =
451- match loc.loc_start.pos_fname with
452- | "" -> uri
453- | path -> Uri. of_path path
454- in
455- Log. log ~section: " debug" (fun () ->
456- Log. msg
457- " merlin returned fname %a"
458- [ " pos_fname" , `String loc.loc_start.pos_fname
459- ; " uri" , `String (Uri. to_string uri)
460- ]);
461- { Location. uri; range }))
448+ (List. filter_map occurrences ~f: (function
449+ | { loc = _ ; is_stale = true } -> None
450+ | { loc; is_stale = false } ->
451+ let range = Range. of_loc loc in
452+ let uri =
453+ match loc.loc_start.pos_fname with
454+ | "" -> uri
455+ | path -> Uri. of_path path
456+ in
457+ Log. log ~section: " debug" (fun () ->
458+ Log. msg
459+ " merlin returned fname %a"
460+ [ " pos_fname" , `String loc.loc_start.pos_fname
461+ ; " uri" , `String (Uri. to_string uri)
462+ ]);
463+ Some { Location. uri; range }))
462464;;
463465
464466let highlight
@@ -470,14 +472,15 @@ let highlight
470472 match Document. kind doc with
471473 | `Other -> Fiber. return None
472474 | `Merlin m ->
473- let + locs , _synced =
475+ let + occurrences , _synced =
474476 Document.Merlin. dispatch_exn
475477 ~name: " occurrences"
476478 m
477479 (Occurrences (`Ident_at (Position. logical position), `Buffer ))
478480 in
479481 let lsp_locs =
480- List. filter_map locs ~f: (fun loc ->
482+ List. filter_map occurrences ~f: (fun (occurrence : Query_protocol.occurrence ) ->
483+ let loc = occurrence.loc in
481484 let range = Range. of_loc loc in
482485 (* filter out multi-line ranges, since those are very noisy and happen
483486 a lot with certain PPXs *)
@@ -660,16 +663,19 @@ let on_request
660663 match Document. kind doc with
661664 | `Other -> Fiber. return None
662665 | `Merlin doc ->
663- let + locs , _synced =
666+ let + occurrences , _synced =
664667 Document.Merlin. dispatch_exn
665668 ~name: " occurrences"
666669 doc
667670 (Occurrences (`Ident_at (Position. logical position), `Buffer ))
668671 in
669672 let loc =
670- List. find_opt locs ~f: (fun loc ->
673+ List. find_map occurrences ~f: (fun (occurrence : Query_protocol.occurrence ) ->
674+ let loc = occurrence.loc in
671675 let range = Range. of_loc loc in
672- Position. compare_inclusion position range = `Inside )
676+ match occurrence.is_stale, Position. compare_inclusion position range with
677+ | false , `Inside -> Some loc
678+ | true , _ | _ , `Outside _ -> None )
673679 in
674680 Option. map loc ~f: Range. of_loc)
675681 ()
0 commit comments