Skip to content

Commit

Permalink
Sidebar: Actually add implementations to the sidebar
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Nov 27, 2024
1 parent 99c393b commit b5b762c
Show file tree
Hide file tree
Showing 10 changed files with 65 additions and 11 deletions.
3 changes: 2 additions & 1 deletion src/document/sidebar.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,8 @@ end = struct
in
let f x =
match x.Entry.kind with
| Dir | Page _ | Module _ | Class_type _ | Class _ | ModuleType _ ->
| Dir | Page _ | Module _ | Class_type _ | Class _ | ModuleType _ | Impl
->
Some (map_entry x)
| _ -> None
in
Expand Down
1 change: 1 addition & 0 deletions src/index/entry.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ type kind =
| Constructor of constructor_entry
| Field of field_entry
| Page of Odoc_model.Frontmatter.t
| Impl
| Dir

type t = {
Expand Down
1 change: 1 addition & 0 deletions src/index/entry.mli
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ type kind =
| Constructor of constructor_entry
| Field of field_entry
| Page of Odoc_model.Frontmatter.t
| Impl
| Dir

type t = {
Expand Down
5 changes: 5 additions & 0 deletions src/index/in_progress.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,11 @@ let dirs (_, dir_content) =
let modules (_, dir_content) =
RMH.fold (fun id payload acc -> (id, payload) :: acc) dir_content.modules []

let implementations (_, dir_content) =
SPH.fold
(fun id payload acc -> (id, payload) :: acc)
dir_content.implementations []

let rec get_or_create (dir : in_progress) (id : container_page) : in_progress =
let _, { dirs = parent_dirs; _ } =
match get_parent id with
Expand Down
4 changes: 4 additions & 0 deletions src/index/in_progress.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,5 +36,9 @@ val dirs : in_progress -> (Id.ContainerPage.t * in_progress) list
val modules : in_progress -> (Id.RootModule.t * Skeleton.t) list
(** [modules dir] returns the modules in [dir] *)

val implementations :
in_progress -> (Id.SourcePage.t * Lang.Implementation.t) list
(** [implementations dir] returns the implementations in [dir] *)

val index : in_progress -> (Id.LeafPage.t * Lang.Page.t) option
(** [index dir] returns the potential [index] leaf page in [dir] *)
12 changes: 11 additions & 1 deletion src/index/skeleton_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,11 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
let id = page.name in
Entry.entry ~kind ~doc ~id
in
let entry_of_impl id =
let kind = Entry.Impl in
let doc = [] in
Entry.entry ~kind ~doc ~id
in
let children_order, index =
match In_progress.index dir with
| Some (_, page) ->
Expand Down Expand Up @@ -72,7 +77,12 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
In_progress.modules dir
|> List.map (fun (id, payload) -> ((id :> Id.t), payload))
in
leafs @ dirs @ modules
let implementations =
In_progress.implementations dir
|> List.map (fun (id, _impl) ->
((id :> Id.t), Tree.leaf @@ entry_of_impl id))
in
leafs @ dirs @ modules @ implementations
in
match children_order with
| None -> ([], contents)
Expand Down
2 changes: 1 addition & 1 deletion src/model/paths.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ module Identifier = struct
| `Method (_, name) -> MethodName.to_string name
| `InstanceVariable (_, name) -> InstanceVariableName.to_string name
| `Label (_, name) -> LabelName.to_string name
| `SourcePage (dir, name) -> name_aux (dir :> t) ^ name
| `SourcePage (_, name) -> name
| `SourceLocation (x, anchor) ->
name_aux (x :> t) ^ "#" ^ DefName.to_string anchor
| `SourceLocationMod x -> name_aux (x :> t)
Expand Down
5 changes: 4 additions & 1 deletion src/search/html.ml
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,8 @@ let kind_page = "page"

let kind_dir = "dir"

let kind_impl = "impl"

let kind_typedecl = "type"

let kind_module = "mod"
Expand Down Expand Up @@ -170,6 +172,7 @@ let string_of_kind =
| ModuleType _ -> kind_module_type
| Doc -> kind_doc
| Page _ -> kind_page
| Impl -> kind_impl
| Dir -> kind_dir

let value_rhs (t : Entry.value_entry) = " : " ^ Text.of_type t.type_
Expand All @@ -188,7 +191,7 @@ let rhs_of_kind (entry : Entry.kind) =
Some (constructor_rhs t)
| Field f -> Some (field_rhs f)
| Module _ | Class_type _ | Method _ | Class _ | TypeExtension _
| ModuleType _ | Doc | Page _ | Dir ->
| ModuleType _ | Doc | Page _ | Impl | Dir ->
None

let names_of_id id =
Expand Down
1 change: 1 addition & 0 deletions src/search/json_index/json_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,7 @@ let of_entry ({ Entry.id; doc; kind } as entry) html occurrences =
("parent_type", `String (Text.of_type parent_type));
]
| Page _ -> return "Page" []
| Impl -> return "Impl" []
| Dir -> return "Dir" []
in
let occurrences =
Expand Down
42 changes: 35 additions & 7 deletions test/roots_and_hierarchy/sidebar.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,14 @@
$ odoc compile --output-dir _odoc/ --parent-id pkg file.mld
$ odoc compile --output-dir _odoc/ --parent-id pkg index.mld
$ odoc compile --output-dir _odoc/ --parent-id pkg/libname unit.cmt
$ odoc compile-impl --output-dir _odoc/ --parent-id pkg/src/libname unit.cmt
$ odoc compile-impl --output-dir _odoc/ --source-id pkg/src/libname/unit.ml --parent-id pkg/libname unit.cmt

$ odoc link -P pkg:_odoc/pkg/ -L libname:_odoc/pkg/libname _odoc/pkg/page-file.odoc
$ odoc link -P pkg:_odoc/pkg/ _odoc/pkg/dir1/page-my_page.odoc
$ odoc link -P pkg:_odoc/pkg/ _odoc/pkg/dir1/page-index.odoc
$ odoc link -P pkg:_odoc/pkg/ _odoc/pkg/page-index.odoc
$ odoc link -P pkg:_odoc/pkg/ _odoc/pkg/libname/unit.odoc
$ odoc link -P pkg:_odoc/pkg/ _odoc/pkg/libname/impl-unit.odoc

$ odoc compile-index --root _odoc/pkg/
$ odoc sidebar-generate index.odoc-index
Expand Down Expand Up @@ -109,6 +110,32 @@ A json version of a sidebar can be obtained using the sidebar-generate command:
]
}
]
},
{
"node": {
"url": null,
"kind": null,
"content": "src"
},
"children": [
{
"node": {
"url": null,
"kind": null,
"content": "libname"
},
"children": [
{
"node": {
"url": "pkg/src/libname/unit.ml.html",
"kind": "source",
"content": "unit.ml"
},
"children": []
}
]
}
]
}
]
}
Expand All @@ -123,13 +150,14 @@ A json version of a sidebar can be obtained using the sidebar-generate command:
<li>libname
<ul><li><a href="libname/Unit/index.html">Unit</a></li></ul>
</li>
<li>src
<ul>
<li>libname
<ul><li><a href="src/libname/unit.ml.html">unit.ml</a></li></ul>
</li>
</ul>
</li>
</ul>
</li>
</ul>
</nav>
</div><div class="odoc-content"></div>
</body>
</html>

$ cat html/pkg/libname/Unit/X/index.html | grep odoc-global-toc -A 15
<nav class="odoc-toc odoc-global-toc">
Expand Down

0 comments on commit b5b762c

Please sign in to comment.