Skip to content

Commit

Permalink
Allow to order modules
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Nov 21, 2024
1 parent be33724 commit 57854ca
Show file tree
Hide file tree
Showing 7 changed files with 38 additions and 13 deletions.
22 changes: 16 additions & 6 deletions src/index/skeleton_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ open Odoc_model
(* Selective opens *)
module Id = Odoc_model.Paths.Identifier
module PageName = Odoc_model.Names.PageName
module ModuleName = Odoc_model.Names.ModuleName

type t = Entry.t Tree.t

Expand Down Expand Up @@ -42,28 +43,36 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
match id.Id.iv with
| `LeafPage (_, name) -> Format.fprintf fmt "'%s'" (PageName.to_string name)
| `Page (_, name) -> Format.fprintf fmt "'%s/'" (PageName.to_string name)
| `Root (_, name) ->
Format.fprintf fmt "'module-%s'" (ModuleName.to_string name)
| _ -> Format.fprintf fmt "'unsupported'"
in
let pp_children fmt c =
match c.Location_.value with
| Frontmatter.Page s -> Format.fprintf fmt "'%s'" s
| Dir s -> Format.fprintf fmt "'%s/'" s
| Module s -> Format.fprintf fmt "'module-%s'" s
in
let ordered, unordered =
let contents =
let leafs =
In_progress.leafs dir
|> List.map (fun (_, page) ->
let id :> Id.Page.t = page.Lang.Page.name in
let id :> Id.t = page.Lang.Page.name in
let entry = entry_of_page page in
(id, Tree.leaf entry))
in
let dirs =
In_progress.dirs dir
|> List.map (fun (id, payload) ->
let id :> Id.Page.t = id in
let id :> Id.t = id in
(id, t_of_in_progress payload))
in
leafs @ dirs
let modules =
In_progress.modules dir
|> List.map (fun (id, payload) -> ((id :> Id.t), payload))
in
leafs @ dirs @ modules
in
match children_order with
| None -> ([], contents)
Expand All @@ -77,12 +86,14 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
String.equal (PageName.to_string name) c
| (_, { Location_.value = Page c; _ }), `LeafPage (_, name) ->
String.equal (PageName.to_string name) c
| (_, { Location_.value = Module c; _ }), `Root (_, name) ->
String.equal (ModuleName.to_string name) c
| _ -> false
in
let children_indexes, indexed_content, unindexed_content =
List.fold_left
(fun (children_indexes, indexed_content, unindexed_content)
(((id : Id.Page.t), _) as entry) ->
((id, _) as entry) ->
let indexes_for_entry, children_indexes =
List.partition (equal id) children_indexes
in
Expand Down Expand Up @@ -129,9 +140,8 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
String.compare (Paths.Identifier.name x) (Paths.Identifier.name y))
unordered
in
let modules = In_progress.modules dir |> List.map snd in
let contents = ordered @ unordered |> List.map snd in
{ Tree.node = index; children = contents @ modules }
{ Tree.node = index; children = contents }

let rec remove_common_root (v : t) =
match v with
Expand Down
7 changes: 6 additions & 1 deletion src/model/frontmatter.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
type child = Page of string | Dir of string
type child = Page of string | Dir of string | Module of string

type short_title = Comment.link_content

Expand Down Expand Up @@ -38,9 +38,14 @@ let apply fm line =
{ fm with children_order }

let parse_child c =
let mod_prefix = "module-" in
if Astring.String.is_suffix ~affix:"/" c then
let c = String.sub c 0 (String.length c - 1) in
Dir c
else if Astring.String.is_prefix ~affix:mod_prefix c then
let l = String.length mod_prefix in
let c = String.sub c l (String.length c - l) in
Module c
else Page c

let parse_children_order loc co =
Expand Down
2 changes: 1 addition & 1 deletion src/model/frontmatter.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
type child = Page of string | Dir of string
type child = Page of string | Dir of string | Module of string

type short_title = Comment.link_content

Expand Down
3 changes: 2 additions & 1 deletion src/model_desc/lang_desc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -725,7 +725,8 @@ and child =
Variant
(function
| { Location_.value = Page s; _ } -> C ("Page", s, string)
| { Location_.value = Dir s; _ } -> C ("Dir", s, string))
| { Location_.value = Dir s; _ } -> C ("Dir", s, string)
| { Location_.value = Module s; _ } -> C ("Module", s, string))

and implementation_t =
let open Lang.Implementation in
Expand Down
2 changes: 1 addition & 1 deletion test/frontmatter/toc_order.t/index.mld
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
@children_order content dir1/ dir1/ typo
@children_order content module-Unit dir1/ dir1/ typo

{0 This is the main index}

Expand Down
14 changes: 11 additions & 3 deletions test/frontmatter/toc_order.t/run.t
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
$ ocamlc -c -bin-annot unit.ml

$ odoc compile --parent-id pkg --output-dir _odoc unit.cmt
$ odoc compile --parent-id pkg --output-dir _odoc index.mld
$ odoc compile --parent-id pkg --output-dir _odoc content.mld
$ odoc compile --parent-id pkg --output-dir _odoc omitted.mld
Expand All @@ -6,18 +9,19 @@
$ odoc compile --parent-id pkg/dir1 --output-dir _odoc dir1/dontent.mld

$ odoc link _odoc/pkg/page-index.odoc
$ odoc link _odoc/pkg/unit.odoc
$ odoc link _odoc/pkg/page-content.odoc
$ odoc link _odoc/pkg/page-omitted.odoc
$ odoc link _odoc/pkg/dir1/page-index.odoc
$ odoc link _odoc/pkg/dir1/page-content_in_dir.odoc
$ odoc link _odoc/pkg/dir1/page-dontent.odoc

$ odoc compile-index --root _odoc/pkg
File "index.mld", line 1, characters 30-35:
File "index.mld", line 1, characters 42-47:
Warning: Duplicate 'dir1/' in (children).
File "index.mld", line 1, characters 36-40:
File "index.mld", line 1, characters 48-52:
Warning: 'typo' in (children) does not correspond to anything.
File "index.mld", line 1, characters 0-40:
File "index.mld", line 1, characters 0-52:
Warning: (children) doesn't include 'omitted'.

Turn the index into a sidebar (removes all unnecessary entries)
Expand All @@ -38,6 +42,9 @@ Turn the index into a sidebar (removes all unnecessary entries)
{
"Page": "content"
},
{
"Module": "Unit"
},
{
"Dir": "dir1"
},
Expand Down Expand Up @@ -65,6 +72,7 @@ but this should be a warning!
<nav class="odoc-toc odoc-global-toc">
<a href="#" class="current_unit">This is the main index</a>
<ul><li><a href="content.html">This is top level content</a></li>
<li><a href="Unit/index.html">Unit</a></li>
<li><a href="dir1/index.html">This is dir1's index</a></li>
<li><a href="omitted.html">This one is omitted</a></li>
</ul>
Expand Down
1 change: 1 addition & 0 deletions test/frontmatter/toc_order.t/unit.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let x = 1

0 comments on commit 57854ca

Please sign in to comment.