Skip to content

Commit

Permalink
Driver: uniformize names for _odoc dir
Browse files Browse the repository at this point in the history
`odoc_dir` was sometimes used to refer to the root of the directory containing
.odoc files (`_odoc` by default), and sometimes used to refer to the direct
parent of a `.odoc` file.

The root of the directory containing `.odoc` files was referred as `odoc_dir`,
`output_dir`.

The root of the directory containing `.odocl` files was referred as `odocl_dir`,
`link_dir`, `linked_dir`.

This commit cleans that. The root of the directory for `.odoc` files is
consistently named `odoc_dir`, the root for `.odocl` files is
`odocl_dir`.
  • Loading branch information
panglesd authored and jonludlam committed Nov 5, 2024
1 parent 770c17d commit 3addbf9
Show file tree
Hide file tree
Showing 7 changed files with 65 additions and 109 deletions.
2 changes: 1 addition & 1 deletion src/driver/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -92,7 +92,7 @@ let find_partials odoc_dir :
| Ok h -> (h, tbl)
| Error _ -> (* odoc_dir doesn't exist...? *) (Util.StringMap.empty, tbl)

let compile ?partial ~partial_dir ?linked_dir:_ (all : Odoc_unit.t list) =
let compile ?partial ~partial_dir (all : Odoc_unit.t list) =
let hashes = mk_byhash all in
let compile_mod =
(* Modules have a more complicated compilation because:
Expand Down
6 changes: 1 addition & 5 deletions src/driver/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,7 @@ type compiled
val init_stats : Odoc_unit.t list -> unit

val compile :
?partial:Fpath.t ->
partial_dir:Fpath.t ->
?linked_dir:Fpath.t ->
Odoc_unit.t list ->
compiled list
?partial:Fpath.t -> partial_dir:Fpath.t -> Odoc_unit.t list -> compiled list
(** Use [partial] to reuse the output of a previous call to [compile]. Useful in
the voodoo context.
Expand Down
71 changes: 25 additions & 46 deletions src/driver/landing_pages.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ open Odoc_unit

let fpf = Format.fprintf

let make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
let make_unit ~odoc_dir ~odocl_dir ~mld_dir rel_path ~content
?(include_dirs = Fpath.Set.empty) ~pkgname ~pkg_args () =
let input_file = Fpath.(mld_dir // rel_path / "index.mld") in
let odoc_file = Fpath.(odoc_dir // rel_path / "page-index.odoc") in
Expand All @@ -14,9 +14,8 @@ let make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
let parent_id = rel_path |> Odoc.Id.of_fpath in
{
parent_id;
odoc_dir;
input_file;
output_dir;
output_dir = odoc_dir;
odoc_file;
odocl_file;
pkg_args;
Expand All @@ -37,20 +36,15 @@ module PackageLanding = struct
fpf ppf "{1 Libraries}@\n@\n{{!/%s/lib/index}Libraries for %s}@\n"
pkg.name pkg.name

let page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg =
let page ~odoc_dir ~odocl_dir ~mld_dir ~pkg =
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 = [];
compile_dir = output_dir;
link_dir = odocl_dir;
}
{ Pkg_args.pages = pages_rel; libs = []; odoc_dir; odocl_dir }
in
make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
~pkgname:pkg.name ~pkg_args ()
make_unit ~odoc_dir ~odocl_dir ~mld_dir rel_path ~content ~pkgname:pkg.name
~pkg_args ()
end

module PackageList = struct
Expand All @@ -64,21 +58,16 @@ module PackageList = struct
in
List.iter print_pkg sorted_packages

let page ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all =
let page ~mld_dir ~odoc_dir ~odocl_dir all =
let content = content all in
let rel_path = Fpath.v "./" in
let pkgname = "__driver" in
let pages_rel = [ (pkgname, rel_path) ] in
let pkg_args =
{
Pkg_args.pages = pages_rel;
libs = [];
compile_dir = output_dir;
link_dir = odocl_dir;
}
{ Pkg_args.pages = pages_rel; libs = []; odoc_dir; odocl_dir }
in
make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~content ~pkgname
~pkg_args rel_path ()
make_unit ~odoc_dir ~odocl_dir ~mld_dir ~content ~pkgname ~pkg_args rel_path
()
end

module LibraryLanding = struct
Expand All @@ -89,21 +78,16 @@ module LibraryLanding = struct
in
List.iter print_module lib.modules

let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg_dir lib =
let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~pkg_dir lib =
let content = content lib in
let rel_path = Fpath.(pkg_dir / "lib" / lib.lib_name) in
let pages_rel = [ (pkg.name, rel_path) ] in
let pkg_args =
{
Pkg_args.pages = pages_rel;
libs = [];
link_dir = odocl_dir;
compile_dir = output_dir;
}
{ Pkg_args.pages = pages_rel; libs = []; odocl_dir; odoc_dir }
in
let include_dirs = Fpath.Set.singleton Fpath.(odoc_dir // rel_path) in
make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
~pkgname:pkg.name ~include_dirs ~pkg_args ()
make_unit ~odoc_dir ~odocl_dir ~mld_dir rel_path ~content ~pkgname:pkg.name
~include_dirs ~pkg_args ()
end

module PackageLibLanding = struct
Expand All @@ -114,37 +98,32 @@ module PackageLibLanding = struct
in
List.iter print_lib pkg.libraries

let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir =
let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir =
let content = content pkg in
let rel_path = Fpath.(pkg.pkg_dir / "lib") in
let pages_rel = [ (pkg.name, rel_path) ] in
let pkg_args =
{
Pkg_args.pages = pages_rel;
libs = [];
compile_dir = output_dir;
link_dir = odocl_dir;
}
{ Pkg_args.pages = pages_rel; libs = []; odoc_dir; odocl_dir }
in
make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
~pkgname:pkg.name ~pkg_args ()
make_unit ~odoc_dir ~odocl_dir ~mld_dir rel_path ~content ~pkgname:pkg.name
~pkg_args ()
end

let of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir pkg =
let of_package ~mld_dir ~odoc_dir ~odocl_dir pkg =
let library_pages =
List.map
(LibraryLanding.page ~pkg ~odoc_dir ~odocl_dir ~mld_dir
~pkg_dir:pkg.pkg_dir ~output_dir)
~pkg_dir:pkg.pkg_dir)
pkg.libraries
in
let package_landing_page =
PackageLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg
PackageLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~pkg
in
let library_list_page =
PackageLibLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg
PackageLibLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~pkg
in
package_landing_page :: library_list_page :: library_pages

let of_packages ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all =
PackageList.page ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all
:: List.concat_map (of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir) all
let of_packages ~mld_dir ~odoc_dir ~odocl_dir all =
PackageList.page ~mld_dir ~odoc_dir ~odocl_dir all
:: List.concat_map (of_package ~mld_dir ~odoc_dir ~odocl_dir) all
1 change: 0 additions & 1 deletion src/driver/landing_pages.mli
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,5 @@ val of_packages :
mld_dir:Fpath.t ->
odoc_dir:Fpath.t ->
odocl_dir:Fpath.t ->
output_dir:Fpath.t ->
Packages.t list ->
[> `Mld ] Odoc_unit.unit list
12 changes: 4 additions & 8 deletions src/driver/odoc_driver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -625,22 +625,18 @@ let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
let all =
let all = Util.StringMap.bindings all |> List.map snd in
let internal =
Odoc_unit.of_packages ~output_dir:odoc_dir ~linked_dir:odocl_dir
~index_dir:None ~extra_libs_paths all
Odoc_unit.of_packages ~odoc_dir ~odocl_dir ~index_dir:None
~extra_libs_paths all
in
let external_ =
let mld_dir = odoc_dir in
let odocl_dir = Option.value odocl_dir ~default:odoc_dir in
Landing_pages.of_packages ~mld_dir ~odoc_dir ~odocl_dir
~output_dir:odoc_dir all
Landing_pages.of_packages ~mld_dir ~odoc_dir ~odocl_dir all
in
internal @ external_
in
Compile.init_stats all;
let compiled =
Compile.compile ?partial ~partial_dir:odoc_dir ?linked_dir:odocl_dir
all
in
let compiled = Compile.compile ?partial ~partial_dir:odoc_dir all in
let linked = Compile.link compiled in
let occurrence_file =
let output =
Expand Down
73 changes: 30 additions & 43 deletions src/driver/odoc_unit.ml
Original file line number Diff line number Diff line change
@@ -1,26 +1,26 @@
module Pkg_args = struct
type t = {
compile_dir : Fpath.t;
link_dir : Fpath.t;
odoc_dir : Fpath.t;
odocl_dir : Fpath.t;
pages : (string * Fpath.t) list;
libs : (string * Fpath.t) list;
}

let map_rel dir = List.map (fun (a, b) -> (a, Fpath.(dir // b)))

let compiled_pages v = map_rel v.compile_dir v.pages
let compiled_libs v = map_rel v.compile_dir v.libs
let linked_pages v = map_rel v.link_dir v.pages
let linked_libs v = map_rel v.link_dir v.libs
let compiled_pages v = map_rel v.odoc_dir v.pages
let compiled_libs v = map_rel v.odoc_dir v.libs
let linked_pages v = map_rel v.odocl_dir v.pages
let linked_libs v = map_rel v.odocl_dir v.libs

let combine v1 v2 =
if v1.compile_dir <> v2.compile_dir then
Fmt.invalid_arg "combine: compile_dir differs";
if v1.link_dir <> v2.link_dir then
Fmt.invalid_arg "combine: link_dir differs";
if v1.odoc_dir <> v2.odoc_dir then
Fmt.invalid_arg "combine: odoc_dir differs";
if v1.odocl_dir <> v2.odocl_dir then
Fmt.invalid_arg "combine: odocl_dir differs";
{
compile_dir = v1.compile_dir;
link_dir = v1.link_dir;
odoc_dir = v1.odoc_dir;
odocl_dir = v1.odocl_dir;
pages = v1.pages @ v2.pages;
libs = v1.libs @ v2.libs;
}
Expand All @@ -32,8 +32,8 @@ module Pkg_args = struct
Format.fprintf fmt "(%s, %a)" a Fpath.pp b))
in
Format.fprintf fmt
"@[<hov>compile_dir: %a@;link_dir: %a@;pages: [%a]@;libs: [%a]@]" Fpath.pp
x.compile_dir Fpath.pp x.link_dir sfp_pp x.pages sfp_pp x.libs
"@[<hov>odoc_dir: %a@;odocl_dir: %a@;pages: [%a]@;libs: [%a]@]" Fpath.pp
x.odoc_dir Fpath.pp x.odocl_dir sfp_pp x.pages sfp_pp x.libs
end

type index = {
Expand All @@ -50,7 +50,6 @@ let pp_index fmt x =

type 'a unit = {
parent_id : Odoc.Id.t;
odoc_dir : Fpath.t;
input_file : Fpath.t;
output_dir : Fpath.t;
odoc_file : Fpath.t;
Expand Down Expand Up @@ -98,7 +97,6 @@ and pp : all_kinds unit Fmt.t =
fun fmt x ->
Format.fprintf fmt
"@[<hov>parent_id: %s@;\
odoc_dir: %a@;\
input_file: %a@;\
output_dir: %a@;\
odoc_file: %a@;\
Expand All @@ -110,8 +108,8 @@ and pp : all_kinds unit Fmt.t =
kind:%a@;\
@]"
(Odoc.Id.to_string x.parent_id)
Fpath.pp x.odoc_dir Fpath.pp x.input_file Fpath.pp x.output_dir Fpath.pp
x.odoc_file Fpath.pp x.odocl_file Pkg_args.pp x.pkg_args x.pkgname
Fpath.pp x.input_file Fpath.pp x.output_dir Fpath.pp x.odoc_file Fpath.pp
x.odocl_file Pkg_args.pp x.pkg_args x.pkgname
Fmt.(list ~sep:comma Fpath.pp)
(Fpath.Set.to_list x.include_dirs)
(Fmt.option pp_index) x.index pp_kind
Expand All @@ -121,12 +119,10 @@ let doc_dir pkg = Fpath.(pkg.Packages.pkg_dir / "doc")
let lib_dir pkg lib =
Fpath.(pkg.Packages.pkg_dir / "lib" / lib.Packages.lib_name)

let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
let of_packages ~odoc_dir ~odocl_dir ~index_dir ~extra_libs_paths
(pkgs : Packages.t list) : t list =
let linked_dir =
match linked_dir with None -> output_dir | Some dir -> dir
in
let index_dir = match index_dir with None -> output_dir | Some dir -> dir in
let odocl_dir = match odocl_dir with None -> odoc_dir | Some dir -> dir in
let index_dir = match index_dir with None -> odoc_dir | Some dir -> dir in

(* [module_of_hash] Maps a hash to the corresponding [Package.t], library name and
[Packages.modulety]. [lib_dirs] maps a library name to the odoc dir containing its
Expand Down Expand Up @@ -168,12 +164,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
let base_args pkg lib_deps : Pkg_args.t =
let own_page = dash_p pkg in
let own_libs = List.concat_map dash_l (Util.StringSet.to_list lib_deps) in
{
pages = [ own_page ];
libs = own_libs;
compile_dir = output_dir;
link_dir = linked_dir;
}
{ pages = [ own_page ]; libs = own_libs; odoc_dir; odocl_dir }
in
let args_of_config config : Pkg_args.t =
let { Global_config.deps = { packages; libraries } } = config in
Expand All @@ -186,12 +177,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
packages
in
let libs_rel = List.concat_map dash_l libraries in
{
pages = pages_rel;
libs = libs_rel;
compile_dir = output_dir;
link_dir = linked_dir;
}
{ pages = pages_rel; libs = libs_rel; odoc_dir; odocl_dir }
in
let args_of =
let cache = Hashtbl.create 10 in
Expand Down Expand Up @@ -222,19 +208,19 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
let ( // ) = Fpath.( // ) in
let ( / ) = Fpath.( / ) in
let pkg_args = args_of pkg lib_deps in
let odoc_dir = output_dir // rel_dir in
let parent_id = rel_dir |> Odoc.Id.of_fpath in
let odoc_file = odoc_dir / (String.uncapitalize_ascii name ^ ".odoc") in
let odoc_file =
odoc_dir // rel_dir / (String.uncapitalize_ascii name ^ ".odoc")
in
(* odoc will uncapitalise the output filename *)
let odocl_file =
linked_dir // rel_dir / (String.uncapitalize_ascii name ^ ".odocl")
odocl_dir // rel_dir / (String.uncapitalize_ascii name ^ ".odocl")
in
{
output_dir;
output_dir = odoc_dir;
pkgname = pkg.Packages.name;
pkg_args;
parent_id;
odoc_dir;
input_file;
odoc_file;
odocl_file;
Expand Down Expand Up @@ -268,7 +254,8 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
let include_dirs, kind =
let deps = build_deps intf.mif_deps in
let include_dirs =
List.map (fun u -> u.odoc_dir) deps |> Fpath.Set.of_list
List.map (fun u -> Fpath.parent u.odoc_file) deps
|> Fpath.Set.of_list
in
let kind = `Intf { hidden; hash = intf.mif_hash; deps } in
(include_dirs, kind)
Expand All @@ -291,7 +278,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
let rel_dir = lib_dir pkg lib in
let include_dirs =
let deps = build_deps impl.mip_deps in
List.map (fun u -> u.odoc_dir) deps |> Fpath.Set.of_list
List.map (fun u -> Fpath.parent u.odoc_file) deps |> Fpath.Set.of_list
in
let kind =
let src_name = Fpath.filename src_path in
Expand Down Expand Up @@ -334,7 +321,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
List.map (fun (lib : Packages.libty) -> lib_dir pkg lib) pkg.libraries
in
let include_dirs =
(output_dir // rel_dir) :: include_dirs |> Fpath.Set.of_list
(odoc_dir // rel_dir) :: include_dirs |> Fpath.Set.of_list
in
let kind = `Mld in
let name = mld_path |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
Expand Down
Loading

0 comments on commit 3addbf9

Please sign in to comment.