Skip to content

Commit 8320206

Browse files
panglesdjonludlam
authored andcommitted
Occurrences: control which occurrences are counted
Persistent and hidden occurrences can be counted, or not. Signed-off-by: Paul-Elliot <[email protected]>
1 parent ec22f3e commit 8320206

File tree

8 files changed

+129
-79
lines changed

8 files changed

+129
-79
lines changed

src/document/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -256,7 +256,7 @@ module Make (Syntax : SYNTAX) = struct
256256
let documentation =
257257
let open Paths.Path.Resolved in
258258
match documentation with
259-
| Some (`Resolved p) when not (is_hidden (p :> t)) -> (
259+
| Some (`Resolved p, _) when not (is_hidden (p :> t)) -> (
260260
let id = identifier (p :> t) in
261261
match Url.from_identifier ~stop_before:false id with
262262
| Ok link -> Some link

src/loader/implementation.ml

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,12 @@
11
#if OCAML_VERSION >= (4, 14, 0)
22

3-
(* open Odoc_model.Lang.Source_info *)
3+
let rec is_persistent : Path.t -> bool = function
4+
| Path.Pident id -> Ident.persistent id
5+
| Path.Pdot(p, _) -> is_persistent p
6+
| Path.Papply(p, _) -> is_persistent p
7+
#if OCAML_VERSION >= (5,1,0)
8+
| Path.Pextra_ty -> assert false
9+
#endif
410

511
let pos_of_loc loc = (loc.Location.loc_start.pos_cnum, loc.loc_end.pos_cnum)
612

@@ -303,7 +309,7 @@ let process_occurrences env poses loc_to_id local_ident_to_loc =
303309
| p -> (
304310
match find_in_env env p with
305311
| path ->
306-
let documentation = Some path
312+
let documentation = Some (path, is_persistent p)
307313
and implementation = Some (Unresolved path) in
308314
Some { documentation; implementation }
309315
| exception _ -> None)

src/model/lang.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,9 @@ module Source_info = struct
2323
| Resolved of Identifier.SourceLocation.t
2424

2525
type ('doc, 'impl) jump_to = {
26-
documentation : 'doc option;
26+
documentation : ('doc * bool) option;
27+
(* The boolean indicate if the path is "persistent": from the same
28+
compilation unit. *)
2729
implementation : 'impl jump_to_impl option;
2830
}
2931

src/odoc/bin/main.ml

Lines changed: 17 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1112,9 +1112,11 @@ end
11121112

11131113
module Occurrences = struct
11141114
module Count = struct
1115-
let index directories dst warnings_options =
1115+
let count directories dst warnings_options include_hidden include_persistent
1116+
=
11161117
let dst = Fpath.v dst in
1117-
Occurrences.count ~dst ~warnings_options directories
1118+
Occurrences.count ~dst ~warnings_options directories include_hidden
1119+
include_persistent
11181120

11191121
let cmd =
11201122
let dst =
@@ -1124,9 +1126,21 @@ module Occurrences = struct
11241126
& opt (some string) None
11251127
& info ~docs ~docv:"PATH" ~doc [ "o" ])
11261128
in
1129+
let include_hidden =
1130+
let doc = "Include hidden identifiers in the table" in
1131+
Arg.(value & flag & info ~docs ~doc [ "include-hidden" ])
1132+
in
1133+
let include_persistent =
1134+
let doc =
1135+
"Include persistent identifiers in the table: occurrences of in ids \
1136+
intheir own implementation."
1137+
in
1138+
Arg.(value & flag & info ~docs ~doc [ "include-persistent" ])
1139+
in
11271140
Term.(
11281141
const handle_error
1129-
$ (const index $ odoc_file_directories $ dst $ warnings_options))
1142+
$ (const count $ odoc_file_directories $ dst $ warnings_options
1143+
$ include_hidden $ include_persistent))
11301144

11311145
let info ~docs =
11321146
let doc =

src/odoc/occurrences.ml

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -119,28 +119,31 @@ end = struct
119119
tbl
120120
end
121121

