@@ -4,7 +4,53 @@ module Lid_set = Index_format.Lid_set
4
4
let { Logger. log } = Logger. for_section " occurrences"
5
5
6
6
type t =
7
- { locs : Warnings .loc list ; status : Query_protocol .occurrences_status }
7
+ { occurrences : Query_protocol .occurrence list ;
8
+ status : Query_protocol .occurrences_status
9
+ }
10
+
11
+ module Staleness = struct
12
+ type t = Stale | Fresh
13
+
14
+ let is_stale = function
15
+ | Stale -> true
16
+ | Fresh -> false
17
+ end
18
+
19
+ module Occurrence_set : sig
20
+ type t
21
+
22
+ val empty : t
23
+
24
+ (* * Filter an [Lid_set.t]. [Lid.t]s that are kept must be assigned a staleness *)
25
+ val of_filtered_lid_set :
26
+ Lid_set .t -> f :(Index_format .Lid .t -> Staleness .t option ) -> t
27
+
28
+ val to_list : t -> (Index_format.Lid .t * Staleness .t ) list
29
+ val union : t -> t -> t
30
+ end = struct
31
+ module Lid_map = Map. Make (Index_format. Lid )
32
+
33
+ type t = Staleness .t Lid_map .t
34
+
35
+ let empty = Lid_map. empty
36
+ let to_list = Lid_map. to_list
37
+
38
+ let of_filtered_lid_set lid_set ~f :get_staleness =
39
+ let maybe_add_lid lid acc =
40
+ match get_staleness lid with
41
+ | Some staleness -> Lid_map. add lid staleness acc
42
+ | None -> acc
43
+ in
44
+ Lid_set. fold maybe_add_lid lid_set empty
45
+
46
+ let either_fresh a b =
47
+ let open Staleness in
48
+ match (a, b) with
49
+ | Fresh , _ | _ , Fresh -> Fresh
50
+ | Stale , Stale -> Stale
51
+
52
+ let union a b = Lid_map. union (fun _ a b -> Some (either_fresh a b)) a b
53
+ end
8
54
9
55
let () = Mtyper. set_index_items Index_occurrences. items
10
56
@@ -116,7 +162,8 @@ let get_buffer_locs result uid =
116
162
if Shape.Uid. equal uid uid' then Lid_set. add loc acc else acc)
117
163
(Mtyper. get_index result) Lid_set. empty
118
164
119
- let get_external_locs ~(config : Mconfig.t ) ~current_buffer_path uid =
165
+ let get_external_locs ~(config : Mconfig.t ) ~current_buffer_path uid :
166
+ (Occurrence_set. t * Std.String.Set. t ) list =
120
167
let title = " get_external_locs" in
121
168
List. filter_map config.merlin.index_files ~f: (fun index_file ->
122
169
log ~title " Lookin for occurrences of %a in index %s" Logger. fmt
@@ -133,8 +180,7 @@ let get_external_locs ~(config : Mconfig.t) ~current_buffer_path uid =
133
180
in
134
181
Option. map external_locs ~f: (fun (index , locs ) ->
135
182
let stats = Stat_check. create ~cache_size: 128 index in
136
- ( Lid_set. filter
137
- (fun { loc; _ } ->
183
+ ( Occurrence_set. of_filtered_lid_set locs ~f: (fun { loc; _ } ->
138
184
(* We ignore external results that concern the current buffer *)
139
185
let file_rel_to_root =
140
186
loc.Location. loc_start.Lexing. pos_fname
@@ -147,15 +193,21 @@ let get_external_locs ~(config : Mconfig.t) ~current_buffer_path uid =
147
193
in
148
194
let file = Misc. canonicalize_filename file_uncanon in
149
195
let buf = Misc. canonicalize_filename buf_uncanon in
150
- if String. equal file buf then false
196
+ if String. equal file buf then None
151
197
else begin
152
198
(* We ignore external results if their source was modified *)
153
- let check = Stat_check. check stats ~file: file_rel_to_root in
154
- if not check then
155
- log ~title " File %s might be out-of-sync." file;
156
- check
157
- end )
158
- locs,
199
+ let is_fresh =
200
+ Stat_check. check stats ~file: file_rel_to_root
201
+ in
202
+ if not is_fresh then
203
+ log ~title: " locs_of" " File %s might be out-of-sync." file;
204
+ let staleness : Staleness.t =
205
+ match is_fresh with
206
+ | true -> Fresh
207
+ | false -> Stale
208
+ in
209
+ Some staleness
210
+ end ),
159
211
Stat_check. get_outdated_files stats )))
160
212
161
213
let lookup_related_uids_in_indexes ~(config : Mconfig.t ) uid =
@@ -255,7 +307,10 @@ let locs_of ~config ~env ~typer_result ~pos ~scope path =
255
307
(fun fmt -> Location. print_loc fmt def_loc);
256
308
log ~title: " locs_of" " Indexing current buffer" ;
257
309
let buffer_locs = get_buffer_locs typer_result def_uid in
258
- let external_locs =
310
+ let buffer_occurrences =
311
+ Occurrence_set. of_filtered_lid_set buffer_locs ~f: (fun _ -> Some Fresh )
312
+ in
313
+ let external_occurrences =
259
314
if scope = `Buffer then []
260
315
else
261
316
let name =
@@ -266,47 +321,51 @@ let locs_of ~config ~env ~typer_result ~pos ~scope path =
266
321
(def_uid :: additional_uids)
267
322
~f: (get_external_locs ~config ~current_buffer_path )
268
323
in
269
- let external_locs , out_of_sync_files =
324
+ let external_occurrences , out_of_sync_files =
270
325
List. fold_left
271
- ~init: (Lid_set . empty, String.Set. empty)
326
+ ~init: (Occurrence_set . empty, String.Set. empty)
272
327
~f: (fun (acc_locs , acc_files ) (locs , files ) ->
273
- (Lid_set . union acc_locs locs, String.Set. union acc_files files))
274
- external_locs
328
+ (Occurrence_set . union acc_locs locs, String.Set. union acc_files files))
329
+ external_occurrences
275
330
in
276
- let locs = Lid_set. union buffer_locs external_locs in
277
- (* Some of the paths may have redundant `.`s or `..`s in them. Although canonicalizing
278
- is not necessary for correctness, it makes the output a bit nicer. *)
279
- let canonicalize_file_in_loc ({ txt; loc } : 'a Location.loc ) :
280
- 'a Location. loc =
281
- let file =
282
- Misc. canonicalize_filename ?cwd:config.merlin.source_root
283
- loc.loc_start.pos_fname
284
- in
285
- { txt; loc = set_fname ~file loc }
331
+ let occurrences =
332
+ Occurrence_set. union buffer_occurrences external_occurrences
286
333
in
287
- let locs = Lid_set. map canonicalize_file_in_loc locs in
288
- let locs =
289
- log ~title: " occurrences" " Found %i locs" (Lid_set. cardinal locs);
290
- Lid_set. elements locs
291
- |> List. filter_map ~f: (fun { Location. txt; loc } ->
292
- let lid = try Longident. head txt with _ -> " not flat lid" in
293
- log ~title: " occurrences" " Found occ: %s %a" lid Logger. fmt
294
- (Fun. flip Location. print_loc loc);
295
- let loc = last_loc loc txt in
296
- let fname = loc.Location. loc_start.Lexing. pos_fname in
297
- if not (Filename. is_relative fname) then Some loc
298
- else
299
- match config.merlin.source_root with
300
- | Some path ->
301
- let file = Filename. concat path loc.loc_start.pos_fname in
302
- Some (set_fname ~file loc)
303
- | None -> begin
304
- match Locate. find_source ~config loc fname with
305
- | `Found (file , _ ) -> Some (set_fname ~file loc)
306
- | `File_not_found msg ->
307
- log ~title: " occurrences" " %s" msg;
308
- None
309
- end )
334
+ let occurrences = Occurrence_set. to_list occurrences in
335
+ log ~title: " occurrences" " Found %i locs" (List. length occurrences);
336
+ let occurrences =
337
+ List. filter_map occurrences
338
+ ~f: (fun (({ txt; loc } : _ Location.loc ), staleness ) ->
339
+ (* Canonoicalize filenames. Some of the paths may have redundant `.`s or `..`s in
340
+ them. Although canonicalizing is not necessary for correctness, it makes the
341
+ output a bit nicer. *)
342
+ let file =
343
+ Misc. canonicalize_filename ?cwd:config.merlin.source_root
344
+ loc.loc_start.pos_fname
345
+ in
346
+ let loc = set_fname ~file loc in
347
+ let lid = try Longident. head txt with _ -> " not flat lid" in
348
+ log ~title: " occurrences" " Found occ: %s %a" lid Logger. fmt
349
+ (Fun. flip Location. print_loc loc);
350
+ let loc = last_loc loc txt in
351
+ let fname = loc.Location. loc_start.Lexing. pos_fname in
352
+ let loc =
353
+ if not (Filename. is_relative fname) then Some loc
354
+ else
355
+ match config.merlin.source_root with
356
+ | Some path ->
357
+ let file = Filename. concat path loc.loc_start.pos_fname in
358
+ Some (set_fname ~file loc)
359
+ | None -> begin
360
+ match Locate. find_source ~config loc fname with
361
+ | `Found (file , _ ) -> Some (set_fname ~file loc)
362
+ | `File_not_found msg ->
363
+ log ~title: " occurrences" " %s" msg;
364
+ None
365
+ end
366
+ in
367
+ Option. map loc ~f: (fun loc : Query_protocol. occurrence ->
368
+ { loc; is_stale = Staleness. is_stale staleness }))
310
369
in
311
370
let def_uid_is_in_current_unit =
312
371
let uid_comp_unit = comp_unit_of_uid def_uid in
@@ -319,8 +378,11 @@ let locs_of ~config ~env ~typer_result ~pos ~scope path =
319
378
| _ , [] -> `Included
320
379
| _ , l -> `Out_of_sync l
321
380
in
322
- if not def_uid_is_in_current_unit then { locs ; status }
381
+ if not def_uid_is_in_current_unit then { occurrences ; status }
323
382
else
324
- let locs = set_fname ~file: current_buffer_path def_loc :: locs in
325
- { locs; status }
326
- | None -> { locs = [] ; status = `No_def }
383
+ let definition_occurrence : Query_protocol.occurrence =
384
+ { loc = set_fname ~file: current_buffer_path def_loc; is_stale = false }
385
+ in
386
+ let occurrences = definition_occurrence :: occurrences in
387
+ { occurrences; status }
388
+ | None -> { occurrences = [] ; status = `No_def }
0 commit comments