Skip to content

Commit 82c4d01

Browse files
committed
Sidebar and index overhaul
This commit includes multiple modifications: Trees ---------- Odoc used to have several representations of trees: one for the page sidebar in the model, one for the document sidebar, and (in a squashed commit) one for the unit sidebar. All trees now have the same type, making the different passes (eg model -> document for pages and units) much easier, at a small cost (the type is less tailored to the usecase, eg the payload cannot be different in leafs than in node, which was the case before in the page hierarchy). Trees (and forests) have basic iterators defined. The index for units ------------------------ The index for the units values used to be a hashtable from ID to entry. The problem was that you cannot rebuild a sidebar from that: you lose the order between children. The index for units now is a tree of index entries. The sidebar for units ------------------------- The sidebar for units finally shows more than just the root module. However, it does not show the full hierarchy either, as that would be overwhelming in the case of big modules. The sidebar shows: - Only entries that could have had an expansion: modules, modules types, classes and class types. - The current page (highlighted), - The children of the current page, (highlighted differently), - The ancestors of the current page, - The children of the ancestors of the current page, - Nothing else. If you allow me, I like to use the github syntax for mathematics 😄. The sidebar has the property that it displays the smallest set $S$ that: - Contains only modules, modules types, classes and class types. - Contains the current page: $current\_page\in S$, - Is ancestor-closed: if $e\in S$ then $parent(e)\in S$, - Is sibling-closed: if $e\in S$ and $parent(e)=parent(f)$, then $f\in S$ The last property is important to avoid displaying only part of the children of a parent, requiring to display some `...` to show that some entries were omitted. Organization in directories and libraries ----------------------------------------------------- The `search/` folder and its associated `odoc_search` library was separated in two: the original one and the new `index/` and `odoc_index` which contains everything that an index should contain: both the info for the sidebar and for the search index.
1 parent 57a9ccf commit 82c4d01

File tree

51 files changed

+1048
-1046
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

51 files changed

+1048
-1046
lines changed

src/document/dune

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,4 +14,4 @@
1414
(backend bisect_ppx))
1515
(instrumentation
1616
(backend landmarks --auto))
17-
(libraries odoc_model fpath astring syntax_highlighter odoc_utils))
17+
(libraries odoc_model fpath astring syntax_highlighter odoc_utils odoc_index))

src/document/renderer.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ let string_of_syntax = function OCaml -> "ml" | Reason -> "re"
66

77
type page = {
88
filename : Fpath.t;
9+
path : Url.Path.t;
910
content : Format.formatter -> unit;
1011
children : page list;
1112
}
@@ -23,7 +24,7 @@ type input =
2324

2425
type 'a t = {
2526
name : string;
26-
render : 'a -> Types.Block.t option -> Types.Document.t -> page list;
27+
render : 'a -> Sidebar.t option -> Types.Document.t -> page list;
2728
filepath : 'a -> Url.Path.t -> Fpath.t;
2829
}
2930

src/document/sidebar.ml

Lines changed: 126 additions & 79 deletions
Original file line numberDiff line numberDiff line change
@@ -2,118 +2,163 @@ open Odoc_utils
22
open Types
33

44
let sidebar_toc_entry id content =
5-
let href = id |> Url.Path.from_identifier |> Url.from_path in
5+
let href =
6+
(id :> Odoc_model.Paths.Identifier.t)
7+
|> Url.from_identifier ~stop_before:false
8+
|> Result.get_ok
9+
in
610
let target = Target.Internal (Resolved href) in
711
inline @@ Inline.Link { target; content; tooltip = None }
812

913
module Toc : sig
1014
type t
1115

12-
val of_lang : Odoc_model.Sidebar.PageToc.t -> t
16+
val of_page_hierarchy : Odoc_index.Page_hierarchy.t -> t
17+
18+
val of_skeleton : Odoc_index.Skeleton.t -> t
1319

14-
val to_sidebar :
15-
?fallback:string -> (Url.Path.t * Inline.one -> Block.one) -> t -> Block.t
20+
val to_block : prune:bool -> Url.Path.t -> t -> Block.t
1621
end = struct
17-
type t = Item of (Url.Path.t * Inline.one) option * t list
22+
type t = (Url.t * Inline.one) option Tree.t
1823

19-
open Odoc_model.Sidebar
20-
open Odoc_model.Paths.Identifier
24+
module Id = Odoc_model.Paths.Identifier
2125

