Skip to content

Commit 1fe2689

Browse files
committed
Immediately grow the final index instead of building and merging
1 parent 005b42c commit 1fe2689

File tree

1 file changed

+32
-28
lines changed

1 file changed

+32
-28
lines changed

src/ocaml-index/lib/index.ml

Lines changed: 32 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,13 @@ let merge m m' =
2424
(fun _uid locs locs' -> Some (Lid_set.union locs locs'))
2525
m m'
2626

27+
let add_one uid lid map =
28+
Shape.Uid.Map.update uid
29+
(function
30+
| None -> Some (Lid_set.singleton lid)
31+
| Some set -> Some (Lid_set.add lid set))
32+
map
33+
2734
(** Cmt files contains a table of declarations' Uids associated to a typedtree
2835
fragment. [add_locs_from_fragments] gather locations from these *)
2936
let gather_locs_from_fragments ~root ~rewrite_root map fragments =
@@ -36,7 +43,7 @@ let gather_locs_from_fragments ~root ~rewrite_root map fragments =
3643
| Some lid ->
3744
let lid = to_located_lid lid in
3845
let lid = if rewrite_root then add_root ~root lid else lid in
39-
Shape.Uid.Map.add uid (Lid_set.singleton lid) acc
46+
add_one uid lid acc
4047
in
4148
Shape.Uid.Tbl.fold add_loc fragments map
4249

@@ -72,8 +79,8 @@ let init_load_path_once ~do_not_use_cmt_loadpath =
7279
Load_path.(init ~auto_include:no_auto_include ~visible ~hidden);
7380
loaded := true)
7481

75-
let index_of_cmt ~root ~rewrite_root ~build_path ~do_not_use_cmt_loadpath
76-
cmt_infos =
82+
let index_of_cmt ~into ~root ~rewrite_root ~build_path ~do_not_use_cmt_loadpath
83+
~store_shapes cmt_infos =
7784
let { Cmt_format.cmt_loadpath;
7885
cmt_impl_shape;
7986
cmt_modname;
@@ -89,8 +96,7 @@ let index_of_cmt ~root ~rewrite_root ~build_path ~do_not_use_cmt_loadpath
8996
init_load_path_once ~do_not_use_cmt_loadpath ~dirs:build_path cmt_loadpath;
9097
let module Reduce = Shape_reduce.Make (Reduce_conf) in
9198
let defs =
92-
gather_locs_from_fragments ~root ~rewrite_root Shape.Uid.Map.empty
93-
cmt_uid_to_decl
99+
gather_locs_from_fragments ~root ~rewrite_root into.defs cmt_uid_to_decl
94100
in
95101
(* The list [cmt_ident_occurrences] associate each ident usage location in the
96102
module with its (partially) reduced shape. We finish the reduction and
@@ -105,30 +111,31 @@ let index_of_cmt ~root ~rewrite_root ~build_path ~do_not_use_cmt_loadpath
105111
| result -> result
106112
in
107113
match Locate.uid_of_result ~traverse_aliases:false resolved with
108-
| Some uid, false -> (add acc_defs uid (Lid_set.singleton lid), acc_apx)
109-
| Some uid, true -> (acc_defs, add acc_apx uid (Lid_set.singleton lid))
114+
| Some uid, false -> (add_one uid lid acc_defs, acc_apx)
115+
| Some uid, true -> (acc_defs, add_one uid lid acc_apx)
110116
| None, _ -> acc)
111-
(defs, Shape.Uid.Map.empty)
112-
cmt_ident_occurrences
117+
(defs, into.approximated) cmt_ident_occurrences
113118
in
114-
let cu_shape = Hashtbl.create 1 in
115-
Option.iter (Hashtbl.add cu_shape cmt_modname) cmt_impl_shape;
119+
let cu_shape = into.cu_shape in
120+
if store_shapes then
121+
Option.iter (Hashtbl.add cu_shape cmt_modname) cmt_impl_shape;
116122
let stats =
117123
match cmt_sourcefile with
118-
| None -> Stats.empty
124+
| None -> into.stats
119125
| Some src -> (
120126
let rooted_src = with_root ?root src in
121127
try
122128
let stats = Unix.stat rooted_src in
123129
let src = if rewrite_root then rooted_src else src in
124-
Stats.singleton src
130+
Stats.add src
125131
{ mtime = stats.st_mtime;
126132
size = stats.st_size;
127133
source_digest = cmt_source_digest
128134
}
129-
with Unix.Unix_error _ -> Stats.empty)
135+
into.stats
136+
with Unix.Unix_error _ -> into.stats)
130137
in
131-
{ defs; approximated; cu_shape; stats; root_directory = None }
138+
{ defs; approximated; cu_shape; stats; root_directory = into.root_directory }
132139

133140
let merge_index ~store_shapes ~into index =
134141
let defs = merge index.defs into.defs in
@@ -154,19 +161,16 @@ let from_files ~store_shapes ~output_file ~root ~rewrite_root ~build_path
154161
@@ fun () ->
155162
List.fold_left
156163
(fun into file ->
157-
let index =
158-
match Cmt_cache.read file with
159-
| cmt_item ->
160-
index_of_cmt ~root ~rewrite_root ~build_path
161-
~do_not_use_cmt_loadpath cmt_item.cmt_infos
162-
| exception _ -> (
163-
match read ~file with
164-
| Index index -> index
165-
| _ ->
166-
Log.error "Unknown file type: %s" file;
167-
exit 1)
168-
in
169-
merge_index ~store_shapes index ~into)
164+
match Cmt_cache.read file with
165+
| cmt_item ->
166+
index_of_cmt ~into ~root ~rewrite_root ~build_path ~store_shapes
167+
~do_not_use_cmt_loadpath cmt_item.cmt_infos
168+
| exception _ -> (
169+
match read ~file with
170+
| Index index -> merge_index ~store_shapes index ~into
171+
| _ ->
172+
Log.error "Unknown file type: %s" file;
173+
exit 1))
170174
initial_index files
171175
in
172176
write ~file:output_file final_index

0 commit comments

Comments
 (0)