Skip to content

Commit

Permalink
Fix search url of aliased modules
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Apr 12, 2024
1 parent 918a527 commit 5395cfe
Show file tree
Hide file tree
Showing 8 changed files with 52 additions and 25 deletions.
22 changes: 19 additions & 3 deletions src/search/entry.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,9 +49,14 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim

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

type module_entry =
| With_expansion
| Alias_of of Odoc_model.Paths.Identifier.Any.t
| Without_expansion

type kind =
| TypeDecl of type_decl_entry
| Module
| Module of module_entry
| Value of value_entry
| Doc of doc_entry
| Exception of constructor_entry
Expand Down Expand Up @@ -150,7 +155,7 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
match x with
| CompilationUnit u -> (
match u.content with
| Module m -> [ entry ~id:u.id ~doc:m.doc ~kind:Module ]
| Module m -> [ entry ~id:u.id ~doc:m.doc ~kind:(Module With_expansion) ]
| Pack _ -> [])
| TypeDecl td ->
let kind =
Expand All @@ -172,7 +177,18 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
| Some Extensible -> []
in
td_entry :: subtype_entries
| Module m -> [ entry ~id:m.id ~doc:m.doc ~kind:Module ]
| Module m ->
let kind =
match m.Module.type_ with
| ModuleType _ -> Module With_expansion
| Alias (`Resolved path, _expansion) ->
Module
(Alias_of
(Odoc_model.Paths.Path.Resolved.identifier
(path :> Odoc_model.Paths.Path.Resolved.t)))
| Alias (_, _expansion) -> Module Without_expansion
in
[ entry ~id:m.id ~doc:m.doc ~kind ]
| Value v ->
let kind = Value { value = v.value; type_ = v.type_ } in
[ entry ~id:v.id ~doc:v.doc ~kind ]
Expand Down
7 changes: 6 additions & 1 deletion src/search/entry.mli
Original file line number Diff line number Diff line change
Expand Up @@ -40,9 +40,14 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim

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

type module_entry =
| With_expansion
| Alias_of of Odoc_model.Paths.Identifier.Any.t
| Without_expansion

type kind =
| TypeDecl of type_decl_entry
| Module
| Module of module_entry
| Value of value_entry
| Doc of doc_entry
| Exception of constructor_entry
Expand Down
18 changes: 11 additions & 7 deletions src/search/html.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,15 @@ type html = Html_types.div_content Tyxml.Html.elt
open Odoc_model
open Lang

let url id =
match
Odoc_document.Url.from_identifier ~stop_before:false
(id :> Odoc_model.Paths.Identifier.t)
with
let url { Entry.id; kind; doc = _ } =
let open Entry in
let url_id, stop_before =
match kind with
| Module Without_expansion -> (id, true)
| Module (Alias_of id) -> (id, false)
| _ -> (id, false)
in
match Odoc_document.Url.from_identifier ~stop_before url_id with
| Ok url ->
let config =
Odoc_html.Config.v ~search_result:true ~semantic_uris:false
Expand Down Expand Up @@ -147,7 +151,7 @@ let string_of_kind =
| Field _ -> kind_field
| ExtensionConstructor _ -> kind_extension_constructor
| TypeDecl _ -> kind_typedecl
| Module -> kind_module
| Module _ -> kind_module
| Value _ -> kind_value
| Exception _ -> kind_exception
| Class_type _ -> kind_class_type
Expand All @@ -172,7 +176,7 @@ let rhs_of_kind (entry : Entry.kind) =
| Constructor t | ExtensionConstructor t | Exception t ->
Some (constructor_rhs t)
| Field f -> Some (field_rhs f)
| Module | Class_type _ | Method _ | Class _ | TypeExtension _ | ModuleType
| Module _ | Class_type _ | Method _ | Class _ | TypeExtension _ | ModuleType
| Doc _ ->
None

Expand Down
4 changes: 1 addition & 3 deletions src/search/html.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,7 @@ type html = Html_types.div_content Tyxml.Html.elt

val of_entry : Entry.t -> html list

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

(** The below is intended for search engine that do not use the Json output but
Odoc as a library. Most search engine will use their own representation
Expand Down
4 changes: 2 additions & 2 deletions src/search/json_index/json_display.ml
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
open Odoc_search

let of_entry { Entry.id; doc = _; kind = _ } h =
match Html.url id with
let of_entry entry h =
match Html.url entry with
| Result.Ok url ->
let html =
h
Expand Down
2 changes: 1 addition & 1 deletion src/search/json_index/json_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ let of_entry ({ Entry.id; doc; kind } as entry) html =
("manifest", manifest);
("constraints", constraints);
]
| Module -> return "Module" []
| Module _ -> return "Module" []
| Value { value = _; type_ } ->
return "Value" [ ("type", `String (Text.of_type type_)) ]
| Doc Paragraph -> return "Doc" [ ("subkind", `String "Paragraph") ]
Expand Down
3 changes: 3 additions & 0 deletions test/search/module_aliases.t/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,6 @@ module X = struct
end

module Y = X
module Z = Y

module L = Stdlib.List
17 changes: 9 additions & 8 deletions test/search/module_aliases.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,12 +8,13 @@ Compile and link the documentation
$ odoc link main.odoc
$ odoc compile-index main.odocl

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

$ cat index.json | jq | grep url |grep Y
"url": "Main/Y/index.html",

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

0 comments on commit 5395cfe

Please sign in to comment.