Skip to content

Commit d1009b4

Browse files
panglesdjonludlam
authored andcommitted
occurrences: only count persistent one
Signed-off-by: Paul-Elliot <[email protected]>
1 parent bcf0664 commit d1009b4

File tree

9 files changed

+30
-112
lines changed

9 files changed

+30
-112
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: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -315,7 +315,7 @@ let process_occurrences env poses loc_to_id local_ident_to_loc =
315315
| p -> (
316316
match find_in_env env p with
317317
| path ->
318-
let documentation = Some (path, is_persistent p)
318+
let documentation = if is_persistent p then Some path else None
319319
and implementation = Some (Unresolved path) in
320320
Some { documentation; implementation }
321321
| exception _ -> None)

src/model/lang.ml

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

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

src/odoc/bin/main.ml

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

11131113
module Occurrences = struct
11141114
module Count = struct
1115-
let count directories dst warnings_options include_hidden include_own
1116-
=
1115+
let count directories dst warnings_options include_hidden =
11171116
let dst = Fpath.v dst in
11181117
Occurrences.count ~dst ~warnings_options directories include_hidden
1119-
include_own
11201118

11211119
let cmd =
11221120
let dst =
@@ -1130,16 +1128,10 @@ module Occurrences = struct
11301128
let doc = "Include hidden identifiers in the table" in
11311129
Arg.(value & flag & info ~docs ~doc [ "include-hidden" ])
11321130
in
1133-
let include_own =
1134-
let doc =
1135-
"Include identifiers from the compilation in the table."
1136-
in
1137-
Arg.(value & flag & info ~docs ~doc [ "include-own" ])
1138-
in
11391131
Term.(
11401132
const handle_error
11411133
$ (const count $ odoc_file_directories $ dst $ warnings_options
1142-
$ include_hidden $ include_own))
1134+
$ include_hidden))
11431135

11441136
let info ~docs =
11451137
let doc =

src/odoc/occurrences.ml

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

122-
let count ~dst ~warnings_options:_ directories include_hidden include_own
123-
=
122+
let count ~dst ~warnings_options:_ directories include_hidden =
124123
let htbl = H.create 100 in
125124
let f () (unit : Odoc_model.Lang.Compilation_unit.t) =
126-
let incr tbl p persistent =
125+
let incr tbl p =
127126
let p = (p :> Odoc_model.Paths.Path.Resolved.t) in
128127
let id = Odoc_model.Paths.Path.Resolved.identifier p in
129128
if (not (Odoc_model.Paths.Path.Resolved.is_hidden p)) || include_hidden
130-
then if persistent || include_own then Occtbl.add tbl id
129+
then Occtbl.add tbl id
131130
in
132131
let () =
133132
List.iter
134133
(function
135134
| ( Odoc_model.Lang.Source_info.Module
136-
{ documentation = Some (`Resolved p, persistent); _ },
135+
{ documentation = Some (`Resolved p); _ },
137136
_ ) ->
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-
->
143-
incr htbl p persistent
144-
| ModuleType { documentation = Some (`Resolved p, persistent); _ }, _
145-
->
146-
incr htbl p persistent
147-
| Type { documentation = Some (`Resolved p, persistent); _ }, _ ->
148-
incr htbl p persistent
137+
incr htbl p
138+
| Value { documentation = Some (`Resolved p); _ }, _ -> incr htbl p
139+
| ClassType { documentation = Some (`Resolved p); _ }, _ ->
140+
incr htbl p
141+
| ModuleType { documentation = Some (`Resolved p); _ }, _ ->
142+
incr htbl p
143+
| Type { documentation = Some (`Resolved p); _ }, _ -> incr htbl p
149144
| _ -> ())
150145
(match unit.source_info with None -> [] | Some i -> i.infos)
151146
in

src/xref2/compile.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -89,9 +89,7 @@ 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
93-
| Some (p, persistent) -> Some (f p, persistent)
94-
| None -> None
92+
match v.documentation with Some p -> Some (f p) | None -> None
9593
in
9694
{ v with documentation }
9795
in

