Skip to content

Commit

Permalink
Add info about displayed name in references
Browse files Browse the repository at this point in the history
  • Loading branch information
gpetiot committed Aug 29, 2023
1 parent c536c9d commit 044e06b
Show file tree
Hide file tree
Showing 7 changed files with 18 additions and 13 deletions.
2 changes: 1 addition & 1 deletion src/document/comment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module Reference = struct
| `Field (r, s) -> render_resolved (r :> t) ^ "." ^ FieldName.to_string s
| `Extension (r, s) ->
render_resolved (r :> t) ^ "." ^ ExtensionName.to_string s
| `ExtensionDecl (r, s) ->
| `ExtensionDecl (r, _, s) ->
render_resolved (r :> t) ^ "." ^ ExtensionName.to_string s
| `Exception (r, s) ->
render_resolved (r :> t) ^ "." ^ ExceptionName.to_string s
Expand Down
2 changes: 1 addition & 1 deletion src/model/paths.ml
Original file line number Diff line number Diff line change
Expand Up @@ -855,7 +855,7 @@ module Reference = struct
Identifier.Mk.constructor (parent_type_identifier s, n)
| `Extension (p, q) ->
Identifier.Mk.extension (parent_signature_identifier p, q)
| `ExtensionDecl (p, q) ->
| `ExtensionDecl (p, q, _) ->
Identifier.Mk.extension_decl (parent_signature_identifier p, q)
| `Exception (p, q) ->
Identifier.Mk.exception_ (parent_signature_identifier p, q)
Expand Down
6 changes: 3 additions & 3 deletions src/model/paths_types.ml
Original file line number Diff line number Diff line change
Expand Up @@ -803,7 +803,6 @@ and Resolved_reference : sig
[ `Identifier of Identifier.reference_constructor
| `Constructor of datatype * ConstructorName.t
| `Extension of signature * ExtensionName.t
| `ExtensionDecl of signature * ExtensionName.t
| `Exception of signature * ExceptionName.t ]
(** @canonical Odoc_model.Paths.Reference.Resolved.Constructor.t *)

Expand All @@ -820,7 +819,8 @@ and Resolved_reference : sig

type extension_decl =
[ `Identifier of Identifier.reference_extension
| `ExtensionDecl of signature * ExtensionName.t
| `ExtensionDecl of
signature * ExtensionName.t (* url *) * ExtensionName.t (* displayed *)
| `Exception of signature * ExceptionName.t ]
(** @canonical Odoc_model.Paths.Reference.Resolved.Extension.t *)

Expand Down Expand Up @@ -874,7 +874,7 @@ and Resolved_reference : sig
| `Constructor of datatype * ConstructorName.t
| `Field of parent * FieldName.t
| `Extension of signature * ExtensionName.t
| `ExtensionDecl of signature * ExtensionName.t
| `ExtensionDecl of signature * ExtensionName.t * ExtensionName.t
| `Exception of signature * ExceptionName.t
| `Value of signature * ValueName.t
| `Class of signature * ClassName.t
Expand Down
8 changes: 5 additions & 3 deletions src/model_desc/paths_desc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -350,11 +350,13 @@ module General_paths = struct
( "`Extension",
((x1 :> rr), x2),
Pair (resolved_reference, Names.extensionname) )
| `ExtensionDecl (x1, x2) ->
| `ExtensionDecl (x1, x2, x3) ->
C
( "`ExtensionDecl",
((x1 :> rr), x2),
Pair (resolved_reference, Names.extensionname) )
((x1 :> rr), x2, x3),
Triple
(resolved_reference, Names.extensionname, Names.extensionname)
)
| `Field (x1, x2) ->
C
( "`Field",
Expand Down
2 changes: 1 addition & 1 deletion src/xref2/component.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1417,7 +1417,7 @@ module Fmt = struct
Format.fprintf ppf "%a.%s" model_resolved_reference
(parent :> t)
(ExtensionName.to_string name)
| `ExtensionDecl (parent, name) ->
| `ExtensionDecl (parent, name, _) ->
Format.fprintf ppf "%a.%s" model_resolved_reference
(parent :> t)
(ExtensionName.to_string name)
Expand Down
7 changes: 5 additions & 2 deletions src/xref2/ref_tools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -404,7 +404,9 @@ module ED = struct
let parent_id = match id.iv with `Extension (parent, _) -> parent in
Ok
(`ExtensionDecl
(`Identifier parent_id, ExtensionName.make_std c.name))
( `Identifier parent_id,
ExtensionName.make_std c.name,
ExtensionName.make_std name ))

let in_signature _env ((parent', parent_cp, sg) : signature_lookup_result)
name =
Expand All @@ -413,7 +415,8 @@ module ED = struct
>>= fun (`FExt (ext, _) : Find.extension) ->
match ext.constructors with
| [] -> assert false
| c :: _ -> Ok (`ExtensionDecl (parent', ExtensionName.make_std c.name))
| c :: _ ->
Ok (`ExtensionDecl (parent', ExtensionName.make_std c.name, name))
end

module EX = struct
Expand Down
4 changes: 2 additions & 2 deletions test/xref2/github_issue_932.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ The rendered html
--
<li>extension-decl-A : <a href="#extension-decl-A"><code>Foo.A</code></a>
</li>
<li>extension-decl-B : <a href="#extension-decl-A"><code>Foo.A</code></a>
<li>extension-decl-B : <a href="#extension-decl-A"><code>Foo.B</code></a>
</li><li>extension-A : <a href="#extension-A"><code>A</code></a></li>
<li>extension-B : <a href="#extension-B"><code>B</code></a></li>
<li>A : <a href="#extension-A"><code>A</code></a></li>
Expand All @@ -53,7 +53,7 @@ The rendered html
<a href="M/index.html#extension-decl-A"><code>M.A</code></a>
</li>
<li>M.extension-decl-B :
<a href="M/index.html#extension-decl-A"><code>M.A</code></a>
<a href="M/index.html#extension-decl-A"><code>M.B</code></a>
</li>
<li>M.extension-A :
<a href="M/index.html#extension-A"><code>M.A</code></a>
Expand Down

0 comments on commit 044e06b

Please sign in to comment.