Skip to content

Commit b9f3c09

Browse files
panglesdjonludlam
authored andcommitted
Do not report resolution warning for occurrences
Signed-off-by: Paul-Elliot <[email protected]>
1 parent e4ceb80 commit b9f3c09

File tree

6 files changed

+75
-103
lines changed

6 files changed

+75
-103
lines changed

src/xref2/link.ml

Lines changed: 75 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -135,8 +135,9 @@ and should_resolve : Paths.Path.t -> bool =
135135
(* | `Resolved p -> should_reresolve (p :> Paths.Path.Resolved.t) *)
136136
(* | _ -> true *)
137137

138-
let type_path : Env.t -> Paths.Path.Type.t -> Paths.Path.Type.t =
139-
fun env p ->
138+
let type_path :
139+
?report_errors:bool -> Env.t -> Paths.Path.Type.t -> Paths.Path.Type.t =
140+
fun ?(report_errors = true) env p ->
140141
if not (should_resolve (p :> Paths.Path.t)) then p
141142
else
142143
let cp = Component.Of_Lang.(type_path (empty ()) p) in
@@ -150,49 +151,61 @@ let type_path : Env.t -> Paths.Path.Type.t -> Paths.Path.Type.t =
150151
let result = Tools.reresolve_type env p' in
151152
`Resolved Lang_of.(Path.resolved_type (empty ()) result)
152153
| Error e ->
153-
Errors.report ~what:(`Type_path cp) ~tools_error:e `Lookup;
154+
if report_errors then
155+
Errors.report ~what:(`Type_path cp) ~tools_error:e `Lookup;
154156
p)
155157

156-
(* let value_path : Env.t -> Paths.Path.Value.t -> Paths.Path.Value.t = *)
157-
(* fun env p -> *)
158-
(* if not (should_resolve (p :> Paths.Path.t)) then p *)
159-
(* else *)
160-
(* let cp = Component.Of_Lang.(value_path (empty ()) p) in *)
161-
(* match cp with *)
162-
(* | `Resolved p -> *)
163-
(* let result = Tools.reresolve_value env p in *)
164-
(* `Resolved Lang_of.(Path.resolved_value (empty ()) result) *)
165-
(* | _ -> ( *)
166-
(* match Tools.resolve_value_path env cp with *)
167-
(* | Ok p' -> *)
168-
(* let result = Tools.reresolve_value env p' in *)
169-
(* `Resolved Lang_of.(Path.resolved_value (empty ()) result) *)
170-
(* | Error e -> *)
171-
(* Errors.report ~what:(`Value_path cp) ~tools_error:e `Lookup; *)
172-
(* p) *)
173-
174-
(* let constructor_path : *)
175-
(* Env.t -> Paths.Path.Constructor.t -> Paths.Path.Constructor.t = *)
176-
(* fun env p -> *)
177-
(* if not (should_resolve_constructor p) then p *)
178-
(* else *)
179-
(* let cp = Component.Of_Lang.(constructor_path (empty ()) p) in *)
180-
(* match cp with *)
181-
(* | `Resolved p -> *)
182-
(* let result = Tools.reresolve_constructor env p in *)
183-
(* `Resolved Lang_of.(Path.resolved_constructor (empty ()) result) *)
184-
(* | _ -> ( *)
185-
(* match Tools.resolve_constructor_path env cp with *)
186-
(* | Ok p' -> *)
187-
(* let result = Tools.reresolve_constructor env p' in *)
188-
(* `Resolved Lang_of.(Path.resolved_constructor (empty ()) result) *)
189-
(* | Error e -> *)
190-
(* Errors.report ~what:(`Constructor_path cp) ~tools_error:e `Lookup; *)
191-
(* p) *)
192-
193-
let class_type_path : Env.t -> Paths.Path.ClassType.t -> Paths.Path.ClassType.t
194-
=
195-
fun env p ->
158+
let value_path :
159+
?report_errors:bool -> Env.t -> Paths.Path.Value.t -> Paths.Path.Value.t =
160+
fun ?(report_errors = true) env p ->
161+
if not (should_resolve (p :> Paths.Path.t)) then p
162+
else
163+
let cp = Component.Of_Lang.(value_path (empty ()) p) in
164+
match cp with
165+
| `Resolved p ->
166+
let result = Tools.reresolve_value env p in
167+
`Resolved Lang_of.(Path.resolved_value (empty ()) result)
168+
| _ -> (
169+
match Tools.resolve_value_path env cp with
170+
| Ok p' ->
171+
let result = Tools.reresolve_value env p' in
172+
`Resolved Lang_of.(Path.resolved_value (empty ()) result)
173+
| Error e ->
174+
if report_errors then
175+
Errors.report ~what:(`Value_path cp) ~tools_error:e `Lookup;
176+
p)
177+
178+
let constructor_path :
179+
?report_errors:bool ->
180+
Env.t ->
181+
Paths.Path.Constructor.t ->
182+
Paths.Path.Constructor.t =
183+
fun ?(report_errors = true) env p ->
184+
(* if not (should_resolve (p : Paths.Path.Constructor.t :> Paths.Path.t)) then p *)
185+
(* else *)
186+
if not (should_resolve_constructor p) then p
187+
else
188+
let cp = Component.Of_Lang.(constructor_path (empty ()) p) in
189+
match cp with
190+
| `Resolved p ->
191+
let result = Tools.reresolve_constructor env p in
192+
`Resolved Lang_of.(Path.resolved_constructor (empty ()) result)
193+
| _ -> (
194+
match Tools.resolve_constructor_path env cp with
195+
| Ok p' ->
196+
let result = Tools.reresolve_constructor env p' in
197+
`Resolved Lang_of.(Path.resolved_constructor (empty ()) result)
198+
| Error e ->
199+
if report_errors then
200+
Errors.report ~what:(`Constructor_path cp) ~tools_error:e `Lookup;
201+
p)
202+
203+
let class_type_path :
204+
?report_errors:bool ->
205+
Env.t ->
206+
Paths.Path.ClassType.t ->
207+
Paths.Path.ClassType.t =
208+
fun ?(report_errors = true) env p ->
196209
if not (should_resolve (p :> Paths.Path.t)) then p
197210
else
198211
let cp = Component.Of_Lang.(class_type_path (empty ()) p) in
@@ -206,12 +219,16 @@ let class_type_path : Env.t -> Paths.Path.ClassType.t -> Paths.Path.ClassType.t
206219
let result = Tools.reresolve_class_type env p' in
207220
`Resolved Lang_of.(Path.resolved_class_type (empty ()) result)
208221
| Error e ->
209-
Errors.report ~what:(`Class_type_path cp) ~tools_error:e `Lookup;
222+
if report_errors then
223+
Errors.report ~what:(`Class_type_path cp) ~tools_error:e `Lookup;
210224
p)
211225

212226
and module_type_path :
213-
Env.t -> Paths.Path.ModuleType.t -> Paths.Path.ModuleType.t =
214-
fun env p ->
227+
?report_errors:bool ->
228+
Env.t ->
229+
Paths.Path.ModuleType.t ->
230+
Paths.Path.ModuleType.t =
231+
fun ?(report_errors = true) env p ->
215232
if not (should_resolve (p :> Paths.Path.t)) then p
216233
else
217234
let cp = Component.Of_Lang.(module_type_path (empty ()) p) in
@@ -225,11 +242,13 @@ and module_type_path :
225242
let result = Tools.reresolve_module_type env p' in
226243
`Resolved Lang_of.(Path.resolved_module_type (empty ()) result)
227244
| Error e ->
228-
Errors.report ~what:(`Module_type_path cp) ~tools_error:e `Resolve;
245+
if report_errors then
246+
Errors.report ~what:(`Module_type_path cp) ~tools_error:e `Resolve;
229247
p)
230248

231-
and module_path : Env.t -> Paths.Path.Module.t -> Paths.Path.Module.t =
232-
fun env p ->
249+
and module_path :
250+
?report_errors:bool -> Env.t -> Paths.Path.Module.t -> Paths.Path.Module.t =
251+
fun ?(report_errors = true) env p ->
233252
if not (should_resolve (p :> Paths.Path.t)) then p
234253
else
235254
let cp = Component.Of_Lang.(module_path (empty ()) p) in
@@ -244,7 +263,8 @@ and module_path : Env.t -> Paths.Path.Module.t -> Paths.Path.Module.t =
244263
`Resolved Lang_of.(Path.resolved_module (empty ()) result)
245264
| Error _ when is_forward p -> p
246265
| Error e ->
247-
Errors.report ~what:(`Module_path cp) ~tools_error:e `Resolve;
266+
if report_errors then
267+
Errors.report ~what:(`Module_path cp) ~tools_error:e `Resolve;
248268
p)
249269

250270
let rec comment_inline_element :
@@ -433,16 +453,16 @@ let rec unit env t =
433453
Value
434454
(jump_to v
435455
(Shape_tools.lookup_value_path env)
436-
(value_path env))
456+
(value_path ~report_errors:false env))
437457
| Module v ->
438-
Module (jump_to v (fun _ -> None) (module_path env))
458+
Module (jump_to v (fun _ -> None) (module_path ~report_errors:false env))
439459
| ModuleType v ->
440460
ModuleType
441-
(jump_to v (fun _ -> None) (module_type_path env))
442-
| Type v -> Type (jump_to v (fun _ -> None) (type_path env))
461+
(jump_to v (fun _ -> None) (module_type_path ~report_errors:false env))
462+
| Type v -> Type (jump_to v (fun _ -> None) (type_path ~report_errors:false env))
443463
| Constructor v ->
444464
Constructor
445-
(jump_to v (fun _ -> None) (constructor_path env))
465+
(jump_to v (fun _ -> None) (constructor_path ~report_errors:false env))
446466
| i -> i
447467
in
448468
(info, pos))

test/occurrences/double_wrapped.t/run.t

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,13 +23,7 @@ occurrences information.
2323
$ odoc link -I . main.odoc
2424
$ odoc link -I . main__A.odoc
2525
$ odoc link -I . main__B.odoc
26-
File "main__B.odoc":
27-
Warning: Failed to lookup value identifier((root Main__B).Z, false).y Parent_module: Lookup failure (module): (root Main__B).Z
28-
File "main__B.odoc":
29-
Warning: Failed to lookup value identifier((root Main__B).Y, false).x Parent_module: Lookup failure (module): (root Main__B).Y
3026
$ odoc link -I . main__C.odoc
31-
File "main__C.odoc":
32-
Warning: Failed to lookup value identifier((root Main__C).Y, false).x Parent_module: Lookup failure (module): (root Main__C).Y
3327
$ odoc link -I . main__.odoc
3428

3529
The count occurrences command outputs a marshalled hashtable, whose keys are

test/sources/functor.t/run.t

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -12,16 +12,8 @@ Verify the behavior on functors.
1212
$ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmt
1313
$ odoc compile --source-name b.ml --source-parent-file src-source.odoc -I . b.cmt
1414
$ odoc link -I . s.odoc
15-
File "s.odoc":
16-
Warning: Failed to lookup type identifier((root S).S.t, false) Lookup failure (type): (root S).S.t
1715
$ odoc link -I . a.odoc
18-
File "a.odoc":
19-
Warning: Failed to lookup value identifier((param (root A).F S), false).x Parent_module: Lookup failure (module): (param (root A).F S)
20-
File "a.odoc":
21-
Warning: Failed to lookup type identifier((param (root A).F S), false).t Parent_module: Lookup failure (module): (param (root A).F S)
2216
$ odoc link -I . b.odoc
23-
File "b.odoc":
24-
Warning: Failed to resolve module path identifier((root B).S, false) Lookup failure (module): (root B).S
2517
$ odoc html-generate --source s.ml --indent -o html s.odocl
2618
$ odoc html-generate --source a.ml --indent -o html a.odocl
2719
$ odoc html-generate --source b.ml --indent -o html b.odocl

test/sources/lookup_def.t/run.t

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,6 @@ Compile the modules:
88
$ ocamlc -c a.mli a.ml -bin-annot
99
$ odoc compile --cmt a.cmt --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti
1010
$ odoc link a.odoc
11-
File "a.odoc":
12-
Warning: Failed to resolve module type path identifier((root A).N.S, false) Lookup failure (module type): (root A).N.S
1311

1412
Show the locations:
1513

test/sources/recursive_module.t/run.t

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -8,14 +8,6 @@ Checking that source links exists inside recursive modules.
88
$ ocamlc -c main.ml -bin-annot -I .
99
$ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt
1010
$ odoc link -I . main.odoc
11-
File "main.odoc":
12-
Warning: Failed to lookup type identifier((root Main).A, false).t Parent_module: Lookup failure (module): (root Main).A
13-
File "main.odoc":
14-
Warning: Failed to resolve module path identifier((root Main).B, false) Lookup failure (module): (root Main).B
15-
File "main.odoc":
16-
Warning: Failed to lookup type identifier((root Main).B, false).t Parent_module: Lookup failure (module): (root Main).B
17-
File "main.odoc":
18-
Warning: Failed to resolve module path identifier((root Main).A, false) Lookup failure (module): (root Main).A
1911
$ odoc html-generate --source main.ml --indent -o html main.odocl
2012

2113
Both modules should contain source links

test/sources/source.t/run.t

Lines changed: 0 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -88,30 +88,6 @@ Now, compile the pages with the --source option:
8888

8989
$ odoc compile -I . --source-name a.ml --source-parent-file src-source.odoc a.cmt
9090
$ odoc link -I . a.odoc
91-
File "a.odoc":
92-
Warning: Failed to resolve module path identifier((root A).F, false) Lookup failure (module): (root A).F
93-
File "a.odoc":
94-
Warning: Failed to resolve module path identifier((param (root A).F M), false).A Parent_module: Lookup failure (module): (param (root A).F M)
95-
File "a.odoc":
96-
Warning: Failed to lookup type identifier((root A).a1, false) Lookup failure (type): (root A).a1
97-
File "a.odoc":
98-
Warning: Failed to resolve module type path identifier((root A).T, false) Lookup failure (module type): (root A).T
99-
File "a.odoc":
100-
Warning: Failed to resolve module path identifier((root A).A, false) Lookup failure (module): (root A).A
101-
File "a.odoc":
102-
Warning: Failed to lookup value identifier((root A).y, false) Lookup failure (value): (root A).y
103-
File "a.odoc":
104-
Warning: Failed to lookup value identifier((root A).{x}2, false) Lookup failure (value): (root A).{x}2
105-
File "a.odoc":
106-
Warning: Failed to lookup value identifier((root A).{x}2, false) Lookup failure (value): (root A).{x}2
107-
File "a.odoc":
108-
Warning: Failed to lookup value identifier((root A).y, false) Lookup failure (value): (root A).y
109-
File "a.odoc":
110-
Warning: Failed to lookup value identifier((root A).{x}2, false) Lookup failure (value): (root A).{x}2
111-
File "a.odoc":
112-
Warning: Failed to lookup value identifier((root A).{x}2, false) Lookup failure (value): (root A).{x}2
113-
File "a.odoc":
114-
Warning: Failed to lookup value identifier((root A).{x}2, false) Lookup failure (value): (root A).{x}2
11591
$ odoc link -I . page-root.odoc
11692
$ odoc link -I . src-source.odoc
11793
$ odoc html-generate --indent -o html src-source.odocl

0 commit comments

Comments
 (0)