Skip to content

Commit

Permalink
occurrences: only count persistent one
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Dec 6, 2023
1 parent 44b1382 commit 4f78011
Show file tree
Hide file tree
Showing 9 changed files with 30 additions and 112 deletions.
2 changes: 1 addition & 1 deletion src/document/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -256,7 +256,7 @@ module Make (Syntax : SYNTAX) = struct
let documentation =
let open Paths.Path.Resolved in
match documentation with
| Some (`Resolved p, _) when not (is_hidden (p :> t)) -> (
| Some (`Resolved p) when not (is_hidden (p :> t)) -> (
let id = identifier (p :> t) in
match Url.from_identifier ~stop_before:false id with
| Ok link -> Some link
Expand Down
2 changes: 1 addition & 1 deletion src/loader/implementation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -315,7 +315,7 @@ let process_occurrences env poses loc_to_id local_ident_to_loc =
| p -> (
match find_in_env env p with
| path ->
let documentation = Some (path, is_persistent p)
let documentation = if is_persistent p then Some path else None
and implementation = Some (Unresolved path) in
Some { documentation; implementation }
| exception _ -> None)
Expand Down
4 changes: 1 addition & 3 deletions src/model/lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,7 @@ module Source_info = struct
| Resolved of Identifier.SourceLocation.t

type ('doc, 'impl) jump_to = {
documentation : ('doc * bool) option;
(* The boolean indicate if the path is "persistent": from the same
compilation unit. *)
documentation : 'doc option;
implementation : 'impl jump_to_impl option;
}

Expand Down
12 changes: 2 additions & 10 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1113,11 +1113,9 @@ end

module Occurrences = struct
module Count = struct
let count directories dst warnings_options include_hidden include_own
=
let count directories dst warnings_options include_hidden =
let dst = Fpath.v dst in
Occurrences.count ~dst ~warnings_options directories include_hidden
include_own

let cmd =
let dst =
Expand All @@ -1131,16 +1129,10 @@ module Occurrences = struct
let doc = "Include hidden identifiers in the table" in
Arg.(value & flag & info ~docs ~doc [ "include-hidden" ])
in
let include_own =
let doc =
"Include identifiers from the compilation in the table."
in
Arg.(value & flag & info ~docs ~doc [ "include-own" ])
in
Term.(
const handle_error
$ (const count $ odoc_file_directories $ dst $ warnings_options
$ include_hidden $ include_own))
$ include_hidden))

let info ~docs =
let doc =
Expand Down
27 changes: 11 additions & 16 deletions src/odoc/occurrences.ml
Original file line number Diff line number Diff line change
Expand Up @@ -119,33 +119,28 @@ end = struct
tbl
end

let count ~dst ~warnings_options:_ directories include_hidden include_own
=
let count ~dst ~warnings_options:_ directories include_hidden =
let htbl = H.create 100 in
let f () (unit : Odoc_model.Lang.Compilation_unit.t) =
let incr tbl p persistent =
let incr tbl p =
let p = (p :> Odoc_model.Paths.Path.Resolved.t) in
let id = Odoc_model.Paths.Path.Resolved.identifier p in
if (not (Odoc_model.Paths.Path.Resolved.is_hidden p)) || include_hidden
then if persistent || include_own then Occtbl.add tbl id
then Occtbl.add tbl id
in
let () =
List.iter
(function
| ( Odoc_model.Lang.Source_info.Module
{ documentation = Some (`Resolved p, persistent); _ },
{ documentation = Some (`Resolved p); _ },
_ ) ->
incr htbl p persistent
| Value { documentation = Some (`Resolved p, persistent); _ }, _ ->
incr htbl p persistent
| ClassType { documentation = Some (`Resolved p, persistent); _ }, _
->
incr htbl p persistent
| ModuleType { documentation = Some (`Resolved p, persistent); _ }, _
->
incr htbl p persistent
| Type { documentation = Some (`Resolved p, persistent); _ }, _ ->
incr htbl p persistent
incr htbl p
| Value { documentation = Some (`Resolved p); _ }, _ -> incr htbl p
| ClassType { documentation = Some (`Resolved p); _ }, _ ->
incr htbl p
| ModuleType { documentation = Some (`Resolved p); _ }, _ ->
incr htbl p
| Type { documentation = Some (`Resolved p); _ }, _ -> incr htbl p
| _ -> ())
(match unit.source_info with None -> [] | Some i -> i.infos)
in
Expand Down
4 changes: 1 addition & 3 deletions src/xref2/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,9 +94,7 @@ and source_info_infos env infos =
let open Source_info in
let map_doc f v =
let documentation =
match v.documentation with
| Some (p, persistent) -> Some (f p, persistent)
| None -> None
match v.documentation with Some p -> Some (f p) | None -> None
in
{ v with documentation }
in
Expand Down
4 changes: 1 addition & 3 deletions src/xref2/link.ml
Original file line number Diff line number Diff line change
Expand Up @@ -533,9 +533,7 @@ let rec unit env t =
| Some inf ->
let jump_to v f_impl f_doc =
let documentation =
match v.documentation with
| Some (p, persistent) -> Some (f_doc p, persistent)
| None -> None
match v.documentation with Some p -> Some (f_doc p) | None -> None
in
let implementation =
match v.implementation with
Expand Down
4 changes: 3 additions & 1 deletion test/occurrences/double_wrapped.t/b.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,4 +10,6 @@ module M : A.M = struct end

