Skip to content

Commit 5395cfe

Browse files
committed
Fix search url of aliased modules
Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent 918a527 commit 5395cfe

File tree

8 files changed

+52
-25
lines changed

8 files changed

+52
-25
lines changed

src/search/entry.ml

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -49,9 +49,14 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim
4949

5050
type value_entry = { value : Value.value; type_ : TypeExpr.t }
5151

52+
type module_entry =
53+
| With_expansion
54+
| Alias_of of Odoc_model.Paths.Identifier.Any.t
55+
| Without_expansion
56+
5257
type kind =
5358
| TypeDecl of type_decl_entry
54-
| Module
59+
| Module of module_entry
5560
| Value of value_entry
5661
| Doc of doc_entry
5762
| Exception of constructor_entry
@@ -150,7 +155,7 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
150155
match x with
151156
| CompilationUnit u -> (
152157
match u.content with
153-
| Module m -> [ entry ~id:u.id ~doc:m.doc ~kind:Module ]
158+
| Module m -> [ entry ~id:u.id ~doc:m.doc ~kind:(Module With_expansion) ]
154159
| Pack _ -> [])
155160
| TypeDecl td ->
156161
let kind =
@@ -172,7 +177,18 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
172177
| Some Extensible -> []
173178
in
174179
td_entry :: subtype_entries
175-
| Module m -> [ entry ~id:m.id ~doc:m.doc ~kind:Module ]
180+
| Module m ->
181+
let kind =
182+
match m.Module.type_ with
183+
| ModuleType _ -> Module With_expansion
184+
| Alias (`Resolved path, _expansion) ->
185+
Module
186+
(Alias_of
187+
(Odoc_model.Paths.Path.Resolved.identifier
188+
(path :> Odoc_model.Paths.Path.Resolved.t)))
189+
| Alias (_, _expansion) -> Module Without_expansion
190+
in
191+
[ entry ~id:m.id ~doc:m.doc ~kind ]
176192
| Value v ->
177193
let kind = Value { value = v.value; type_ = v.type_ } in
178194
[ entry ~id:v.id ~doc:v.doc ~kind ]

src/search/entry.mli

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,9 +40,14 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim
4040

4141
type value_entry = { value : Value.value; type_ : TypeExpr.t }
4242

43+
type module_entry =
44+
| With_expansion
45+
| Alias_of of Odoc_model.Paths.Identifier.Any.t
46+
| Without_expansion
47+
4348
type kind =
4449
| TypeDecl of type_decl_entry
45-
| Module
50+
| Module of module_entry
4651
| Value of value_entry
4752
| Doc of doc_entry
4853
| Exception of constructor_entry

src/search/html.ml

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,15 @@ type html = Html_types.div_content Tyxml.Html.elt
33
open Odoc_model
44
open Lang
55

6-
let url id =
7-
match
8-
Odoc_document.Url.from_identifier ~stop_before:false
9-
(id :> Odoc_model.Paths.Identifier.t)
10-
with
6+
let url { Entry.id; kind; doc = _ } =
7+
let open Entry in
8+
let url_id, stop_before =
9+
match kind with
10+
| Module Without_expansion -> (id, true)
11+
| Module (Alias_of id) -> (id, false)
12+
| _ -> (id, false)
13+
in
14+
match Odoc_document.Url.from_identifier ~stop_before url_id with
1115
| Ok url ->
1216
let config =
1317
Odoc_html.Config.v ~search_result:true ~semantic_uris:false
@@ -147,7 +151,7 @@ let string_of_kind =
147151
| Field _ -> kind_field
148152
| ExtensionConstructor _ -> kind_extension_constructor
149153
| TypeDecl _ -> kind_typedecl
150-
| Module -> kind_module
154+
| Module _ -> kind_module
151155
| Value _ -> kind_value
152156
| Exception _ -> kind_exception
153157
| Class_type _ -> kind_class_type
@@ -172,7 +176,7 @@ let rhs_of_kind (entry : Entry.kind) =
172176
| Constructor t | ExtensionConstructor t | Exception t ->
173177
Some (constructor_rhs t)
174178
| Field f -> Some (field_rhs f)
175-
| Module | Class_type _ | Method _ | Class _ | TypeExtension _ | ModuleType
179+
| Module _ | Class_type _ | Method _ | Class _ | TypeExtension _ | ModuleType
176180
| Doc _ ->
177181
None
178182

src/search/html.mli

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,7 @@ type html = Html_types.div_content Tyxml.Html.elt
44

55
val of_entry : Entry.t -> html list
66

7-
val url :
8-
Odoc_model.Paths.Identifier.Any.t ->
9-
(string, Odoc_document.Url.Error.t) Result.result
7+
val url : Entry.t -> (string, Odoc_document.Url.Error.t) Result.result
108

119
(** The below is intended for search engine that do not use the Json output but
1210
Odoc as a library. Most search engine will use their own representation

src/search/json_index/json_display.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
open Odoc_search
22

3-
let of_entry { Entry.id; doc = _; kind = _ } h =
4-
match Html.url id with
3+
let of_entry entry h =
4+
match Html.url entry with
55
| Result.Ok url ->
66
let html =
77
h

src/search/json_index/json_search.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ let of_entry ({ Entry.id; doc; kind } as entry) html =
124124
("manifest", manifest);
125125
("constraints", constraints);
126126
]
127-
| Module -> return "Module" []
127+
| Module _ -> return "Module" []
128128
| Value { value = _; type_ } ->
129129
return "Value" [ ("type", `String (Text.of_type type_)) ]
130130
| Doc Paragraph -> return "Doc" [ ("subkind", `String "Paragraph") ]

test/search/module_aliases.t/main.ml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,3 +3,6 @@ module X = struct
33
end
44

55
module Y = X
6+
module Z = Y
7+
8+
module L = Stdlib.List

test/search/module_aliases.t/run.t

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -8,12 +8,13 @@ Compile and link the documentation
88
$ odoc link main.odoc
99
$ odoc compile-index main.odocl
1010

11-
We have a problem: The ID for Y generates an URL to a file which is not
12-
generated (as the module does not have an expansion).
11+
Module with expansions (aliased or not) redirect to their expansions, while
12+
module without expansions redirect to their definition point.
1313

14-
$ cat index.json | jq | grep url |grep Y
15-
"url": "Main/Y/index.html",
16-
17-
$ odoc html-generate -o html main.odocl && ls Main/Y/index.html
18-
ls: cannot access 'Main/Y/index.html': No such file or directory
19-
[2]
14+
$ cat index.json | jq -r '.[] | "\(.id[-1].name) -> \(.display.url)"'
15+
Main -> Main/index.html
16+
X -> Main/X/index.html
17+
x -> Main/X/index.html#val-x
18+
Y -> Main/X/index.html
19+
Z -> Main/X/index.html
20+
L -> Main/index.html#module-L

0 commit comments

Comments
 (0)