Skip to content

Commit 22248aa

Browse files
panglesdjonludlam
authored andcommitted
Occurrences: add shapes for other nodes, improve test
Signed-off-by: Paul-Elliot <[email protected]>
1 parent e62ad5b commit 22248aa

File tree

5 files changed

+73
-21
lines changed

5 files changed

+73
-21
lines changed

src/xref2/link.ml

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -565,18 +565,23 @@ let rec unit env t =
565565
| ModuleType v ->
566566
ModuleType
567567
(jump_to v
568-
(fun _ -> None)
568+
(Shape_tools.lookup_module_type_path env)
569569
(module_type_path ~report_errors:false env))
570570
| Type v ->
571571
Type
572572
(jump_to v
573-
(fun _ -> None)
573+
(Shape_tools.lookup_type_path env)
574574
(type_path ~report_errors:false env))
575575
| Constructor v ->
576576
Constructor
577577
(jump_to v
578578
(fun _ -> None)
579579
(constructor_path ~report_errors:false env))
580+
| ClassType v ->
581+
ClassType
582+
(jump_to v
583+
(Shape_tools.lookup_class_type_path env)
584+
(class_type_path ~report_errors:false env))
580585
| i -> i
581586
in
582587
(info, pos))

src/xref2/shape_tools.cppo.ml

Lines changed: 22 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -81,21 +81,20 @@ let rec shape_of_module_path env : _ -> Shape.t option =
8181
| `Identifier (id, _) ->
8282
shape_of_id env (id :> Odoc_model.Paths.Identifier.NonSrc.t)
8383

84-
let shape_of_value_path env :
85-
Odoc_model.Paths.Path.Value.t -> Shape.t option =
84+
let shape_of_kind_path env kind :
85+
_ -> Shape.t option =
8686
let proj parent kind name =
8787
let item = Shape.Item.make name kind in
8888
match shape_of_module_path env parent with
8989
| Some shape -> Some (Shape.proj shape item)
9090
| None -> None
9191
in
92-
fun (path : Odoc_model.Paths.Path.Value.t) ->
92+
fun path ->
9393
match path with
9494
| `Resolved _ -> None
95-
| `Dot (parent, name) -> proj parent Kind.Value name
95+
| `Dot (parent, name) -> proj parent kind name
9696
| `Identifier (id, _) -> shape_of_id env (id :> Odoc_model.Paths.Identifier.NonSrc.t)
9797

98-
9998
module MkId = Identifier.Mk
10099

101100
let unit_of_uid uid =
@@ -151,25 +150,24 @@ let lookup_def :
151150
| None -> None
152151
| Some query -> lookup_shape env query
153152

154-
let lookup_value_path :
155-
Env.t ->
156-
Path.Value.t ->
157-
Identifier.SourceLocation.t option
158-
= fun env path ->
159-
match shape_of_value_path env path with
153+
let lookup_module_path = fun env path ->
154+
match shape_of_module_path env path with
160155
| None -> None
161156
| Some query -> lookup_shape env query
162157

163-
164-
let lookup_module_path :
165-
Env.t ->
166-
Path.Module.t ->
167-
Identifier.SourceLocation.t option
168-
= fun env path ->
169-
match shape_of_module_path env path with
158+
let lookup_kind_path = fun kind env path ->
159+
match shape_of_kind_path env kind path with
170160
| None -> None
171161
| Some query -> lookup_shape env query
172162

163+
let lookup_value_path = lookup_kind_path Kind.Value
164+
165+
let lookup_type_path = lookup_kind_path Kind.Type
166+
167+
let lookup_module_type_path = lookup_kind_path Kind.Module_type
168+
169+
let lookup_class_type_path = lookup_kind_path Kind.Class_type
170+
173171
#else
174172

175173
type t = unit
@@ -180,4 +178,10 @@ let lookup_value_path _ _id = None
180178

181179
let lookup_module_path _ _id = None
182180

181+
let lookup_type_path _ _id = None
182+
183+
let lookup_module_type_path _ _id = None
184+
185+
let lookup_class_type_path _ _id = None
186+
183187
#endif

src/xref2/shape_tools.cppo.mli

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,23 @@ val lookup_value_path :
1919
Path.Value.t ->
2020
Identifier.SourceLocation.t option
2121

22+
val lookup_type_path :
23+
Env.t ->
24+
Path.Type.t ->
25+
Identifier.SourceLocation.t option
26+
2227
val lookup_module_path :
2328
Env.t ->
2429
Path.Module.t ->
2530
Identifier.SourceLocation.t option
31+
32+
val lookup_module_type_path :
33+
Env.t ->
34+
Path.ModuleType.t ->
35+
Identifier.SourceLocation.t option
36+
37+
val lookup_class_type_path :
38+
Env.t ->
39+
Path.ClassType.t ->
40+
Identifier.SourceLocation.t option
41+

test/occurrences/double_wrapped.t/a.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,3 +5,5 @@ type t = string
55
module type M = sig end
66

77
let (||>) x y = x + y
8+
9+
let _ = x + x

test/occurrences/double_wrapped.t/run.t

Lines changed: 26 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -119,6 +119,8 @@ We can also include persistent ids, and hidden ids:
119119

120120
$ odoc count-occurrences -I main__A -o occurrences.txt --include-own --include-hidden
121121
$ 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
122124
string was used directly 1 times and indirectly 0 times
123125

124126
$ odoc count-occurrences -I . -o occurrences.txt --include-own
@@ -160,9 +162,32 @@ We can also include persistent ids, and hidden ids:
160162
Main__ was used directly 0 times and indirectly 2 times
161163
Main__.C was used directly 1 times and indirectly 1 times
162164
Main__.C.y was used directly 1 times and indirectly 0 times
163-
Main__A 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
164167
Main__B was used directly 1 times and indirectly 1 times
165168
Main__B.Z was used directly 0 times and indirectly 1 times
166169
Main__B.Z.y was used directly 1 times and indirectly 0 times
167170
Main__C was used directly 1 times and indirectly 0 times
168171
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)