Skip to content

Commit c0117bb

Browse files
committed
Remove Unresolved_apply errors
1 parent df142dd commit c0117bb

File tree

3 files changed

+2
-6
lines changed

3 files changed

+2
-6
lines changed

src/xref2/errors.ml

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ module Tools_error = struct
2727
[ `Local of
2828
Env.t * Ident.path_module
2929
(* Internal error: Found local path during lookup *)
30-
| `Unresolved_apply (* [`Apply] argument is not [`Resolved] *)
3130
| `Find_failure
3231
| (* Internal error: the module was not found in the parent signature *)
3332
`Lookup_failure of
@@ -136,7 +135,6 @@ module Tools_error = struct
136135
| `LocalMT (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
137136
| `Local (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
138137
| `LocalType (_, id) -> Format.fprintf fmt "Local id found: %a" Ident.fmt id
139-
| `Unresolved_apply -> Format.fprintf fmt "Unresolved apply"
140138
| `Find_failure -> Format.fprintf fmt "Find failure"
141139
| `Lookup_failure m ->
142140
Format.fprintf fmt "Lookup failure (module): %a"
@@ -189,7 +187,6 @@ let is_unexpanded_module_type_of =
189187
| `Local _ -> false
190188
| `Find_failure -> false
191189
| `Lookup_failure _ -> false
192-
| `Unresolved_apply -> false
193190
| `Lookup_failure_root _ -> false
194191
| `Parent p -> inner (p :> any)
195192
| `Parent_sig p -> inner (p :> any)

src/xref2/tools.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -951,7 +951,8 @@ and resolve_module :
951951
match handle_apply ~mark_substituted env func_path' arg_path' m with
952952
| Ok (p, m) -> Ok (p, Component.Delayed.put_val m)
953953
| Error e -> Error (`Parent (`Parent_expr e)))
954-
| _ -> Error `Unresolved_apply)
954+
| Error e, _ -> Error e
955+
| _, Error e -> Error e)
955956
| `Identifier (i, hidden) ->
956957
of_option ~error:(`Lookup_failure i) (Env.(lookup_by_id s_module) i env)
957958
>>= fun (`Module (_, m)) ->

test/xref2/github_issue_944.t/run.t

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,5 @@ A quick test to repro the issue found in #944
44

55
$ odoc compile foo.cmti
66
$ odoc link foo.odoc
7-
File "foo.odoc":
8-
Warning: Failed to lookup type unresolvedroot(Stdlib).Set.Make(unresolvedroot(Stdlib).String).t Parent_module: Unresolved apply
97

108
$ odoc html-generate --indent -o html/ foo.odocl

0 commit comments

Comments
 (0)