122-
let count ~dst ~warnings_options:_ directories =
122+
let count ~dst ~warnings_options:_ directories include_hidden include_persistent =
123123
let htbl = H.create 100 in
124124
let f () (unit : Odoc_model.Lang.Compilation_unit.t) =
125-
let incr tbl p p' =
126-
let id = Odoc_model.Paths.Path.Resolved.(identifier (p :> t)) in
127-
if not Odoc_model.Paths.Path.(is_hidden p') then Occtbl.add tbl id
125+
let incr tbl p persistent =
126+
let p = (p :> Odoc_model.Paths.Path.Resolved.t) in
127+
let id = Odoc_model.Paths.Path.Resolved.identifier p in
128+
if not (Odoc_model.Paths.Path.Resolved.is_hidden p) || include_hidden then
129+
if not persistent || include_persistent then
130+
Occtbl.add tbl id
128131
in
129132
let () =
130133
List.iter
131134
(function
132135
| ( Odoc_model.Lang.Source_info.Module
133-
{ documentation = Some (`Resolved p as p'); _ },
136+
{ documentation = Some (`Resolved p, persistent); _ },
134137
_ ) ->
135-
incr htbl p Odoc_model.Paths.Path.((p' : Module.t :> t))
136-
| Value { documentation = Some (`Resolved p as p'); _ }, _ ->
137-
incr htbl p Odoc_model.Paths.Path.((p' : Value.t :> t))
138-
| ClassType { documentation = Some (`Resolved p as p'); _ }, _ ->
139-
incr htbl p Odoc_model.Paths.Path.((p' : ClassType.t :> t))
140-
| ModuleType { documentation = Some (`Resolved p as p'); _ }, _ ->
141-
incr htbl p Odoc_model.Paths.Path.((p' : ModuleType.t :> t))
142-
| Type { documentation = Some (`Resolved p as p'); _ }, _ ->
143-
incr htbl p Odoc_model.Paths.Path.((p' : Type.t :> t))
138+
incr htbl p persistent
139+
| Value { documentation = Some (`Resolved p, persistent); _ }, _ ->
140+
incr htbl p persistent
141+
| ClassType { documentation = Some (`Resolved p, persistent); _ }, _ ->
142+
incr htbl p persistent
143+
| ModuleType { documentation = Some (`Resolved p, persistent); _ }, _ ->
144+
incr htbl p persistent
145+
| Type { documentation = Some (`Resolved p, persistent); _ }, _ ->
146+
incr htbl p persistent
144147
| _ -> ())
145148
(match unit.source_info with None -> [] | Some i -> i.infos)
146149
in

src/xref2/compile.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,9 @@ and source_info_infos env infos =
8989
let open Source_info in
9090
let map_doc f v =
9191
let documentation =
92-
match v.documentation with Some p -> Some (f p) | None -> None
92+
match v.documentation with
93+
| Some (p, persistent) -> Some (f p, persistent)
94+
| None -> None
9395
in
9496
{ v with documentation }
9597
in

src/xref2/link.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -533,7 +533,9 @@ let rec unit env t =
533533
| Some inf ->
534534
let jump_to v f_impl f_doc =
535535
let documentation =
536-
match v.documentation with Some p -> Some (f_doc p) | None -> None
536+
match v.documentation with
537+
| Some (p, persistent) -> Some (f_doc p, persistent)
538+
| None -> None
537539
in
538540
let implementation =
539541
match v.implementation with

test/occurrences/double_wrapped.t/run.t

Lines changed: 77 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -25,37 +25,27 @@ occurrences information.
2525
$ odoc link -I . main__C.odoc
2626
$ odoc link -I . main__.odoc
2727

28-
$ odoc html-generate -o html main.odocl
29-
$ odoc html-generate -o html main__A.odocl
30-
$ odoc html-generate -o html main__B.odocl
31-
$ odoc html-generate -o html main__C.odocl
32-
$ odoc html-generate -o html main__.odocl
33-
3428
The count occurrences command outputs a marshalled hashtable, whose keys are
3529
odoc identifiers, and whose values are integers corresponding to the number of
3630
uses. We can later aggregate those hashtables, so we create the full hashtable,
3731
and a hashtable for each compilation unit.
3832

39-
$ mkdir dir1
40-
$ mkdir dir2
41-
$ mkdir dir3
42-
$ mkdir dir4
43-
$ mkdir dir5
44-
45-
$ mv main.odocl dir1
46-
$ mv main__.odocl dir2
47-
$ mv main__A.odocl dir3
48-
$ mv main__B.odocl dir4
49-
$ mv main__C.odocl dir5
50-
$ odoc count-occurrences -I . -o occurrences.txt
51-
$ odoc count-occurrences -I dir1 -o occurrences1.txt
52-
$ odoc count-occurrences -I dir2 -o occurrences2.txt
53-
$ odoc count-occurrences -I dir3 -o occurrences3.txt
54-
$ odoc count-occurrences -I dir4 -o occurrences4.txt
55-
$ odoc count-occurrences -I dir5 -o occurrences5.txt
56-
57-
$ du -h occurrences.txt
58-
4.0K occurrences.txt
33+
$ mkdir main
34+
$ mkdir main__
35+
$ mkdir main__A
36+
$ mkdir main__B
37+
$ mkdir main__C
38+
39+
$ mv main.odocl main
40+
$ mv main__.odocl main__
41+
$ mv main__A.odocl main__A
42+
$ mv main__B.odocl main__B
43+
$ 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
5949

6050
The occurrences_print executable, available only for testing, unmarshal the file
6151
and prints the number of occurrences in a readable format.
@@ -66,54 +56,85 @@ Uses of C are not counted, since the canonical destination (Main.C, generated by
6656
Uses of B.Z are not counted since they go to a hidden module.
6757
Uses of values Y.x and Z.y (in b.ml) are not counted since they come from a "local" module.
6858

69-
$ occurrences_print occurrences.txt | sort
70-
Main was used directly 0 times and indirectly 13 times
71-
Main.A was used directly 4 times and indirectly 8 times
72-
Main.A.(||>) was used directly 1 times and indirectly 0 times
73-
Main.A.M was used directly 2 times and indirectly 0 times
74-
Main.A.t was used directly 1 times and indirectly 0 times
75-
Main.A.x was used directly 4 times and indirectly 0 times
76-
Main.B was used directly 1 times and indirectly 0 times
59+
$ occurrences_print main.occ | sort
60+
61+
$ occurrences_print main__.occ | sort
62+
63+
$ occurrences_print main__A.occ | sort
7764
string was used directly 1 times and indirectly 0 times
7865

79-
$ occurrences_print occurrences1.txt | sort
66+
$ occurrences_print main__B.occ | sort
67+
Main was used directly 0 times and indirectly 1 times
68+
Main.A was used directly 0 times and indirectly 1 times
69+
Main.A.x was used directly 1 times and indirectly 0 times
70+
71+
$ occurrences_print main__C.occ | sort
72+
Main was used directly 0 times and indirectly 1 times
73+
Main.A was used directly 0 times and indirectly 1 times
74+
Main.A.x was used directly 1 times and indirectly 0 times
75+
76+
Now we can merge both files
77+
78+
$ cat > files.map << EOF
79+
> main__A.occ
80+
> main__B.occ
81+
> main__C.occ
82+
> EOF
83+
$ odoc aggregate-occurrences main.occ main__.occ --file-list files.map -o aggregated.txt
84+
85+
$ occurrences_print aggregated.txt | sort
8086
Main was used directly 0 times and indirectly 2 times
81-
Main.A was used directly 1 times and indirectly 0 times
82-
Main.B was used directly 1 times and indirectly 0 times
87+
Main.A was used directly 0 times and indirectly 2 times
88+
Main.A.x was used directly 2 times and indirectly 0 times
89+
string was used directly 1 times and indirectly 0 times
8390

84-
$ occurrences_print occurrences2.txt | sort
91+
Compare with the one created directly with all occurrences:
8592

86-
$ occurrences_print occurrences3.txt | sort
93+
$ odoc count-occurrences -I . -o occurrences.txt
94+
$ occurrences_print occurrences.txt | sort
95+
Main was used directly 0 times and indirectly 2 times
96+
Main.A was used directly 0 times and indirectly 2 times
97+
Main.A.x was used directly 2 times and indirectly 0 times
8798
string was used directly 1 times and indirectly 0 times
8899

89-
$ occurrences_print occurrences4.txt | sort
90-
Main was used directly 0 times and indirectly 8 times
91-
Main.A was used directly 2 times and indirectly 6 times
100+
We can also include persistent ids, and hidden ids:
101+
102+
$ odoc count-occurrences -I . -o occurrences.txt --include-persistent
103+
$ occurrences_print occurrences.txt | sort
104+
Main was used directly 0 times and indirectly 13 times
105+
Main.A was used directly 4 times and indirectly 8 times
92106
Main.A.(||>) was used directly 1 times and indirectly 0 times
93107
Main.A.M was used directly 2 times and indirectly 0 times
94108
Main.A.t was used directly 1 times and indirectly 0 times
95-
Main.A.x was used directly 2 times and indirectly 0 times
109+
Main.A.x was used directly 4 times and indirectly 0 times
110+
Main.B was used directly 1 times and indirectly 0 times
111+
string was used directly 1 times and indirectly 0 times
96112

97-
$ occurrences_print occurrences5.txt | sort
98-
Main was used directly 0 times and indirectly 3 times
99-
Main.A was used directly 1 times and indirectly 2 times
113+
$ odoc count-occurrences -I . -o occurrences.txt --include-hidden
114+
$ occurrences_print occurrences.txt | sort
115+
Main was used directly 0 times and indirectly 2 times
116+
Main.A was used directly 0 times and indirectly 2 times
100117
Main.A.x was used directly 2 times and indirectly 0 times
118+
Main__B was used directly 0 times and indirectly 1 times
119+
Main__B.Z was used directly 0 times and indirectly 1 times
120+
Main__B.Z.y was used directly 1 times and indirectly 0 times
121+
string was used directly 1 times and indirectly 0 times
101122

102-
Now we can merge both files
103-
104-
$ cat > files.map << EOF
105-
> occurrences3.txt
106-
> occurrences4.txt
107-
> occurrences5.txt
108-
> EOF
109-
$ odoc aggregate-occurrences occurrences1.txt occurrences2.txt --file-list files.map -o aggregated.txt
110-
111-
$ occurrences_print aggregated.txt | sort
123+
$ odoc count-occurrences -I . -o occurrences.txt --include-persistent --include-hidden
124+
$ occurrences_print occurrences.txt | sort
112125
Main was used directly 0 times and indirectly 13 times
113126
Main.A was used directly 4 times and indirectly 8 times
114127
Main.A.(||>) was used directly 1 times and indirectly 0 times
115128
Main.A.M was used directly 2 times and indirectly 0 times
116129
Main.A.t was used directly 1 times and indirectly 0 times
117130
Main.A.x was used directly 4 times and indirectly 0 times
118131
Main.B was used directly 1 times and indirectly 0 times
132+
Main__ was used directly 0 times and indirectly 2 times
133+
Main__.C was used directly 1 times and indirectly 1 times
134+
Main__.C.y was used directly 1 times and indirectly 0 times
135+
Main__A was used directly 1 times and indirectly 0 times
136+
Main__B was used directly 1 times and indirectly 1 times
137+
Main__B.Z was used directly 0 times and indirectly 1 times
138+
Main__B.Z.y was used directly 1 times and indirectly 0 times
139+
Main__C was used directly 1 times and indirectly 0 times
119140
string was used directly 1 times and indirectly 0 times

0 commit comments

Comments
 (0)