Skip to content

Commit

Permalink
Rename file
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Nov 21, 2024
1 parent 54b39aa commit 12a42d7
Show file tree
Hide file tree
Showing 7 changed files with 7 additions and 7 deletions.
2 changes: 1 addition & 1 deletion src/document/sidebar.ml
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ end

type t = Toc.t list

let of_lang (v : Odoc_index.t) = List.map Toc.of_page_hierarchy v
let of_index (v : Odoc_index.t) = List.map Toc.of_page_hierarchy v

let to_block (sidebar : t) path =
List.map (Toc.to_block ~prune:true path) sidebar
2 changes: 1 addition & 1 deletion src/document/sidebar.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ type entry = Url.t option * Inline.one

type t = entry Tree.t list

val of_lang : Odoc_index.t -> t
val of_index : Odoc_index.t -> t

val to_block : t -> Url.Path.t -> Types.Block.t list
(** Generates the sidebar document given a global sidebar and the path at which
Expand Down
2 changes: 1 addition & 1 deletion src/index/odoc_index.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
module Skeleton = Skeleton
module Entry = Entry
module Page_hierarchy = Page_hierarchy
module Skeleton_of = Skeleton_of

type t = Skeleton.t list
2 changes: 1 addition & 1 deletion src/index/page_hierarchy.ml → src/index/skeleton_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -224,7 +224,7 @@ let rec remove_common_root (v : t) =
| { Tree.children = [ v ]; node = { kind = Dir; _ } } -> remove_common_root v
| _ -> v

let of_list ~pages ~modules =
let lang ~pages ~modules =
let dir = empty_t None in
List.iter (add_page dir) pages;
List.iter (add_module dir) modules;
Expand Down
2 changes: 1 addition & 1 deletion src/index/page_hierarchy.mli → src/index/skeleton_of.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ open Odoc_model

(** Page hierarchies represent a hierarchy of pages. *)

val of_list :
val lang :
pages:Lang.Page.t list -> modules:Lang.Compilation_unit.t list -> Skeleton.t
(** Uses the convention that the [index] children passes its payload to the
container directory to output a payload *)
2 changes: 1 addition & 1 deletion src/odoc/indexing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ let compile out_format ~output ~warnings_options ~occurrences ~roots
in
List.fold_left read ([], []) files
in
let hierarchy = Odoc_index.Page_hierarchy.of_list ~pages ~modules in
let hierarchy = Odoc_index.Skeleton_of.lang ~pages ~modules in
match out_format with
| `JSON -> compile_to_json ~output ~occurrences files
| `Marshall -> compile_to_marshall ~output [ hierarchy ]
2 changes: 1 addition & 1 deletion src/odoc/sidebar.ml
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ let compile_to_json ~output sidebar =

let generate ~marshall ~output ~warnings_options:_ ~index =
Odoc_file.load_index index >>= fun index ->
let sidebar = Odoc_document.Sidebar.of_lang index in
let sidebar = Odoc_document.Sidebar.of_index index in
match marshall with
| `JSON -> Ok (compile_to_json ~output sidebar)
| `Marshall -> Ok (Odoc_file.save_sidebar output sidebar)

0 comments on commit 12a42d7

Please sign in to comment.