22-
let of_lang (dir : PageToc.t) =
23-
let rec of_lang ~parent_id ((content, index) : PageToc.t) =
24-
let title, parent_id =
26+
let of_page_hierarchy (dir : Odoc_index.Page_hierarchy.t) =
27+
let fun_ index =
28+
let payload =
2529
match index with
26-
| Some (index_id, title) -> (Some title, Some (index_id :> Page.t))
27-
| None -> (None, (parent_id :> Page.t option))
30+
| None -> None
31+
| Some (index_id, title) ->
32+
let path =
33+
Url.from_identifier ~stop_before:false (index_id :> Id.t)
34+
|> Result.get_ok
35+
in
36+
let content = Comment.link_content title in
37+
Some (path, sidebar_toc_entry index_id content)
2838
in
29-
let entries =
30-
List.filter_map
31-
(fun id ->
32-
match id with
33-
| id, PageToc.Entry title ->
34-
(* TODO warn on non empty children order if not index page somewhere *)
35-
let payload =
36-
let path = Url.Path.from_identifier id in
37-
let content = Comment.link_content title in
38-
Some (path, sidebar_toc_entry id content)
39-
in
40-
Some (Item (payload, []))
41-
| id, PageToc.Dir dir -> Some (of_lang ~parent_id:(Some id) dir))
42-
content
39+
payload
40+
in
41+
Tree.map_t fun_ dir
42+
43+
let rec is_prefix (url1 : Url.Path.t) (url2 : Url.Path.t) =
44+
if url1 = url2 then true
45+
else
46+
match url2 with
47+
| { parent = Some parent; _ } -> is_prefix url1 parent
48+
| { parent = None; _ } -> false
49+
50+
let parent (url : Url.t) =
51+
match url with
52+
| { anchor = ""; page = { parent = Some parent; _ }; _ } -> parent
53+
| { page; _ } -> page
54+
55+
let to_block ~prune (current_url : Url.Path.t) tree =
56+
let block_tree_of_t (current_url : Url.Path.t) tree =
57+
(* When transforming the tree, we use a filter_map to remove the nodes that
58+
are irrelevant for the current url. However, we always want to keep the
59+
root. So we apply the filter_map starting from the first children. *)
60+
let convert ((url : Url.t), b) =
61+
let link =
62+
if url.page = current_url && String.equal url.anchor "" then
63+
{ b with Inline.attr = [ "current_unit" ] }
64+
else b
65+
in
66+
Types.block @@ Inline [ link ]
4367
in
44-
let payload =
45-
match (title, parent_id) with
46-
| None, _ | _, None -> None
47-
| Some title, Some parent_id ->
48-
let path = Url.Path.from_identifier parent_id in
49-
let content = Comment.link_content title in
50-
Some (path, sidebar_toc_entry parent_id content)
68+
let fun_ name =
69+
match name with
70+
| Some ((url, _) as v)
71+
when (not prune) || is_prefix (parent url) current_url ->
72+
Some (convert v)
73+
| _ -> None
74+
in
75+
let root_entry =
76+
match tree.Tree.node with
77+
| Some v -> convert v
78+
| None -> block (Block.Inline [ inline (Text "root") ])
5179
in
52-
Item (payload, entries)
80+
{
81+
Tree.node = root_entry;
82+
children = Tree.filter_map_f fun_ tree.children;
83+
}
5384
in
54-
of_lang ~parent_id:None dir
85+
let rec block_of_block_tree { Tree.node = name; children = content } =
86+
let content =
87+
match content with
88+
| [] -> []
89+
| _ :: _ ->
90+
let content = List.map block_of_block_tree content in
91+
[ block (Block.List (Block.Unordered, content)) ]
92+
in
93+
name :: content
94+
in
95+
let block_tree = block_tree_of_t current_url tree in
96+
block_of_block_tree block_tree
5597

