Skip to content

Commit

Permalink
Driver: add an index page if no-one is provided by the package
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd authored and jonludlam committed Nov 8, 2024
1 parent e626634 commit 3e137a1
Show file tree
Hide file tree
Showing 4 changed files with 29 additions and 10 deletions.
9 changes: 8 additions & 1 deletion src/driver/landing_pages.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,14 @@ let library ~dirs ~pkg ~index lib =
List.iter print_module lib.modules
in
let rel_dir = lib_dir pkg lib in
make_index ~dirs ~rel_dir ?index ~content ()
make_index ~dirs ~rel_dir ~index ~content ()

let package ~dirs ~pkg ~index =
let content ppf =
Format.fprintf ppf "{0 %s}@\nUse sidebar to navigate." pkg.Packages.name
in
let rel_dir = doc_dir pkg in
make_index ~dirs ~rel_dir ~index ~content ()

let package_list ~dirs all =
let content all ppf =
Expand Down
8 changes: 3 additions & 5 deletions src/driver/landing_pages.mli
Original file line number Diff line number Diff line change
@@ -1,10 +1,8 @@
open Odoc_unit

val library :
dirs:dirs ->
pkg:Packages.t ->
index:index option ->
Packages.libty ->
mld unit
dirs:dirs -> pkg:Packages.t -> index:index -> Packages.libty -> mld unit

val package : dirs:dirs -> pkg:Packages.t -> index:index -> mld unit

val package_list : dirs:dirs -> Packages.t list -> mld unit
21 changes: 17 additions & 4 deletions src/driver/odoc_units_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -187,9 +187,7 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
let of_lib pkg (lib : Packages.libty) =
let lib_deps = Util.StringSet.add lib.lib_name lib.lib_deps in
let index = index_of pkg in
let landing_page :> t =
Landing_pages.library ~dirs ~pkg ~index:(Some index) lib
in
let landing_page :> t = Landing_pages.library ~dirs ~pkg ~index lib in
landing_page :: List.concat_map (of_module pkg lib lib_deps) lib.modules
in
let of_mld pkg (mld : Packages.mld) : mld unit list =
Expand Down Expand Up @@ -235,7 +233,22 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
let lib_units :> t list list = List.map (of_lib pkg) pkg.libraries in
let mld_units :> t list list = List.map (of_mld pkg) pkg.mlds in
let asset_units :> t list list = List.map (of_asset pkg) pkg.assets in
List.concat (lib_units @ mld_units @ asset_units)
let pkg_index :> t list =
let has_index_page =
List.exists
(fun mld ->
Fpath.equal
(Fpath.normalize mld.Packages.mld_rel_path)
(Fpath.normalize (Fpath.v "./index.mld")))
pkg.mlds
in
if has_index_page then []
else
let index = index_of pkg in
[ Landing_pages.package ~dirs ~pkg ~index ]
in
List.concat ((pkg_index :: lib_units) @ mld_units @ asset_units)
in

let pkg_list :> t = Landing_pages.package_list ~dirs pkgs in
pkg_list :: List.concat_map of_package pkgs
1 change: 1 addition & 0 deletions src/driver/util.ml
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ let lines_of_process cmd =
if needed. *)
let with_out_to filename f =
let open ResultMonad in
let filename = Fpath.normalize filename in
OS.Dir.create (Fpath.parent filename) >>= fun _ ->
OS.File.with_oc filename
(fun oc () ->
Expand Down

0 comments on commit 3e137a1

Please sign in to comment.