@@ -135,8 +135,9 @@ and should_resolve : Paths.Path.t -> bool =
135
135
(* | `Resolved p -> should_reresolve (p :> Paths.Path.Resolved.t) *)
136
136
(* | _ -> true *)
137
137
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 ->
140
141
if not (should_resolve (p :> Paths.Path.t )) then p
141
142
else
142
143
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 =
150
151
let result = Tools. reresolve_type env p' in
151
152
`Resolved Lang_of. (Path. resolved_type (empty () ) result)
152
153
| 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 ;
154
156
p)
155
157
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 ->
196
209
if not (should_resolve (p :> Paths.Path.t )) then p
197
210
else
198
211
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
206
219
let result = Tools. reresolve_class_type env p' in
207
220
`Resolved Lang_of. (Path. resolved_class_type (empty () ) result)
208
221
| 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 ;
210
224
p)
211
225
212
226
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 ->
215
232
if not (should_resolve (p :> Paths.Path.t )) then p
216
233
else
217
234
let cp = Component.Of_Lang. (module_type_path (empty () ) p) in
@@ -225,11 +242,13 @@ and module_type_path :
225
242
let result = Tools. reresolve_module_type env p' in
226
243
`Resolved Lang_of. (Path. resolved_module_type (empty () ) result)
227
244
| 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 ;
229
247
p)
230
248
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 ->
233
252
if not (should_resolve (p :> Paths.Path.t )) then p
234
253
else
235
254
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 =
244
263
`Resolved Lang_of. (Path. resolved_module (empty () ) result)
245
264
| Error _ when is_forward p -> p
246
265
| 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 ;
248
268
p)
249
269
250
270
let rec comment_inline_element :
@@ -433,16 +453,16 @@ let rec unit env t =
433
453
Value
434
454
(jump_to v
435
455
(Shape_tools. lookup_value_path env)
436
- (value_path env))
456
+ (value_path ~report_errors: false env))
437
457
| 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))
439
459
| ModuleType v ->
440
460
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))
443
463
| Constructor v ->
444
464
Constructor
445
- (jump_to v (fun _ -> None ) (constructor_path env))
465
+ (jump_to v (fun _ -> None ) (constructor_path ~report_errors: false env))
446
466
| i -> i
447
467
in
448
468
(info, pos))
0 commit comments