56-
let rec to_sidebar ?(fallback = "root") convert (Item (name, content)) =
57-
let name =
58-
match name with
59-
| Some v -> convert v
60-
| None -> block (Block.Inline [ inline (Text fallback) ])
98+
let of_skeleton ({ node = entry; children } : Odoc_index.Entry.t Tree.t) =
99+
let map_entry entry =
100+
let stop_before =
101+
match entry.Odoc_index.Entry.kind with
102+
| ModuleType { has_expansion } | Module { has_expansion } ->
103+
not has_expansion
104+
| _ -> false
105+
in
106+
let path = Url.from_identifier ~stop_before entry.id in
107+
let name = Odoc_model.Paths.Identifier.name entry.id in
108+
match path with
109+
| Ok path ->
110+
let content =
111+
let target = Target.Internal (Resolved path) in
112+
inline
113+
(Link { target; content = [ inline (Text name) ]; tooltip = None })
114+
in
115+
Some (path, content)
116+
| Error _ -> None
61117
in
62-
let content =
63-
match content with
64-
| [] -> []
65-
| _ :: _ ->
66-
let content = List.map (to_sidebar convert) content in
67-
[ block (Block.List (Block.Unordered, content)) ]
118+
let fun_ entry =
119+
match entry.Odoc_index.Entry.kind with
120+
| Module _ | Class_type _ | Class _ | ModuleType _ ->
121+
Some (map_entry entry)
122+
| _ -> None
68123
in
69-
name :: content
124+
let entry = map_entry entry in
125+
let children = Tree.filter_map_f fun_ children in
126+
{ Tree.node = entry; children }
70127
end
128+
71129
type pages = { name : string; pages : Toc.t }
72-
type library = { name : string; units : (Url.Path.t * Inline.one) list }
130+
type library = { name : string; units : Toc.t list }
73131

74132
type t = { pages : pages list; libraries : library list }
75133

76-
let of_lang (v : Odoc_model.Sidebar.t) =
134+
let of_lang (v : Odoc_index.t) =
135+
let { Odoc_index.pages; libs; extra = _ } = v in
77136
let pages =
78-
let page_hierarchy { Odoc_model.Sidebar.hierarchy_name; pages } =
79-
let hierarchy = Toc.of_lang pages in
80-
Some { name = hierarchy_name; pages = hierarchy }
137+
let page_hierarchy { Odoc_index.p_name; p_hierarchy } =
138+
let hierarchy = Toc.of_page_hierarchy p_hierarchy in
139+
{ name = p_name; pages = hierarchy }
81140
in
82-
Odoc_utils.List.filter_map page_hierarchy v.pages
141+
Odoc_utils.List.map page_hierarchy pages
83142
in
84-
let units =
85-
let item id =
86-
let content = [ inline @@ Text (Odoc_model.Paths.Identifier.name id) ] in
87-
(Url.Path.from_identifier id, sidebar_toc_entry id content)
143+
let libraries =
144+
let lib_hierarchies { Odoc_index.l_name; l_hierarchies } =
145+
let hierarchies = List.map Toc.of_skeleton l_hierarchies in
146+
{ units = hierarchies; name = l_name }
88147
in
89-
let units =
90-
List.map
91-
(fun { Odoc_model.Sidebar.units; name } ->
92-
let units = List.map item units in
93-
{ name; units })
94-
v.libraries
95-
in
96-
units
148+
Odoc_utils.List.map lib_hierarchies libs
97149
in
98-
{ pages; libraries = units }
150+
{ pages; libraries }
99151

100-
let to_block (sidebar : t) url =
152+
let to_block (sidebar : t) path =
101153
let { pages; libraries } = sidebar in
102154
let title t =
103155
block
104156
(Inline [ inline (Inline.Styled (`Bold, [ inline (Inline.Text t) ])) ])
105157
in
106-
let render_entry (entry_path, b) =
107-
let link =
108-
if entry_path = url then { b with Inline.attr = [ "current_unit" ] }
109-
else b
110-
in
111-
Types.block @@ Inline [ link ]
112-
in
113158
let pages =
114159
Odoc_utils.List.concat_map
115160
~f:(fun (p : pages) ->
116-
let pages = Toc.to_sidebar render_entry p.pages in
161+
let pages = Toc.to_block ~prune:false path p.pages in
117162
let pages = [ block (Block.List (Block.Unordered, [ pages ])) ] in
118163
let pages = [ title @@ p.name ^ "'s Pages" ] @ pages in
119164
pages)
@@ -123,10 +168,12 @@ let to_block (sidebar : t) url =
123168
let units =
124169
List.map
125170
(fun { units; name } ->
126-
[
127-
title name;
128-
block (List (Block.Unordered, [ List.map render_entry units ]));
129-
])
171+
let units =
172+
List.concat_map ~f:(Toc.to_block ~prune:true path) units
173+
in
174+
let units = [ block (Block.List (Block.Unordered, [ units ])) ] in
175+
let units = [ title @@ name ^ "'s Units" ] @ units in
176+
units)
130177
libraries
131178
in
132179
let units = block (Block.List (Block.Unordered, units)) in

src/document/sidebar.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
type t
22

3-
val of_lang : Odoc_model.Sidebar.t -> t
3+
val of_lang : Odoc_index.t -> t
44

55
val to_block : t -> Url.Path.t -> Types.Block.t
66
(** Generates the sidebar document given a global sidebar and the path at which

0 commit comments

Comments
 (0)