@@ -24,6 +24,13 @@ let merge m m' =
24
24
(fun _uid locs locs' -> Some (Lid_set. union locs locs'))
25
25
m m'
26
26
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
+
27
34
(* * Cmt files contains a table of declarations' Uids associated to a typedtree
28
35
fragment. [add_locs_from_fragments] gather locations from these *)
29
36
let gather_locs_from_fragments ~root ~rewrite_root map fragments =
@@ -36,7 +43,7 @@ let gather_locs_from_fragments ~root ~rewrite_root map fragments =
36
43
| Some lid ->
37
44
let lid = to_located_lid lid in
38
45
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
40
47
in
41
48
Shape.Uid.Tbl. fold add_loc fragments map
42
49
@@ -72,8 +79,8 @@ let init_load_path_once ~do_not_use_cmt_loadpath =
72
79
Load_path. (init ~auto_include: no_auto_include ~visible ~hidden );
73
80
loaded := true )
74
81
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 =
77
84
let { Cmt_format. cmt_loadpath;
78
85
cmt_impl_shape;
79
86
cmt_modname;
@@ -89,8 +96,7 @@ let index_of_cmt ~root ~rewrite_root ~build_path ~do_not_use_cmt_loadpath
89
96
init_load_path_once ~do_not_use_cmt_loadpath ~dirs: build_path cmt_loadpath;
90
97
let module Reduce = Shape_reduce. Make (Reduce_conf ) in
91
98
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
94
100
in
95
101
(* The list [cmt_ident_occurrences] associate each ident usage location in the
96
102
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
105
111
| result -> result
106
112
in
107
113
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 )
110
116
| None , _ -> acc)
111
- (defs, Shape.Uid.Map. empty)
112
- cmt_ident_occurrences
117
+ (defs, into.approximated) cmt_ident_occurrences
113
118
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;
116
122
let stats =
117
123
match cmt_sourcefile with
118
- | None -> Stats. empty
124
+ | None -> into.stats
119
125
| Some src -> (
120
126
let rooted_src = with_root ?root src in
121
127
try
122
128
let stats = Unix. stat rooted_src in
123
129
let src = if rewrite_root then rooted_src else src in
124
- Stats. singleton src
130
+ Stats. add src
125
131
{ mtime = stats.st_mtime;
126
132
size = stats.st_size;
127
133
source_digest = cmt_source_digest
128
134
}
129
- with Unix. Unix_error _ -> Stats. empty)
135
+ into.stats
136
+ with Unix. Unix_error _ -> into.stats)
130
137
in
131
- { defs; approximated; cu_shape; stats; root_directory = None }
138
+ { defs; approximated; cu_shape; stats; root_directory = into.root_directory }
132
139
133
140
let merge_index ~store_shapes ~into index =
134
141
let defs = merge index.defs into.defs in
@@ -154,19 +161,16 @@ let from_files ~store_shapes ~output_file ~root ~rewrite_root ~build_path
154
161
@@ fun () ->
155
162
List. fold_left
156
163
(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 ))
170
174
initial_index files
171
175
in
172
176
write ~file: output_file final_index
0 commit comments