Skip to content

Commit

Permalink
Fix urls
Browse files Browse the repository at this point in the history
  • Loading branch information
gpetiot committed Aug 29, 2023
1 parent f2180e3 commit 76f408f
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 5 deletions.
14 changes: 14 additions & 0 deletions src/xref2/find.ml
Original file line number Diff line number Diff line change
Expand Up @@ -289,6 +289,20 @@ let extension_in_sig sg name =
| Signature.TypExt t -> inner t t.Extension.constructors
| _ -> None)

let extension_decl_in_sig sg name =
let rec inner t first = function
| ec :: _ when ec.Extension.Constructor.name = name ->
Some (`FExt (t, first))
| _ :: tl -> inner t first tl
| [] -> None
in
find_in_sig sg (function
| Signature.TypExt t -> (
match t.Extension.constructors with
| [] -> None
| first :: _ as cs -> inner t first cs)
| _ -> None)

let label_parent_in_sig sg name =
filter_in_sig sg (function
| Signature.Module (id, _, m) when N.module_ id = name ->
Expand Down
2 changes: 2 additions & 0 deletions src/xref2/find.mli
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,8 @@ val exception_in_sig : Signature.t -> string -> exception_ option

val extension_in_sig : Signature.t -> string -> extension option

val extension_decl_in_sig : Signature.t -> string -> extension option

val any_in_type : TypeDecl.t -> string -> any_in_type option

val any_in_typext : Extension.t -> string -> extension option
Expand Down
9 changes: 6 additions & 3 deletions src/xref2/ref_tools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -397,13 +397,16 @@ module ED = struct

let in_env env name =
env_lookup_by_name Env.s_extension_decl name env
>>= fun (`ExtensionDecl (id, _)) -> Ok (`Identifier id :> t)
>>= fun (`ExtensionDecl (_, c)) ->
env_lookup_by_name Env.s_extension c.name env
>>= fun (`Extension (id, _)) -> Ok (`Identifier id :> t)

let in_signature _env ((parent', parent_cp, sg) : signature_lookup_result)
name =
let sg = Tools.prefix_signature (parent_cp, sg) in
find Find.extension_in_sig sg (ExtensionName.to_string name) >>= fun _ ->
Ok (`ExtensionDecl (parent', name))
find Find.extension_decl_in_sig sg (ExtensionName.to_string name)
>>= fun (`FExt (_, c) : Find.extension) ->
Ok (`ExtensionDecl (parent', ExtensionName.make_std c.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 @@ -42,7 +42,7 @@ The rendered html
</ol>
--
<li>extension-decl-A : <a href="#extension-A"><code>A</code></a></li>
<li>extension-decl-B : <a href="#extension-B"><code>B</code></a></li>
<li>extension-decl-B : <a href="#extension-A"><code>A</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 @@ -52,7 +52,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-B"><code>M.B</code></a>
<a href="M/index.html#extension-decl-A"><code>M.A</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 76f408f

Please sign in to comment.