Skip to content

Commit 5516e8e

Browse files
panglesdjonludlam
authored andcommitted
Occurrences: Constrain output file name
Similar to source trees: must have `odoc` extension and `occurrences-` prefix Signed-off-by: Paul-Elliot <[email protected]>
1 parent cfd949a commit 5516e8e

File tree

4 files changed

+76
-53
lines changed

4 files changed

+76
-53
lines changed

doc/driver.mld

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -760,7 +760,7 @@ let compiled = compile_all () in
760760
let linked = link_all compiled in
761761
let () = index_generate () in
762762
let _ = js_index () in
763-
let _ = count_occurrences (Fpath.v "occurrences.txt") in
763+
let _ = count_occurrences (Fpath.v "occurrences-odoc_and_deps.odoc") in
764764
generate_all linked
765765
]}
766766

src/odoc/bin/main.ml

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1111,9 +1111,21 @@ module Targets = struct
11111111
end
11121112

11131113
module Occurrences = struct
1114+
let has_occurrences_prefix input =
1115+
input |> Fs.File.basename |> Fs.File.to_string
1116+
|> Astring.String.is_prefix ~affix:"occurrences-"
1117+
1118+
let dst_of_string s =
1119+
let f = Fs.File.of_string s in
1120+
if not (Fs.File.has_ext ".odoc" f) then
1121+
Error (`Msg "Output file must have '.odoc' extension.")
1122+
else if not (has_occurrences_prefix f) then
1123+
Error (`Msg "Output file must be prefixed with 'occurrences-'.")
1124+
else Ok f
1125+
open Or_error
11141126
module Count = struct
11151127
let count directories dst warnings_options include_hidden =
1116-
let dst = Fpath.v dst in
1128+
dst_of_string dst >>= fun dst ->
11171129
Occurrences.count ~dst ~warnings_options directories include_hidden
11181130

11191131
let cmd =
@@ -1150,7 +1162,7 @@ module Occurrences = struct
11501162
"At least one of --file-list or a path to a file must be passed \
11511163
to odoc aggregate-occurrences")
11521164
| _ ->
1153-
let dst = Fpath.v dst in
1165+
dst_of_string dst >>= fun dst ->
11541166
Occurrences.aggregate ~dst ~warnings_options files file_list
11551167

11561168
let cmd =

src/odoc/occurrences.ml

Lines changed: 31 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -172,32 +172,34 @@ let parse_input_files input =
172172
>>= fun files -> Ok (List.concat files)
173173

174174
let aggregate files file_list ~warnings_options:_ ~dst =
175-
parse_input_files file_list >>= fun new_files ->
176-
let files = files @ new_files in
177-
let from_file file : Occtbl.t =
178-
let ic = open_in_bin (Fs.File.to_string file) in
179-
Marshal.from_channel ic
180-
in
181-
let rec loop n f =
182-
if n > 0 then (
183-
f ();
184-
loop (n - 1) f)
185-
else ()
186-
in
187-
let occtbl =
188-
match files with
189-
| [] -> H.create 0
190-
| file1 :: files ->
191-
let acc = from_file file1 in
192-
List.iter
193-
(fun file ->
194-
Occtbl.iter
195-
(fun id { direct; _ } ->
196-
loop direct (fun () -> Occtbl.add acc id))
197-
(from_file file))
198-
files;
199-
acc
200-
in
201-
let oc = open_out_bin (Fs.File.to_string dst) in
202-
Marshal.to_channel oc occtbl [];
203-
Ok ()
175+
try
176+
parse_input_files file_list >>= fun new_files ->
177+
let files = files @ new_files in
178+
let from_file file : Occtbl.t =
179+
let ic = open_in_bin (Fs.File.to_string file) in
180+
Marshal.from_channel ic
181+
in
182+
let rec loop n f =
183+
if n > 0 then (
184+
f ();
185+
loop (n - 1) f)
186+
else ()
187+
in
188+
let occtbl =
189+
match files with
190+
| [] -> H.create 0
191+
| file1 :: files ->
192+
let acc = from_file file1 in
193+
List.iter
194+
(fun file ->
195+
Occtbl.iter
196+
(fun id { direct; _ } ->
197+
loop direct (fun () -> Occtbl.add acc id))
198+
(from_file file))
199+
files;
200+
acc
201+
in
202+
let oc = open_out_bin (Fs.File.to_string dst) in
203+
Marshal.to_channel oc occtbl [];
204+
Ok ()
205+
with Sys_error s -> Error (`Msg s)

test/occurrences/double_wrapped.t/run.t

Lines changed: 30 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -41,11 +41,11 @@ and a hashtable for each compilation unit.
4141
$ mv main__A.odocl main__A
4242
$ mv main__B.odocl main__B
4343
$ mv main__C.odocl main__C
44-
$ odoc count-occurrences -I main -o main.occ
45-
$ odoc count-occurrences -I main__ -o main__.occ
46-
$ odoc count-occurrences -I main__A -o main__A.occ
47-
$ odoc count-occurrences -I main__B -o main__B.occ
48-
$ odoc count-occurrences -I main__C -o main__C.occ
44+
$ odoc count-occurrences -I main -o occurrences-main.odoc
45+
$ odoc count-occurrences -I main__ -o occurrences-main__.odoc
46+
$ odoc count-occurrences -I main__A -o occurrences-main__A.odoc
47+
$ odoc count-occurrences -I main__B -o occurrences-main__B.odoc
48+
$ odoc count-occurrences -I main__C -o occurrences-main__C.odoc
4949

5050
The occurrences_print executable, available only for testing, unmarshal the file
5151
and prints the number of occurrences in a readable format.
@@ -56,18 +56,18 @@ Uses of C are not counted, since the canonical destination (Main.C, generated by
5656
Uses of B.Z are not counted since they go to a hidden module.
5757
Uses of values Y.x and Z.y (in b.ml) are not counted since they come from a "local" module.
5858

59-
$ occurrences_print main.occ | sort
59+
$ occurrences_print occurrences-main.odoc | sort
6060
Main was used directly 0 times and indirectly 2 times
6161
Main.A was used directly 1 times and indirectly 0 times
6262
Main.B was used directly 1 times and indirectly 0 times
6363

64-
$ occurrences_print main__.occ | sort
64+
$ occurrences_print occurrences-main__.odoc | sort
6565

6666
A only uses "persistent" values: one it defines itself.
67-
$ occurrences_print main__A.occ | sort
67+
$ occurrences_print occurrences-main__A.odoc | sort
6868

6969
"Aliased" values are not counted since they become persistent
70-
$ occurrences_print main__B.occ | sort
70+
$ occurrences_print occurrences-main__B.odoc | sort
7171
Main was used directly 0 times and indirectly 7 times
7272
Main.A was used directly 2 times and indirectly 5 times
7373
Main.A.(||>) was used directly 1 times and indirectly 0 times
@@ -76,21 +76,21 @@ A only uses "persistent" values: one it defines itself.
7676
Main.A.x was used directly 1 times and indirectly 0 times
7777

7878
"Aliased" values are not counted since they become persistent
79-
$ occurrences_print main__C.occ | sort
79+
$ occurrences_print occurrences-main__C.odoc | sort
8080
Main was used directly 0 times and indirectly 2 times
8181
Main.A was used directly 1 times and indirectly 1 times
8282
Main.A.x was used directly 1 times and indirectly 0 times
8383

8484
Now we can merge all tables
8585

8686
$ cat > files.map << EOF
87-
> main__A.occ
88-
> main__B.occ
89-
> main__C.occ
87+
> occurrences-main__A.odoc
88+
> occurrences-main__B.odoc
89+
> occurrences-main__C.odoc
9090
> EOF
91-
$ odoc aggregate-occurrences main.occ main__.occ --file-list files.map -o aggregated.txt
91+
$ odoc aggregate-occurrences occurrences-main.odoc occurrences-main__.odoc --file-list files.map -o occurrences-aggregated.odoc
9292

93-
$ occurrences_print aggregated.txt | sort > all_merged
93+
$ occurrences_print occurrences-aggregated.odoc | sort > all_merged
9494
$ cat all_merged
9595
Main was used directly 0 times and indirectly 11 times
9696
Main.A was used directly 4 times and indirectly 6 times
@@ -102,17 +102,26 @@ Now we can merge all tables
102102

103103
Compare with the one created directly with all occurrences:
104104

105-
$ odoc count-occurrences -I . -o occurrences.txt
106-
$ occurrences_print occurrences.txt | sort > directly_all
105+
$ odoc count-occurrences -I . -o occurrences-all.odoc
106+
$ occurrences_print occurrences-all.odoc | sort > directly_all
107107
$ diff all_merged directly_all
108108

109109
We can also include hidden ids:
110110

111-
$ odoc count-occurrences -I main__A -o occurrences.txt --include-hidden
112-
$ occurrences_print occurrences.txt | sort
111+
$ odoc count-occurrences -I main__B -o occurrences-b.odoc --include-hidden
112+
$ occurrences_print occurrences-b.odoc | sort
113+
Main was used directly 0 times and indirectly 7 times
114+
Main.A was used directly 2 times and indirectly 5 times
115+
Main.A.(||>) was used directly 1 times and indirectly 0 times
116+
Main.A.M was used directly 2 times and indirectly 0 times
117+
Main.A.t was used directly 1 times and indirectly 0 times
118+
Main.A.x was used directly 1 times and indirectly 0 times
119+
Main__ was used directly 0 times and indirectly 2 times
120+
Main__.C was used directly 1 times and indirectly 1 times
121+
Main__.C.y was used directly 1 times and indirectly 0 times
113122

114-
$ odoc count-occurrences -I . -o occurrences.txt --include-hidden
115-
$ occurrences_print occurrences.txt | sort
123+
$ odoc count-occurrences -I . -o occurrences-all.odoc --include-hidden
124+
$ occurrences_print occurrences-all.odoc | sort
116125
Main was used directly 0 times and indirectly 11 times
117126
Main.A was used directly 4 times and indirectly 6 times
118127
Main.A.(||>) was used directly 1 times and indirectly 0 times

0 commit comments

Comments
 (0)