Skip to content

Commit

Permalink
Sidebar: better default order
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Dec 5, 2024
1 parent d9d70b7 commit 4d5d7c4
Show file tree
Hide file tree
Showing 2 changed files with 49 additions and 9 deletions.
41 changes: 32 additions & 9 deletions src/index/skeleton_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,41 @@ module ModuleName = Odoc_model.Names.ModuleName

type t = Entry.t Tree.t

let compare_entry (e1 : Entry.t) (e2 : Entry.t) =
let int_of_kind (kind : Entry.kind) =
match kind with
| Page _ -> -10
| Dir -> 0
let compare_entry (t1 : t) (t2 : t) =
let by_kind (t : t) =
match t.node.kind with
| Page _ when List.is_empty t.children -> -10
| Page _ | Dir -> 0
| Module _ -> 10
| Impl -> 20
| _ -> 30
in
match Int.compare (int_of_kind e1.kind) (int_of_kind e2.kind) with
| 0 -> Astring.String.compare (Id.name e1.id) (Id.name e2.id)
| i -> i
(* Heuristic: If a dir contains only pages, place it before. *)
let by_content (t : t) =
if
List.for_all
(fun x ->
match x.Tree.node.Entry.kind with Page _ -> true | _ -> false)
t.children
then -10
else 10
in
let by_name (t : t) =
match t.node.kind with
| Page { short_title = Some title; _ } -> Comment.to_string title
| _ -> (
match t.node.id.iv with
| `LeafPage (Some parent, name)
when Names.PageName.to_string name = "index" ->
Id.name parent
| _ -> Id.name t.node.id)
in
let try_ comp f fallback =
match comp (f t1) (f t2) with 0 -> fallback () | i -> i
in
try_ (compare : int -> int -> int) by_kind @@ fun () ->
try_ (compare : int -> int -> int) by_content @@ fun () ->
try_ Astring.String.compare by_name @@ fun () -> 0

let rec t_of_in_progress (dir : In_progress.in_progress) : t =
let entry_of_page page =
Expand Down Expand Up @@ -158,7 +181,7 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
|> List.map snd
in
let unordered =
List.sort (fun (_, x) (_, y) -> compare_entry x.Tree.node y.node) unordered
List.sort (fun (_, x) (_, y) -> compare_entry x y) unordered
in
let contents = ordered @ unordered |> List.map snd in
{ Tree.node = index; children = contents }
Expand Down
17 changes: 17 additions & 0 deletions src/model/comment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -145,3 +145,20 @@ let find_zero_heading docs : link_content option =
Some (link_content_of_inline_elements h_content)
| _ -> None)
docs

(* Used in particular to sort the title names *)
let to_string (l : link_content) =
let rec s_of_i (i : non_link_inline_element) =
match i with
| `Code_span s -> s
| `Word w -> w
| `Math_span m -> m
| `Space -> " "
| `Styled (_, is) -> s_of_is is
| `Raw_markup (_, r) -> r
and s_of_is is =
is
|> List.map (fun { Location_.value; _ } -> s_of_i value)
|> String.concat ""
in
s_of_is l

0 comments on commit 4d5d7c4

Please sign in to comment.