-
Notifications
You must be signed in to change notification settings - Fork 96
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Showing
4 changed files
with
55 additions
and
91 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,96 +1,52 @@ | ||
open Packages | ||
open Odoc_unit | ||
|
||
let fpf = Format.fprintf | ||
|
||
let make_unit ~dirs rel_path ~content ?(include_dirs = Fpath.Set.empty) ~pkgname | ||
~pkg_args () = | ||
let input_file = Fpath.(dirs.mld_dir // rel_path / "index.mld") in | ||
let odoc_file = Fpath.(dirs.odoc_dir // rel_path / "page-index.odoc") in | ||
let odocl_file = Fpath.(dirs.odocl_dir // rel_path / "page-index.odocl") in | ||
let make_index ~dirs ~rel_dir ?index ~content () = | ||
let { odoc_dir; odocl_dir; mld_dir; _ } = dirs in | ||
let input_file = Fpath.(mld_dir // rel_dir / "index.mld") in | ||
let odoc_file = Fpath.(odoc_dir // rel_dir / "page-index.odoc") in | ||
let odocl_file = Fpath.(odocl_dir // rel_dir / "page-index.odocl") in | ||
let parent_id = rel_dir |> Odoc.Id.of_fpath in | ||
Util.with_out_to input_file (fun oc -> | ||
fpf (Format.formatter_of_out_channel oc) "%t@?" content) | ||
Format.fprintf (Format.formatter_of_out_channel oc) "%t@?" content) | ||
|> Result.get_ok; | ||
let parent_id = rel_path |> Odoc.Id.of_fpath in | ||
{ | ||
output_dir = dirs.odoc_dir; | ||
pkgname = None; | ||
pkg_args = { Pkg_args.pages = []; libs = []; odoc_dir; odocl_dir }; | ||
parent_id; | ||
input_file; | ||
output_dir = dirs.odoc_dir; | ||
odoc_file; | ||
odocl_file; | ||
pkg_args; | ||
pkgname; | ||
include_dirs; | ||
index = None; | ||
include_dirs = Fpath.Set.empty; | ||
kind = `Mld; | ||
index; | ||
} | ||
|
||
module PackageLanding = struct | ||
let content pkg ppf = | ||
fpf ppf "{0 %s}\n" pkg.name; | ||
if not (List.is_empty pkg.mlds) then | ||
fpf ppf | ||
"{1 Documentation pages}@\n@\n{{!/%s/doc/index}Documentation for %s}@\n" | ||
pkg.name pkg.name; | ||
if not (List.is_empty pkg.libraries) then | ||
fpf ppf "{1 Libraries}@\n@\n{{!/%s/lib/index}Libraries for %s}@\n" | ||
pkg.name pkg.name | ||
|
||
let page ~dirs ~pkg = | ||
let { Odoc_unit.odoc_dir; odocl_dir; _ } = dirs in | ||
let content = content pkg in | ||
let rel_path = pkg.pkg_dir in | ||
let pages_rel = [ (pkg.name, rel_path) ] in | ||
let pkg_args = | ||
{ Pkg_args.pages = pages_rel; libs = []; odoc_dir; odocl_dir } | ||
let library ~dirs ~pkg ~index lib = | ||
let content ppf = | ||
Format.fprintf ppf "{0 Library %s}@\n" lib.Packages.lib_name; | ||
let print_module m = | ||
if not m.Packages.m_hidden then | ||
Format.fprintf ppf "- {!%s}@\n" m.Packages.m_name | ||
in | ||
make_unit ~dirs rel_path ~content ~pkgname:(Some pkg.name) ~pkg_args () | ||
end | ||
List.iter print_module lib.modules | ||
in | ||
let rel_dir = lib_dir pkg lib in | ||
make_index ~dirs ~rel_dir ?index ~content () | ||
|
||
module PackageList = struct | ||
let package_list ~dirs all = | ||
let content all ppf = | ||
let sorted_packages = | ||
all |> List.sort (fun n1 n2 -> String.compare n1.name n2.name) | ||
all | ||
|> List.sort (fun n1 n2 -> | ||
String.compare n1.Packages.name n2.Packages.name) | ||
in | ||
fpf ppf "{0 List of all packages}@\n"; | ||
let print_pkg pkg = fpf ppf "- {{:%s/index.html}%s}@\n" pkg.name pkg.name in | ||
List.iter print_pkg sorted_packages | ||
|
||
let page ~dirs all = | ||
let { Odoc_unit.odoc_dir; odocl_dir; _ } = dirs in | ||
let content = content all in | ||
let rel_path = Fpath.v "./" in | ||
let pkg_args = { Pkg_args.pages = []; libs = []; odoc_dir; odocl_dir } in | ||
make_unit ~dirs ~content ~pkgname:None ~pkg_args rel_path () | ||
end | ||
|
||
module LibraryLanding = struct | ||
let content lib ppf = | ||
fpf ppf "{0 %s}@\n" lib.lib_name; | ||
let print_module m = | ||
if not m.m_hidden then fpf ppf "- {!%s}@\n" m.Packages.m_name | ||
in | ||
List.iter print_module lib.modules | ||
|
||
let page ~pkg ~dirs ~pkg_dir lib = | ||
let { Odoc_unit.odoc_dir; odocl_dir; _ } = dirs in | ||
let content = content lib in | ||
let rel_path = Fpath.(pkg_dir / lib.lib_name) in | ||
let pages_rel = [ (pkg.name, rel_path) ] in | ||
let pkg_args = | ||
{ Pkg_args.pages = pages_rel; libs = []; odocl_dir; odoc_dir } | ||
Format.fprintf ppf "{0 List of all packages}@\n"; | ||
let print_pkg pkg = | ||
Format.fprintf ppf "- {{:%s/index.html}%s}@\n" pkg.Packages.name pkg.name | ||
in | ||
let include_dirs = Fpath.Set.singleton Fpath.(odoc_dir // rel_path) in | ||
make_unit ~dirs rel_path ~content ~pkgname:(Some pkg.name) ~include_dirs | ||
~pkg_args () | ||
end | ||
|
||
let of_package ~dirs pkg = | ||
let library_pages = | ||
List.map (LibraryLanding.page ~pkg ~dirs ~pkg_dir:pkg.pkg_dir) pkg.libraries | ||
List.iter print_pkg sorted_packages | ||
in | ||
let package_landing_page = PackageLanding.page ~dirs ~pkg in | ||
package_landing_page :: library_pages | ||
|
||
let of_packages ~dirs all = | ||
PackageList.page ~dirs all :: List.concat_map (of_package ~dirs) all | ||
let content = content all in | ||
let rel_dir = Fpath.v "./" in | ||
make_index ~dirs ~rel_dir ~content () |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,2 +1,10 @@ | ||
val of_packages : | ||
dirs:Odoc_unit.dirs -> Packages.t list -> [> `Mld ] Odoc_unit.unit list | ||
open Odoc_unit | ||
|
||
val library : | ||
dirs:dirs -> | ||
pkg:Packages.t -> | ||
index:index option -> | ||
Packages.libty -> | ||
mld unit | ||
|
||
val package_list : dirs:dirs -> Packages.t list -> mld unit |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters