Skip to content

Commit b527639

Browse files
panglesdjonludlam
authored andcommitted
Count-occurrences: consistency and driver support
Made the count-occurrences command a bit more consistent: - output names are now `name.odoc-occurrences` instead of `occurrences-name.odoc` (similar to "index" artifacts) - input dirs are positional arguments instead of `-I` (which are for search path). Also, implemented support for counting occurrences, and passing that to the search indexing, in the reference driver.
1 parent 8f15caa commit b527639

File tree

8 files changed

+69
-54
lines changed

8 files changed

+69
-54
lines changed

src/driver/compile.ml

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -225,7 +225,7 @@ let sherlodoc_index_one ~output_dir (index : Odoc_unit.index) =
225225
Sherlodoc.index ~format:`js ~inputs ~dst ();
226226
rel_path
227227

228-
let html_generate output_dir linked =
228+
let html_generate ~occurrence_file output_dir linked =
229229
let tbl = Hashtbl.create 10 in
230230
let _ = OS.Dir.create output_dir |> Result.get_ok in
231231
Sherlodoc.js Fpath.(output_dir // Sherlodoc.js_file);
@@ -235,7 +235,10 @@ let html_generate output_dir linked =
235235
({ pkg_args = { pages; libs }; output_file; json; search_dir = _ } as
236236
index :
237237
Odoc_unit.index) =
238-
let () = Odoc.compile_index ~json ~output_file ~libs ~docs:pages () in
238+
let () =
239+
Odoc.compile_index ~json ~occurrence_file ~output_file ~libs ~docs:pages
240+
()
241+
in
239242
sherlodoc_index_one ~output_dir index
240243
in
241244
match Hashtbl.find_opt tbl index.output_file with

src/driver/compile.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,4 +18,4 @@ type linked
1818

1919
val link : compiled list -> linked list
2020

21-
val html_generate : Fpath.t -> linked list -> unit
21+
val html_generate : occurrence_file:Fpath.t -> Fpath.t -> linked list -> unit

src/driver/odoc.ml

Lines changed: 16 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -138,13 +138,20 @@ let link ?(ignore_output = false) ~input_file:file ?output_file ~includes ~docs
138138
Cmd_outputs.(
139139
add_prefixed_output cmd link_output (Fpath.to_string file) lines)
140140

141-
let compile_index ?(ignore_output = false) ~output_file ~json ~docs ~libs () =
141+
let compile_index ?(ignore_output = false) ~output_file ?occurrence_file ~json
142+
~docs ~libs () =
142143
let docs = doc_args docs in
143144
let libs = lib_args libs in
144145
let json = if json then Cmd.v "--json" else Cmd.empty in
146+
let occ =
147+
match occurrence_file with
148+
| None -> Cmd.empty
149+
| Some f -> Cmd.(v "--occurrences" % p f)
150+
in
145151
let cmd =
146152
Cmd.(
147-
!odoc % "compile-index" %% json %% v "-o" % p output_file %% docs %% libs)
153+
!odoc % "compile-index" %% json %% v "-o" % p output_file %% docs %% libs
154+
%% occ)
148155
in
149156
let desc =
150157
Printf.sprintf "Generating index for %s" (Fpath.to_string output_file)
@@ -212,11 +219,15 @@ let support_files path =
212219
let desc = "Generating support files" in
213220
Cmd_outputs.submit desc cmd None
214221

215-
let count_occurrences output =
222+
let count_occurrences ~input ~output =
216223
let open Cmd in
217-
let cmd = !odoc % "count-occurrences" % "-I" % "." % "-o" % p output in
224+
let input = Cmd.of_values Fpath.to_string input in
225+
let output_c = v "-o" % p output in
226+
let cmd = !odoc % "count-occurrences" %% input %% output_c in
218227
let desc = "Counting occurrences" in
219-
Cmd_outputs.submit desc cmd None
228+
let lines = Cmd_outputs.submit desc cmd None in
229+
Cmd_outputs.(
230+
add_prefixed_output cmd generate_output (Fpath.to_string output) lines)
220231

221232
let source_tree ?(ignore_output = false) ~parent ~output file =
222233
let open Cmd in

src/driver/odoc.mli

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ val link :
4242
val compile_index :
4343
?ignore_output:bool ->
4444
output_file:Fpath.t ->
45+
?occurrence_file:Fpath.t ->
4546
json:bool ->
4647
docs:(string * Fpath.t) list ->
4748
libs:(string * Fpath.t) list ->
@@ -76,6 +77,6 @@ val html_generate_source :
7677

7778
val support_files : Fpath.t -> string list
7879

79-
val count_occurrences : Fpath.t -> string list
80+
val count_occurrences : input:Fpath.t list -> output:Fpath.t -> unit
8081
val source_tree :
8182
?ignore_output:bool -> parent:string -> output:Fpath.t -> Fpath.t -> unit

src/driver/odoc_driver.ml

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -577,7 +577,14 @@ let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
577577
all
578578
in
579579
let linked = Compile.link compiled in
580-
let () = Compile.html_generate html_dir linked in
580+
let occurrence_file =
581+
let output =
582+
Fpath.( / ) odoc_dir "occurrences-all.odoc-occurrences"
583+
in
584+
let () = Odoc.count_occurrences ~input:[ odoc_dir ] ~output in
585+
output
586+
in
587+
let () = Compile.html_generate ~occurrence_file html_dir linked in
581588
let _ = Odoc.support_files html_dir in
582589
())
583590
(fun () -> render_stats env nb_workers)

src/odoc/bin/main.ml

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1438,16 +1438,10 @@ end
14381438
module Occurrences = struct
14391439
open Or_error
14401440

1441-
let has_occurrences_prefix input =
1442-
input |> Fs.File.basename |> Fs.File.to_string
1443-
|> Astring.String.is_prefix ~affix:"occurrences-"
1444-
14451441
let dst_of_string s =
14461442
let f = Fs.File.of_string s in
1447-
if not (Fs.File.has_ext ".odoc" f) then
1448-
Error (`Msg "Output file must have '.odoc' extension.")
1449-
else if not (has_occurrences_prefix f) then
1450-
Error (`Msg "Output file must be prefixed with 'occurrences-'.")
1443+
if not (Fs.File.has_ext ".odoc-occurrences" f) then
1444+
Error (`Msg "Output file must have '.odoc-occurrences' extension.")
14511445
else Ok f
14521446

14531447
module Count = struct
@@ -1467,10 +1461,19 @@ module Occurrences = struct
14671461
let doc = "Include hidden identifiers in the table" in
14681462
Arg.(value & flag & info ~docs ~doc [ "include-hidden" ])
14691463
in
1464+
let input =
1465+
let doc =
1466+
"Directories to recursively traverse, agregating occurrences from \
1467+
$(i,impl-*.odocl) files. Can be present several times."
1468+
in
1469+
Arg.(
1470+
value
1471+
& pos_all (convert_directory ()) []
1472+
& info ~docs ~docv:"DIR" ~doc [])
1473+
in
14701474
Term.(
14711475
const handle_error
1472-
$ (const count $ odoc_file_directories $ dst $ warnings_options
1473-
$ include_hidden))
1476+
$ (const count $ input $ dst $ warnings_options $ include_hidden))
14741477

14751478
let info ~docs =
14761479
let doc =

src/odoc/occurrences.ml

Lines changed: 2 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,8 @@
11
open Or_error
2-
3-
(* Copied from ocaml 5.0 String module *)
4-
let string_starts_with ~prefix s =
5-
let open String in
6-
let len_s = length s and len_pre = length prefix in
7-
let rec aux i =
8-
if i = len_pre then true
9-
else if unsafe_get s i <> unsafe_get prefix i then false
10-
else aux (i + 1)
11-
in
12-
len_s >= len_pre && aux 0
2+
open Astring
133

144
let handle_file file ~f =
15-
if string_starts_with ~prefix:"impl-" (Fpath.filename file) then
5+
if String.is_prefix ~affix:"impl-" (Fpath.filename file) then
166
Odoc_file.load file |> function
177
| Error _ as e -> e
188
| Ok unit' -> (

test/occurrences/double_wrapped.t/run.t

Lines changed: 22 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -50,11 +50,11 @@ and a hashtable for each compilation unit.
5050
$ mv impl-main__A.odocl main__A
5151
$ mv impl-main__B.odocl main__B
5252
$ mv impl-main__C.odocl main__C
53-
$ odoc count-occurrences -I main -o occurrences-main.odoc
54-
$ odoc count-occurrences -I main__ -o occurrences-main__.odoc
55-
$ odoc count-occurrences -I main__A -o occurrences-main__A.odoc
56-
$ odoc count-occurrences -I main__B -o occurrences-main__B.odoc
57-
$ odoc count-occurrences -I main__C -o occurrences-main__C.odoc
53+
$ odoc count-occurrences main -o main.odoc-occurrences
54+
$ odoc count-occurrences main__ -o main__.odoc-occurrences
55+
$ odoc count-occurrences main__A -o main__A.odoc-occurrences
56+
$ odoc count-occurrences main__B -o main__B.odoc-occurrences
57+
$ odoc count-occurrences main__C -o main__C.odoc-occurrences
5858

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

68-
$ occurrences_print occurrences-main.odoc | sort
68+
$ occurrences_print main.odoc-occurrences | sort
6969
Main was used directly 0 times and indirectly 2 times
7070
Main.A was used directly 1 times and indirectly 0 times
7171
Main.B was used directly 1 times and indirectly 0 times
7272

