Skip to content

Commit 03389b1

Browse files
committed
Children order: Remove common root using ID not URL segments
1 parent 6c09910 commit 03389b1

File tree

2 files changed

+5
-9
lines changed

2 files changed

+5
-9
lines changed

src/document/sidebar.ml

Lines changed: 1 addition & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,6 @@ module Toc : sig
1111

1212
val of_lang : Odoc_model.Sidebar.PageToc.t -> t
1313

14-
val remove_common_root : t -> t
15-
(** Returns the deepest subdir containing all files. *)
16-
1714
val to_sidebar :
1815
?fallback:string -> (Url.Path.t * Inline.one -> Block.one) -> t -> Block.t
1916
end = struct
@@ -56,10 +53,6 @@ end = struct
5653
in
5754
of_lang ~parent_id:None dir
5855

59-
let rec remove_common_root = function
60-
| Item (_, [ d ]) -> remove_common_root d
61-
| x -> x
62-
6356
let rec to_sidebar ?(fallback = "root") convert (Item (name, content)) =
6457
let name =
6558
match name with
@@ -83,7 +76,7 @@ type t = { pages : pages list; libraries : library list }
8376
let of_lang (v : Odoc_model.Sidebar.t) =
8477
let pages =
8578
let page_hierarchy { Odoc_model.Sidebar.hierarchy_name; pages } =
86-
let hierarchy = Toc.of_lang pages |> Toc.remove_common_root in
79+
let hierarchy = Toc.of_lang pages in
8780
Some { name = hierarchy_name; pages = hierarchy }
8881
in
8982
Odoc_utils.List.filter_map page_hierarchy v.pages

src/model/sidebar.ml

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -182,10 +182,13 @@ module PageToc = struct
182182
let contents = ordered @ unordered in
183183
(contents, index)
184184

185+
let rec remove_common_root (v : t) =
186+
match v with [ (_, Dir v) ], None -> remove_common_root v | _ -> v
187+
185188
let of_list l =
186189
let dir = empty_t None in
187190
List.iter (add dir) l;
188-
t_of_in_progress dir
191+
t_of_in_progress dir |> remove_common_root
189192
end
190193

191194
type toc = PageToc.t

0 commit comments

Comments
 (0)