module type Y = A.M

let _ = let open A in 1 ||> 2
let _ =
let open A in
1 ||> 2
83 changes: 9 additions & 74 deletions test/occurrences/double_wrapped.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,10 @@ Uses of values Y.x and Z.y (in b.ml) are not counted since they come from a "loc

$ occurrences_print main__.occ | sort

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

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

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

Now we can merge both files
Now we can merge all tables

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

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

$ odoc count-occurrences -I . -o occurrences.txt
$ occurrences_print occurrences.txt | sort
Main was used directly 0 times and indirectly 11 times
Main.A was used directly 4 times and indirectly 6 times
Main.A.(||>) was used directly 1 times and indirectly 0 times
Main.A.M was used directly 2 times and indirectly 0 times
Main.A.t was used directly 1 times and indirectly 0 times
Main.A.x was used directly 2 times and indirectly 0 times
Main.B was used directly 1 times and indirectly 0 times
$ occurrences_print occurrences.txt | sort > directly_all
$ diff all_merged directly_all

We can also include persistent ids, and hidden ids:

$ odoc count-occurrences -I main__A -o occurrences.txt --include-own
$ occurrences_print occurrences.txt | sort
string was used directly 1 times and indirectly 0 times
We can also include hidden ids:

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

$ odoc count-occurrences -I main__A -o occurrences.txt --include-own --include-hidden
$ occurrences_print occurrences.txt | sort
Main__A was used directly 0 times and indirectly 2 times
Main__A.x was used directly 2 times and indirectly 0 times
string was used directly 1 times and indirectly 0 times

$ odoc count-occurrences -I . -o occurrences.txt --include-own
$ occurrences_print occurrences.txt | sort
Main was used directly 0 times and indirectly 13 times
Main.A was used directly 4 times and indirectly 8 times
Main.A.(||>) was used directly 1 times and indirectly 0 times
Main.A.M was used directly 2 times and indirectly 0 times
Main.A.t was used directly 1 times and indirectly 0 times
Main.A.x was used directly 4 times and indirectly 0 times
Main.B was used directly 1 times and indirectly 0 times
string was used directly 1 times and indirectly 0 times

$ odoc count-occurrences -I . -o occurrences.txt --include-hidden
$ occurrences_print occurrences.txt | sort
Main was used directly 0 times and indirectly 11 times
Expand All @@ -149,45 +126,3 @@ We can also include persistent ids, and hidden ids:
Main__A was used directly 1 times and indirectly 0 times
Main__B was used directly 1 times and indirectly 0 times
Main__C was used directly 1 times and indirectly 0 times

$ odoc count-occurrences -I . -o occurrences.txt --include-own --include-hidden
$ occurrences_print occurrences.txt | sort
Main was used directly 0 times and indirectly 13 times
Main.A was used directly 4 times and indirectly 8 times
Main.A.(||>) was used directly 1 times and indirectly 0 times
Main.A.M was used directly 2 times and indirectly 0 times
Main.A.t was used directly 1 times and indirectly 0 times
Main.A.x was used directly 4 times and indirectly 0 times
Main.B was used directly 1 times and indirectly 0 times
Main__ was used directly 0 times and indirectly 2 times
Main__.C was used directly 1 times and indirectly 1 times
Main__.C.y was used directly 1 times and indirectly 0 times
Main__A was used directly 1 times and indirectly 2 times
Main__A.x was used directly 2 times and indirectly 0 times
Main__B was used directly 1 times and indirectly 1 times
Main__B.Z was used directly 0 times and indirectly 1 times
Main__B.Z.y was used directly 1 times and indirectly 0 times
Main__C was used directly 1 times and indirectly 0 times
string was used directly 1 times and indirectly 0 times


REMARKS!

$ odoc count-occurrences -I main__B -o b_only_persistent.occ
$ odoc count-occurrences -I main__B -o b_with_own.occ --include-own
$ occurrences_print b_only_persistent.occ | sort > only_persistent
$ occurrences_print b_with_own.occ | sort > with_own
$ diff only_persistent with_own | grep Main.A.x
< Main.A.x was used directly 1 times and indirectly 0 times
> Main.A.x was used directly 2 times and indirectly 0 times

This is because the persistent Y.x is resolved into Main.A.x. So maybe relying
on Ident.persistent is not the good way of knowing if it is persistent or not?

$ odoc count-occurrences -I main__A -o a_with_own_and_hidden.occ --include-own --include-hidden
$ occurrences_print a_with_own_and_hidden.occ | sort
Main__A was used directly 0 times and indirectly 2 times
Main__A.x was used directly 2 times and indirectly 0 times
string was used directly 1 times and indirectly 0 times

That's a problem: it should be Main.A and Main.A.x

0 comments on commit 4f78011

Please sign in to comment.