73-
$ occurrences_print occurrences-main__.odoc | sort
73+
$ occurrences_print main__.odoc-occurrences | sort
7474

7575
A only uses "persistent" values: one it defines itself.
76-
$ occurrences_print occurrences-main__A.odoc | sort
76+
$ occurrences_print main__A.odoc-occurrences | sort
7777

7878
"Aliased" values are not counted since they become persistent
79-
$ occurrences_print occurrences-main__B.odoc | sort
79+
$ occurrences_print main__B.odoc-occurrences | sort
8080
Main was used directly 0 times and indirectly 7 times
8181
Main.A was used directly 2 times and indirectly 5 times
8282
Main.A.(||>) was used directly 1 times and indirectly 0 times
@@ -85,21 +85,21 @@ A only uses "persistent" values: one it defines itself.
8585
Main.A.x was used directly 1 times and indirectly 0 times
8686

8787
"Aliased" values are not counted since they become persistent
88-
$ occurrences_print occurrences-main__C.odoc | sort
88+
$ occurrences_print main__C.odoc-occurrences | sort
8989
Main was used directly 0 times and indirectly 2 times
9090
Main.A was used directly 1 times and indirectly 1 times
9191
Main.A.x was used directly 1 times and indirectly 0 times
9292

9393
Now we can merge all tables
9494

9595
$ cat > files.map << EOF
96-
> occurrences-main__A.odoc
97-
> occurrences-main__B.odoc
98-
> occurrences-main__C.odoc
96+
> main__A.odoc-occurrences
97+
> main__B.odoc-occurrences
98+
> main__C.odoc-occurrences
9999
> EOF
100-
$ odoc aggregate-occurrences occurrences-main.odoc occurrences-main__.odoc --file-list files.map -o occurrences-aggregated.odoc
100+
$ odoc aggregate-occurrences main.odoc-occurrences main__.odoc-occurrences --file-list files.map -o aggregated.odoc-occurrences
101101

102-
$ occurrences_print occurrences-aggregated.odoc | sort > all_merged
102+
$ occurrences_print aggregated.odoc-occurrences | sort > all_merged
103103
$ cat all_merged
104104
Main was used directly 0 times and indirectly 11 times
105105
Main.A was used directly 4 times and indirectly 6 times
@@ -111,14 +111,14 @@ Now we can merge all tables
111111

112112
Compare with the one created directly with all occurrences:
113113

114-
$ odoc count-occurrences -I . -o occurrences-all.odoc
115-
$ occurrences_print occurrences-all.odoc | sort > directly_all
114+
$ odoc count-occurrences . -o all.odoc-occurrences
115+
$ occurrences_print all.odoc-occurrences | sort > directly_all
116116
$ diff all_merged directly_all
117117

118118
We can also include hidden ids:
119119

120-
$ odoc count-occurrences -I main__B -o occurrences-b.odoc --include-hidden
121-
$ occurrences_print occurrences-b.odoc | sort
120+
$ odoc count-occurrences main__B -o b.odoc-occurrences --include-hidden
121+
$ occurrences_print b.odoc-occurrences | sort
122122
Main was used directly 0 times and indirectly 7 times
123123
Main.A was used directly 2 times and indirectly 5 times
124124
Main.A.(||>) was used directly 1 times and indirectly 0 times
@@ -129,8 +129,8 @@ We can also include hidden ids:
129129
Main__.C was used directly 1 times and indirectly 1 times
130130
Main__.C.y was used directly 1 times and indirectly 0 times
131131

132-
$ odoc count-occurrences -I . -o occurrences-all.odoc --include-hidden
133-
$ occurrences_print occurrences-all.odoc | sort
132+
$ odoc count-occurrences . -o all.odoc-occurrences --include-hidden
133+
$ occurrences_print all.odoc-occurrences | sort
134134
Main was used directly 0 times and indirectly 11 times
135135
Main.A was used directly 4 times and indirectly 6 times
136136
Main.A.(||>) was used directly 1 times and indirectly 0 times
@@ -149,7 +149,7 @@ We can use the generated table when generating the json output:
149149

150150
$ odoc link -I . main.odoc
151151

152-
$ odoc compile-index --json -o index.json --occurrences occurrences-all.odoc main.odocl
152+
$ odoc compile-index --json -o index.json --occurrences all.odoc-occurrences main.odocl
153153

154154
$ cat index.json | jq sort | jq '.[]' -c
155155
{"id":[{"kind":"Root","name":"Main"}],"doc":"Handwritten top-level module","kind":{"kind":"Module"},"display":{"url":"Main/index.html","html":"<code class=\"entry-kind\">mod</code><code class=\"entry-title\"><span class=\"entry-name\">Main</span></code><div class=\"entry-comment\"><div><p>Handwritten top-level module</p></div></div>"},"occurrences":{"direct":0,"indirect":11}}

0 commit comments

Comments
 (0)