Skip to content

Commit 6238376

Browse files
committed
Load unit in the environment before linking the first doc comment
The first comment of a module would be linked with an empty environment. Also make sure that labels in that doc comment are added to the env.
1 parent 2096f96 commit 6238376

File tree

4 files changed

+13
-19
lines changed

4 files changed

+13
-19
lines changed

src/xref2/env.ml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -721,10 +721,6 @@ let rec open_signature : Odoc_model.Lang.Signature.t -> t -> t =
721721
| Odoc_model.Lang.Signature.Open o -> open_signature o.expansion env)
722722
e s.items
723723

724-
let open_unit : Odoc_model.Lang.Compilation_unit.t -> t -> t =
725-
fun unit env ->
726-
match unit.content with Module s -> open_signature s env | Pack _ -> env
727-
728724
let initial_env :
729725
Odoc_model.Lang.Compilation_unit.t ->
730726
resolver ->

src/xref2/env.mli

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -189,8 +189,6 @@ val open_class_signature : Odoc_model.Lang.ClassSignature.t -> t -> t
189189

190190
val open_signature : Odoc_model.Lang.Signature.t -> t -> t
191191

192-
val open_unit : Odoc_model.Lang.Compilation_unit.t -> t -> t
193-
194192
val initial_env :
195193
Odoc_model.Lang.Compilation_unit.t ->
196194
resolver ->

src/xref2/link.ml

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -107,18 +107,18 @@ and module_path : Env.t -> Paths.Path.Module.t -> Paths.Path.Module.t =
107107
let rec unit (resolver : Env.resolver) t =
108108
let open Compilation_unit in
109109
let imports, env = Env.initial_env t resolver in
110-
{
111-
t with
112-
content = content env t.id t.content;
113-
doc = comment_docs env t.doc;
114-
imports;
115-
}
116-
117-
and content env id =
118-
let open Compilation_unit in
119-
function
120-
| Module m -> Module (signature env (id :> Id.Signature.t) m)
121-
| Pack p -> Pack p
110+
let env = (* Add doc to env *) Env.add_docs t.doc env in
111+
let content, env =
112+
match t.content with
113+
| Module sg ->
114+
(* Inline [signature] to keep [env]. *)
115+
let env = Env.open_signature sg env in
116+
let items = signature_items env (t.id :> Id.Signature.t) sg.items in
117+
(Module { sg with items }, env)
118+
| Pack _ as p -> (p, env)
119+
in
120+
let doc = comment_docs env t.doc in
121+
{ t with content; doc; imports }
122122

123123
and value_ env parent t =
124124
let open Value in

test/xref2/references_scope.t/run.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77
The references from a.mli, see the attached text to recognize them:
88

99
$ odoc_print a.odocl | jq_scan_references
10-
[{"`Dot":[{"`Root":["B","`TUnknown"]},"C"]},[{"`Word":"Doc-relative"}]]
10+
[{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"`RootPage":"test"},"A"]},"B"]}},"C"]}},[{"`Word":"Doc-relative"}]]
1111
[{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"`RootPage":"test"},"A"]}},"B"]},"C"]}},[{"`Word":"Doc-absolute"}]]
1212
[{"`Resolved":{"`Module":[{"`Identifier":{"`Module":[{"`Root":[{"`RootPage":"test"},"A"]},"B"]}},"C"]}},[{"`Word":"Defined-below"}]]
1313
[{"`Resolved":{"`Module":[{"`Module":[{"`Identifier":{"`Root":[{"`RootPage":"test"},"A"]}},"B"]},"C"]}},[{"`Word":"Defined-below-but-absolute"}]]

0 commit comments

Comments
 (0)