src/xref2/link.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -533,9 +533,7 @@ 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
537-
| Some (p, persistent) -> Some (f_doc p, persistent)
538-
| None -> None
536+
match v.documentation with Some p -> Some (f_doc p) | None -> None
539537
in
540538
let implementation =
541539
match v.implementation with

test/occurrences/double_wrapped.t/b.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,4 +10,6 @@ module M : A.M = struct end
1010

1111
module type Y = A.M
1212

13-
let _ = let open A in 1 ||> 2
13+
let _ =
14+
let open A in
15+
1 ||> 2

test/occurrences/double_wrapped.t/run.t

Lines changed: 9 additions & 74 deletions
Original file line numberDiff line numberDiff line change
@@ -63,8 +63,10 @@ Uses of values Y.x and Z.y (in b.ml) are not counted since they come from a "loc
6363

6464
$ occurrences_print main__.occ | sort
6565

66+
A only uses "persistent" values: one it defines itself.
6667
$ occurrences_print main__A.occ | sort
6768

69+
"Aliased" values are not counted since they become persistent
6870
$ occurrences_print main__B.occ | sort
6971
Main was used directly 0 times and indirectly 7 times
7072
Main.A was used directly 2 times and indirectly 5 times
@@ -73,12 +75,13 @@ Uses of values Y.x and Z.y (in b.ml) are not counted since they come from a "loc
7375
Main.A.t was used directly 1 times and indirectly 0 times
7476
Main.A.x was used directly 1 times and indirectly 0 times
7577

78+
"Aliased" values are not counted since they become persistent
7679
$ occurrences_print main__C.occ | sort
7780
Main was used directly 0 times and indirectly 2 times
7881
Main.A was used directly 1 times and indirectly 1 times
7982
Main.A.x was used directly 1 times and indirectly 0 times
8083

81-
Now we can merge both files
84+
Now we can merge all tables
8285

8386
$ cat > files.map << EOF
8487
> main__A.occ
@@ -87,7 +90,8 @@ Now we can merge both files
8790
> EOF
8891
$ odoc aggregate-occurrences main.occ main__.occ --file-list files.map -o aggregated.txt
8992

90-
$ occurrences_print aggregated.txt | sort
93+
$ occurrences_print aggregated.txt | sort > all_merged
94+
$ cat all_merged
9195
Main was used directly 0 times and indirectly 11 times
9296
Main.A was used directly 4 times and indirectly 6 times
9397
Main.A.(||>) was used directly 1 times and indirectly 0 times
@@ -99,41 +103,14 @@ Now we can merge both files
99103
Compare with the one created directly with all occurrences:
100104

101105
$ odoc count-occurrences -I . -o occurrences.txt
102-
$ occurrences_print occurrences.txt | sort
103-
Main was used directly 0 times and indirectly 11 times
104-
Main.A was used directly 4 times and indirectly 6 times
105-
Main.A.(||>) was used directly 1 times and indirectly 0 times
106-
Main.A.M was used directly 2 times and indirectly 0 times
107-
Main.A.t was used directly 1 times and indirectly 0 times
108-
Main.A.x was used directly 2 times and indirectly 0 times
109-
Main.B was used directly 1 times and indirectly 0 times
106+
$ occurrences_print occurrences.txt | sort > directly_all
107+
$ diff all_merged directly_all
110108

111-
We can also include persistent ids, and hidden ids:
112-
113-
$ odoc count-occurrences -I main__A -o occurrences.txt --include-own
114-
$ occurrences_print occurrences.txt | sort
115-
string was used directly 1 times and indirectly 0 times
109+
We can also include hidden ids:
116110

117111
$ odoc count-occurrences -I main__A -o occurrences.txt --include-hidden
118112
$ occurrences_print occurrences.txt | sort
119113

