Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions src/xref2/env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -744,6 +744,9 @@ let initial_env :
| Not_found -> (import :: imports, env)))
t.imports ([], initial_env)

let inherit_resolver env =
match env.resolver with Some r -> set_resolver empty r | None -> empty

let modules_of env =
let f acc = function `Module (id, m) -> (id, m) :: acc | _ -> acc in
StringMap.fold (fun _ e acc -> List.fold_left f acc e) env.elts []
Expand Down
3 changes: 3 additions & 0 deletions src/xref2/env.mli
Original file line number Diff line number Diff line change
Expand Up @@ -176,6 +176,9 @@ val initial_env :
resolver ->
Odoc_model.Lang.Compilation_unit.Import.t list * t

val inherit_resolver : t -> t
(** Create an empty environment reusing the same resolver. *)

val modules_of :
t ->
(Odoc_model.Paths.Identifier.Path.Module.t
Expand Down
16 changes: 13 additions & 3 deletions src/xref2/link.ml
Original file line number Diff line number Diff line change
Expand Up @@ -153,11 +153,17 @@ let rec comment_inline_element :
| None -> orig)
| y -> y

and paragraph env elts =
List.map (with_location (comment_inline_element env)) elts

and resolve_external_synopsis env synopsis =
let env = Env.inherit_resolver env in
paragraph env synopsis

and comment_nestable_block_element env parent
(x : Comment.nestable_block_element) =
match x with
| `Paragraph elts ->
`Paragraph (List.map (with_location (comment_inline_element env)) elts)
| `Paragraph elts -> `Paragraph (paragraph env elts)
| (`Code_block _ | `Verbatim _) as x -> x
| `List (x, ys) ->
`List
Expand All @@ -172,7 +178,11 @@ and comment_nestable_block_element env parent
(fun (r : Comment.module_reference) ->
match Ref_tools.resolve_module_reference env r.module_reference with
| Some (r, _, m) ->
let module_synopsis = synopsis_of_module env m in
let module_synopsis =
Opt.map
(resolve_external_synopsis env)
(synopsis_of_module env m)
in
{ Comment.module_reference = `Resolved r; module_synopsis }
| None -> r)
refs
Expand Down
9 changes: 9 additions & 0 deletions test/cases/toplevel_comments.mli
Original file line number Diff line number Diff line change
Expand Up @@ -70,3 +70,12 @@ class type ct =

class c2 : ct
(** Doc of [c2]. *)

module Ref_in_synopsis : sig
(** {!t}.

This reference should resolve in the context of this module, even when
used as a synopsis. *)

type t
end
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head>
<title>
Ref_in_synopsis (test_package+ml.Toplevel_comments.Ref_in_synopsis)
</title>
<link rel="stylesheet" href="../../../odoc.css">
<meta charset="utf-8">
<meta name="generator" content="odoc %%VERSION%%">
<meta name="viewport" content="width=device-width,initial-scale=1.0">
<script src="../../../highlight.pack.js"></script>
<script>
hljs.initHighlightingOnLoad();
</script>
</head>
<body class="odoc">
<nav class="odoc-nav">
<a href="../index.html">Up</a> – <a href="../../index.html">test_package+ml</a> » <a href="../index.html">Toplevel_comments</a> » Ref_in_synopsis
</nav>
<header class="odoc-preamble">
<h1>
Module <code><span>Toplevel_comments.Ref_in_synopsis</span></code>
</h1>
<p>
<a href="#type-t"><code>t</code></a>.
</p>
<p>
This reference should resolve in the context of this module, even when used as a synopsis.
</p>
</header>
<div class="odoc-content">
<div class="odoc-spec">
<div class="spec type" id="type-t">
<a href="#type-t" class="anchor"></a><code><span><span class="keyword">type</span> t</span></code>
</div>
</div>
</div>
</body>
</html>
10 changes: 10 additions & 0 deletions test/html/expect/test_package+ml/Toplevel_comments/index.html
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,16 @@ <h1>
</p>
</div>
</div>
<div class="odoc-spec">
<div class="spec module" id="module-Ref_in_synopsis">
<a href="#module-Ref_in_synopsis" class="anchor"></a><code><span><span class="keyword">module</span> </span><span><a href="Ref_in_synopsis/index.html">Ref_in_synopsis</a></span><span> : <span class="keyword">sig</span> ... <span class="keyword">end</span></span></code>
</div>
<div class="spec-doc">
<p>
<a href="Ref_in_synopsis/index.html#type-t"><code>t</code></a>.
</p>
</div>
</div>
</div>
</body>
</html>
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
<!DOCTYPE html>
<html xmlns="http://www.w3.org/1999/xhtml">
<head>
<title>
Ref_in_synopsis (test_package+re.Toplevel_comments.Ref_in_synopsis)
</title>
<link rel="stylesheet" href="../../../odoc.css">
<meta charset="utf-8">
<meta name="generator" content="odoc %%VERSION%%">
<meta name="viewport" content="width=device-width,initial-scale=1.0">
<script src="../../../highlight.pack.js"></script>
<script>
hljs.initHighlightingOnLoad();
</script>
</head>
<body class="odoc">
<nav class="odoc-nav">
<a href="../index.html">Up</a> – <a href="../../index.html">test_package+re</a> » <a href="../index.html">Toplevel_comments</a> » Ref_in_synopsis
</nav>
<header class="odoc-preamble">
<h1>
Module <code><span>Toplevel_comments.Ref_in_synopsis</span></code>
</h1>
<p>
<a href="#type-t"><code>t</code></a>.
</p>
<p>
This reference should resolve in the context of this module, even when used as a synopsis.
</p>
</header>
<div class="odoc-content">
<div class="odoc-spec">
<div class="spec type" id="type-t">
<a href="#type-t" class="anchor"></a><code><span><span class="keyword">type</span> t</span><span>;</span></code>
</div>
</div>
</div>
</body>
</html>
10 changes: 10 additions & 0 deletions test/html/expect/test_package+re/Toplevel_comments/index.html
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,16 @@ <h1>
</p>
</div>
</div>
<div class="odoc-spec">
<div class="spec module" id="module-Ref_in_synopsis">
<a href="#module-Ref_in_synopsis" class="anchor"></a><code><span><span class="keyword">module</span> </span><span><a href="Ref_in_synopsis/index.html">Ref_in_synopsis</a></span><span>: { ... }</span><span>;</span></code>
</div>
<div class="spec-doc">
<p>
<a href="Ref_in_synopsis/index.html#type-t"><code>t</code></a>.
</p>
</div>
</div>
</div>
</body>
</html>
1 change: 1 addition & 0 deletions test/html/test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -292,6 +292,7 @@ let source_files_all =
"class-c1";
"class-type-ct";
"class-c2";
"Ref_in_synopsis";
];
]

Expand Down
6 changes: 0 additions & 6 deletions test/print/dune

This file was deleted.

Loading