120-
$ odoc count-occurrences -I main__A -o occurrences.txt --include-own --include-hidden
121-
$ occurrences_print occurrences.txt | sort
122-
Main__A was used directly 0 times and indirectly 2 times
123-
Main__A.x was used directly 2 times and indirectly 0 times
124-
string was used directly 1 times and indirectly 0 times
125-
126-
$ odoc count-occurrences -I . -o occurrences.txt --include-own
127-
$ occurrences_print occurrences.txt | sort
128-
Main was used directly 0 times and indirectly 13 times
129-
Main.A was used directly 4 times and indirectly 8 times
130-
Main.A.(||>) was used directly 1 times and indirectly 0 times
131-
Main.A.M was used directly 2 times and indirectly 0 times
132-
Main.A.t was used directly 1 times and indirectly 0 times
133-
Main.A.x was used directly 4 times and indirectly 0 times
134-
Main.B was used directly 1 times and indirectly 0 times
135-
string was used directly 1 times and indirectly 0 times
136-
137114
$ odoc count-occurrences -I . -o occurrences.txt --include-hidden
138115
$ occurrences_print occurrences.txt | sort
139116
Main was used directly 0 times and indirectly 11 times
@@ -149,45 +126,3 @@ We can also include persistent ids, and hidden ids:
149126
Main__A was used directly 1 times and indirectly 0 times
150127
Main__B was used directly 1 times and indirectly 0 times
151128
Main__C was used directly 1 times and indirectly 0 times
152-
153-
$ odoc count-occurrences -I . -o occurrences.txt --include-own --include-hidden
154-
$ occurrences_print occurrences.txt | sort
155-
Main was used directly 0 times and indirectly 13 times
156-
Main.A was used directly 4 times and indirectly 8 times
157-
Main.A.(||>) was used directly 1 times and indirectly 0 times
158-
Main.A.M was used directly 2 times and indirectly 0 times
159-
Main.A.t was used directly 1 times and indirectly 0 times
160-
Main.A.x was used directly 4 times and indirectly 0 times
161-
Main.B was used directly 1 times and indirectly 0 times
162-
Main__ was used directly 0 times and indirectly 2 times
163-
Main__.C was used directly 1 times and indirectly 1 times
164-
Main__.C.y was used directly 1 times and indirectly 0 times
165-
Main__A was used directly 1 times and indirectly 2 times
166-
Main__A.x was used directly 2 times and indirectly 0 times
167-
Main__B was used directly 1 times and indirectly 1 times
168-
Main__B.Z was used directly 0 times and indirectly 1 times
169-
Main__B.Z.y was used directly 1 times and indirectly 0 times
170-
Main__C was used directly 1 times and indirectly 0 times
171-
string was used directly 1 times and indirectly 0 times
172-
173-
174-
REMARKS!
175-
176-
$ odoc count-occurrences -I main__B -o b_only_persistent.occ
177-
$ odoc count-occurrences -I main__B -o b_with_own.occ --include-own
178-
$ occurrences_print b_only_persistent.occ | sort > only_persistent
179-
$ occurrences_print b_with_own.occ | sort > with_own
180-
$ diff only_persistent with_own | grep Main.A.x
181-
< Main.A.x was used directly 1 times and indirectly 0 times
182-
> Main.A.x was used directly 2 times and indirectly 0 times
183-
184-
This is because the persistent Y.x is resolved into Main.A.x. So maybe relying
185-
on Ident.persistent is not the good way of knowing if it is persistent or not?
186-
187-
$ odoc count-occurrences -I main__A -o a_with_own_and_hidden.occ --include-own --include-hidden
188-
$ occurrences_print a_with_own_and_hidden.occ | sort
189-
Main__A was used directly 0 times and indirectly 2 times
190-
Main__A.x was used directly 2 times and indirectly 0 times
191-
string was used directly 1 times and indirectly 0 times
192-
193-
That's a problem: it should be Main.A and Main.A.x

0 commit comments

Comments
 (0)