diff --git a/src/dune_rules/odoc.ml b/src/dune_rules/odoc.ml index b8311a5984c..f032020083e 100644 --- a/src/dune_rules/odoc.ml +++ b/src/dune_rules/odoc.ml @@ -54,11 +54,12 @@ type source = | Module | Mld -type odoc = - { odoc_input : Path.Build.t +type odoc_artefact = + { odoc_file : Path.Build.t + ; odocl_file : Path.Build.t ; html_dir : Path.Build.t ; html_file : Path.Build.t - ; source : source + ; source : source (** source of the [odoc_file], either module or mld *) } let add_rule sctx = @@ -77,13 +78,19 @@ module Paths = struct let html_root ctx = root ctx ++ "_html" - let html ctx m = - html_root ctx + let odocl_root ctx = root ctx ++ "_odocls" + + let add_pkg_lnu base m = + base ++ match m with | Pkg pkg -> Package.Name.to_string pkg | Lib lib -> pkg_or_lnu (Lib.Local.to_lib lib) + let html ctx m = add_pkg_lnu (html_root ctx) m + + let odocl ctx m = add_pkg_lnu (odocl_root ctx) m + let gen_mld_dir ctx pkg = root ctx ++ "_mlds" ++ Package.Name.to_string pkg let css_file ctx = html_root ctx ++ "odoc.css" @@ -252,45 +259,25 @@ let odoc_include_flags ctx pkg requires = (List.concat_map (Path.Set.to_list paths) ~f:(fun dir -> [ Command.Args.A "-I"; Path dir ]))) -let setup_html sctx (odoc_file : odoc) ~pkg ~requires = +let link_odoc_rules sctx (odoc_file : odoc_artefact) ~pkg ~requires = let ctx = Super_context.context sctx in let deps = Dep.deps ctx pkg requires in - let to_remove, dummy = - match odoc_file.source with - | Mld -> (odoc_file.html_file, []) - | Module -> - (* Dummy target so that the below rule as at least one target. We do this - because we don't know the targets of odoc in this case. The proper way - to support this would be to have directory targets. *) - let dummy = Action_builder.create_file (odoc_file.html_dir ++ ".dummy") in - (odoc_file.html_dir, [ dummy ]) - in let open Memo.Build.O in let* odoc = odoc sctx - and* odoc_base_flags = odoc_base_flags sctx odoc_file.odoc_input in + and* odoc_base_flags = odoc_base_flags sctx odoc_file.odoc_file in add_rule sctx (let open Action_builder.With_targets.O in Action_builder.with_no_targets deps - >>> Action_builder.progn - (Action_builder.with_no_targets - (Action_builder.return - (Action.Full.make - (Action.Progn - [ Action.Remove_tree to_remove - ; Action.Mkdir (Path.build odoc_file.html_dir) - ]))) - :: Command.run - ~dir:(Path.build (Paths.html_root ctx)) - odoc - [ A "html" - ; odoc_base_flags - ; odoc_include_flags ctx pkg requires - ; A "-o" - ; Path (Path.build (Paths.html_root ctx)) - ; Dep (Path.build odoc_file.odoc_input) - ; Hidden_targets [ odoc_file.html_file ] - ] - :: dummy)) + >>> Command.run + ~dir:(Path.build (Paths.html_root ctx)) + odoc + [ A "link" + ; odoc_base_flags + ; odoc_include_flags ctx pkg requires + ; A "-o" + ; Target odoc_file.odocl_file + ; Dep (Path.build odoc_file.odoc_file) + ]) let setup_library_odoc_rules cctx (library : Library.t) = let open Memo.Build.O in @@ -330,6 +317,40 @@ let setup_library_odoc_rules cctx (library : Library.t) = Dep.setup_deps ctx (Lib local_lib) (Path.Set.of_list_map modules_and_odoc_files ~f:(fun (_, p) -> Path.build p)) +let setup_html sctx (odoc_file : odoc_artefact) = + let ctx = Super_context.context sctx in + let to_remove, dummy = + match odoc_file.source with + | Mld -> (odoc_file.html_file, []) + | Module -> + (* Dummy target so that the bellow rule as at least one target. We do this + because we don't know the targets of odoc in this case. The proper way + to support this would be to have directory targets. *) + let dummy = Action_builder.create_file (odoc_file.html_dir ++ ".dummy") in + (odoc_file.html_dir, [ dummy ]) + in + let open Memo.Build.O in + let* odoc = odoc sctx in + add_rule sctx + (Action_builder.progn + (Action_builder.with_no_targets + (Action_builder.return + (Action.Full.make + (Action.Progn + [ Action.Remove_tree to_remove + ; Action.Mkdir (Path.build odoc_file.html_dir) + ]))) + :: Command.run + ~dir:(Path.build (Paths.html_root ctx)) + odoc + [ A "html-generate" + ; A "-o" + ; Path (Path.build (Paths.html_root ctx)) + ; Dep (Path.build odoc_file.odocl_file) + ; Hidden_targets [ odoc_file.html_file ] + ] + :: dummy)) + let setup_css_rule sctx = let open Memo.Build.O in let ctx = Super_context.context sctx in @@ -394,30 +415,59 @@ let libs_of_pkg sctx ~pkg = Option.some_if (not is_impl) lib | Deprecated_library_name _ -> None) -let create_odoc ctx ~target odoc_input = +let load_all_odoc_rules_pkg sctx ~pkg = + let pkg_libs = libs_of_pkg sctx ~pkg in + let+ () = + Memo.Build.parallel_iter + (Pkg pkg :: List.map pkg_libs ~f:(fun lib -> Lib lib)) + ~f:(fun _ -> Memo.Build.return ()) + in + pkg_libs + +let entry_modules_by_lib sctx lib = + let info = Lib.Local.info lib in + let dir = Lib_info.src_dir info in + let name = Lib.name (Lib.Local.to_lib lib) in + Dir_contents.get sctx ~dir >>= Dir_contents.ocaml + >>| Ml_sources.modules ~for_:(Library name) + >>| Modules.entry_modules + +let entry_modules sctx ~pkg = + let l = + libs_of_pkg sctx ~pkg + |> List.filter ~f:(fun lib -> + Lib.Local.info lib |> Lib_info.status |> Lib_info.Status.is_private + |> not) + in + let+ l = + Memo.Build.parallel_map l ~f:(fun l -> + let+ m = entry_modules_by_lib sctx l in + (l, m)) + in + Lib.Local.Map.of_list_exn l + +let create_odoc ctx ~target odoc_file = let html_base = Paths.html ctx target in + let odocl_base = Paths.odocl ctx target in + let basename = Path.Build.basename odoc_file |> Filename.chop_extension in + let odocl_file = odocl_base ++ (basename ^ ".odocl") in match target with | Lib _ -> - let html_dir = - html_base - ++ (Path.Build.basename odoc_input - |> Filename.chop_extension |> Stdune.String.capitalize) - in - { odoc_input + let html_dir = html_base ++ Stdune.String.capitalize basename in + { odoc_file + ; odocl_file ; html_dir ; html_file = html_dir ++ "index.html" ; source = Module } | Pkg _ -> - { odoc_input + { odoc_file + ; odocl_file ; html_dir = html_base ; html_file = html_base ++ sprintf "%s.html" - (Path.Build.basename odoc_input - |> Filename.chop_extension - |> String.drop_prefix ~prefix:"page-" - |> Option.value_exn) + (basename |> String.drop_prefix ~prefix:"page-" |> Option.value_exn) ; source = Mld } @@ -440,7 +490,7 @@ let check_mlds_no_dupes ~pkg ~mlds = (Path.to_string_maybe_quoted (Path.build p2)) ] -let odocs sctx target = +let odoc_artefacts sctx target = let ctx = Super_context.context sctx in let dir = Paths.odocs ctx target in match target with @@ -460,18 +510,16 @@ let odocs sctx target = |> create_odoc ctx ~target) | Lib lib -> let info = Lib.Local.info lib in - let dir = Lib_info.src_dir info in - let+ modules = - let name = Lib_info.name info in - Dir_contents.get sctx ~dir >>= Dir_contents.ocaml - >>| Ml_sources.modules ~for_:(Library name) - in let obj_dir = Lib_info.obj_dir info in - Modules.fold_no_vlib modules ~init:[] ~f:(fun m acc -> - let odoc = Obj_dir.Module.odoc obj_dir m in - create_odoc ctx ~target odoc :: acc) - -let setup_lib_html_rules_def = + let* modules = entry_modules_by_lib sctx lib in + List.map + ~f:(fun m -> + let odoc_file = Obj_dir.Module.odoc obj_dir m in + create_odoc ctx ~target odoc_file) + modules + |> Memo.Build.return + +let setup_lib_odocl_rules_def = let module Input = struct module Super_context = Super_context.As_memo_key @@ -491,28 +539,20 @@ let setup_lib_html_rules_def = let to_dyn _ = Dyn.Opaque end in let f (sctx, lib, requires) = - let ctx = Super_context.context sctx in - let* odocs = odocs sctx (Lib lib) in + let* odocs = odoc_artefacts sctx (Lib lib) in let pkg = Lib_info.package (Lib.Local.info lib) in - let* () = Memo.Build.parallel_iter odocs ~f:(fun odoc -> - setup_html sctx ~pkg ~requires odoc) - in - let html_files = List.map ~f:(fun o -> Path.build o.html_file) odocs in - let static_html = List.map ~f:Path.build (static_html ctx) in - Rules.Produce.Alias.add_deps - (Dep.html_alias ctx (Lib lib)) - (Action_builder.paths (List.rev_append static_html html_files)) + link_odoc_rules sctx ~pkg ~requires odoc) in - Memo.With_implicit_output.create "setup-library-html-rules" + Memo.With_implicit_output.create "setup_library_odocls_rules" ~implicit_output:Rules.implicit_output ~input:(module Input) f -let setup_lib_html_rules sctx lib ~requires = - Memo.With_implicit_output.exec setup_lib_html_rules_def (sctx, lib, requires) +let setup_lib_odocl_rules sctx lib ~requires = + Memo.With_implicit_output.exec setup_lib_odocl_rules_def (sctx, lib, requires) -let setup_pkg_html_rules_def = +let setup_pkg_rules_def memo_name f = let module Input = struct module Super_context = Super_context.As_memo_key @@ -536,33 +576,90 @@ let setup_pkg_html_rules_def = ; List (List.map ~f:Lib.Local.to_dyn libs) ] end in - Memo.With_implicit_output.create "setup-package-html-rules" + Memo.With_implicit_output.create memo_name ~input:(module Input) - ~implicit_output:Rules.implicit_output - (fun (sctx, pkg, (libs : Lib.Local.t list)) -> - let* requires = - let libs = (libs :> Lib.t list) in - Lib.closure libs ~linking:false + ~implicit_output:Rules.implicit_output f + +let setup_pkg_odocl_rules_def = + let f (sctx, pkg, (libs : Lib.Local.t list)) = + let* requires = + let libs = (libs :> Lib.t list) in + Lib.closure libs ~linking:false + in + let* () = + Memo.Build.parallel_iter libs ~f:(setup_lib_odocl_rules sctx ~requires) + and* _ = + let* pkg_odocs = odoc_artefacts sctx (Pkg pkg) in + let pkg = Some pkg in + let+ () = + Memo.Build.parallel_iter pkg_odocs ~f:(fun odoc -> + link_odoc_rules sctx ~pkg ~requires odoc) in - let ctx = Super_context.context sctx in - let* () = - Memo.Build.parallel_iter libs ~f:(setup_lib_html_rules sctx ~requires) - and* pkg_odocs = - let* pkg_odocs = odocs sctx (Pkg pkg) in - let+ () = - Memo.Build.parallel_iter pkg_odocs - ~f:(setup_html sctx ~pkg:(Some pkg) ~requires) - in - pkg_odocs - and* lib_odocs = - Memo.Build.parallel_map libs ~f:(fun lib -> odocs sctx (Lib lib)) + pkg_odocs + and* _ = + Memo.Build.parallel_map libs ~f:(fun lib -> odoc_artefacts sctx (Lib lib)) + in + Memo.Build.return () + in + setup_pkg_rules_def "setup-package-odocls-rules" f + +let setup_pkg_odocl_rules sctx ~pkg ~libs : unit Memo.Build.t = + Memo.With_implicit_output.exec setup_pkg_odocl_rules_def (sctx, pkg, libs) + +let setup_lib_html_rules_def = + let module Input = struct + module Super_context = Super_context.As_memo_key + + type t = Super_context.t * Lib.Local.t + + let equal (sc1, l1) (sc2, l2) = + Super_context.equal sc1 sc2 && Lib.Local.equal l1 l2 + + let hash (sc, l) = Hashtbl.hash (Super_context.hash sc, Lib.Local.hash l) + + let to_dyn _ = Dyn.Opaque + end in + let f (sctx, lib) = + let ctx = Super_context.context sctx in + let* odocs = odoc_artefacts sctx (Lib lib) in + let* () = + Memo.Build.parallel_iter odocs ~f:(fun odoc -> setup_html sctx odoc) + in + let html_files = List.map ~f:(fun o -> Path.build o.html_file) odocs in + let static_html = List.map ~f:Path.build (static_html ctx) in + Rules.Produce.Alias.add_deps + (Dep.html_alias ctx (Lib lib)) + (Action_builder.paths (List.rev_append static_html html_files)) + in + Memo.With_implicit_output.create "setup-library-html-rules" + ~implicit_output:Rules.implicit_output + ~input:(module Input) + f + +let setup_lib_html_rules sctx lib = + Memo.With_implicit_output.exec setup_lib_html_rules_def (sctx, lib) + +let setup_pkg_html_rules_def = + let f (sctx, pkg, (libs : Lib.Local.t list)) = + let ctx = Super_context.context sctx in + let* () = Memo.Build.parallel_iter libs ~f:(setup_lib_html_rules sctx) + and* pkg_odocs = + let* pkg_odocs = odoc_artefacts sctx (Pkg pkg) in + let+ () = + Memo.Build.parallel_iter pkg_odocs ~f:(fun o -> setup_html sctx o) in - let odocs = List.concat (pkg_odocs :: lib_odocs) in - let html_files = List.map ~f:(fun o -> Path.build o.html_file) odocs in - let static_html = List.map ~f:Path.build (static_html ctx) in - Rules.Produce.Alias.add_deps - (Dep.html_alias ctx (Pkg pkg)) - (Action_builder.paths (List.rev_append static_html html_files))) + pkg_odocs + and* lib_odocs = + Memo.Build.parallel_map libs ~f:(fun lib -> odoc_artefacts sctx (Lib lib)) + in + let odocs = List.concat (pkg_odocs :: lib_odocs) in + let html_files = List.map ~f:(fun o -> Path.build o.html_file) odocs in + let static_html = List.map ~f:Path.build (static_html ctx) in + Rules.Produce.Alias.add_deps + (Dep.html_alias ctx (Pkg pkg)) + (Action_builder.paths (List.rev_append static_html html_files)) + in + setup_pkg_rules_def "setup-package-html-rules" f let setup_pkg_html_rules sctx ~pkg ~libs : unit Memo.Build.t = Memo.With_implicit_output.exec setup_pkg_html_rules_def (sctx, pkg, libs) @@ -582,28 +679,6 @@ let setup_package_aliases sctx (pkg : Package.t) = |> Action_builder.deps |> Rules.Produce.Alias.add_deps alias -let entry_modules_by_lib sctx lib = - let info = Lib.Local.info lib in - let dir = Lib_info.src_dir info in - let name = Lib.name (Lib.Local.to_lib lib) in - Dir_contents.get sctx ~dir >>= Dir_contents.ocaml - >>| Ml_sources.modules ~for_:(Library name) - >>| Modules.entry_modules - -let entry_modules sctx ~pkg = - let l = - libs_of_pkg sctx ~pkg - |> List.filter ~f:(fun lib -> - Lib.Local.info lib |> Lib_info.status |> Lib_info.Status.is_private - |> not) - in - let+ l = - Memo.Build.parallel_map l ~f:(fun l -> - let+ m = entry_modules_by_lib sctx l in - (l, m)) - in - Lib.Local.Map.of_list_exn l - let default_index ~pkg entry_modules = let b = Buffer.create 512 in Printf.bprintf b "{0 %s index}\n" (Package.Name.to_string pkg); @@ -717,14 +792,14 @@ let gen_rules sctx ~dir:_ rest = Rules.produce rules) | [ "_odoc"; "pkg"; pkg ] -> with_package sctx pkg ~f:(fun pkg -> setup_package_odoc_rules sctx ~pkg) - | [ "_html"; lib_unique_name_or_pkg ] -> + | [ "_odocls"; lib_unique_name_or_pkg ] -> has_rules ((* TODO we can be a better with the error handling in the case where lib_unique_name_or_pkg is neither a valid pkg or lnu *) let lib, lib_db = Scope_key.of_string sctx lib_unique_name_or_pkg in - let setup_pkg_html_rules pkg = - let pkg_libs = libs_of_pkg sctx ~pkg in - setup_pkg_html_rules sctx ~pkg ~libs:pkg_libs + let setup_pkg_odocl_rules pkg = + let* pkg_libs = load_all_odoc_rules_pkg sctx ~pkg in + setup_pkg_odocl_rules sctx ~pkg ~libs:pkg_libs in (* jeremiedimino: why isn't [None] some kind of error here? *) let* lib = @@ -738,9 +813,41 @@ let gen_rules sctx ~dir:_ rest = match Lib_info.package (Lib.Local.info lib) with | None -> let* requires = - Lib.closure ~linking:false [ Lib.Local.to_lib lib ] + Lib.closure [ Lib.Local.to_lib lib ] ~linking:false in - setup_lib_html_rules sctx lib ~requires + setup_lib_odocl_rules sctx lib ~requires + | Some pkg -> setup_pkg_odocl_rules pkg) + and+ () = + match + Package.Name.Map.find (SC.packages sctx) + (Package.Name.of_string lib_unique_name_or_pkg) + with + | None -> Memo.Build.return () + | Some pkg -> + let name = Package.name pkg in + setup_pkg_odocl_rules name + in + ()) + | [ "_html"; lib_unique_name_or_pkg ] -> + has_rules + ((* TODO we can be a better with the error handling in the case where + lib_unique_name_or_pkg is neither a valid pkg or lnu *) + let lib, lib_db = Scope_key.of_string sctx lib_unique_name_or_pkg in + let setup_pkg_html_rules pkg = + let* pkg_libs = load_all_odoc_rules_pkg sctx ~pkg in + setup_pkg_html_rules sctx ~pkg ~libs:pkg_libs + in + (* jeremiedimino: why isn't [None] some kind of error here? *) + let* lib = + let+ lib = Lib.DB.find lib_db lib in + Option.bind ~f:Lib.Local.of_lib lib + in + let+ () = + match lib with + | None -> Memo.Build.return () + | Some lib -> ( + match Lib_info.package (Lib.Local.info lib) with + | None -> setup_lib_html_rules sctx lib | Some pkg -> setup_pkg_html_rules pkg) and+ () = match diff --git a/test/blackbox-tests/test-cases/odoc/multiple-private-libs.t/run.t b/test/blackbox-tests/test-cases/odoc/multiple-private-libs.t/run.t index 9db3ef023eb..bcf2b7dba9e 100644 --- a/test/blackbox-tests/test-cases/odoc/multiple-private-libs.t/run.t +++ b/test/blackbox-tests/test-cases/odoc/multiple-private-libs.t/run.t @@ -6,5 +6,7 @@ This test checks that there is no clash when two private libraries have the same ocamlc b/.test.objs/byte/test.{cmi,cmo,cmt} odoc a/.test.objs/byte/test.odoc odoc b/.test.objs/byte/test.odoc + odoc _doc/_odocls/test@6aabb9861046/test.odocl + odoc _doc/_odocls/test@ea8c79305c05/test.odocl odoc _doc/_html/test@6aabb9861046/Test/.dummy,_doc/_html/test@6aabb9861046/Test/index.html odoc _doc/_html/test@ea8c79305c05/Test/.dummy,_doc/_html/test@ea8c79305c05/Test/index.html diff --git a/test/blackbox-tests/test-cases/odoc/odoc-simple.t/run.t b/test/blackbox-tests/test-cases/odoc/odoc-simple.t/run.t index fabc45c58e7..6b74815d066 100644 --- a/test/blackbox-tests/test-cases/odoc/odoc-simple.t/run.t +++ b/test/blackbox-tests/test-cases/odoc/odoc-simple.t/run.t @@ -1,6 +1,16 @@ This test generates documentation using odoc for a library: $ dune build @doc + +This test if `.odocl` files are generated + $ find _build/default/_doc/_odocls -name '*.odocl' | sort -n + _build/default/_doc/_odocls/bar/bar.odocl + _build/default/_doc/_odocls/bar/page-index.odocl + _build/default/_doc/_odocls/foo/foo.odocl + _build/default/_doc/_odocls/foo/foo2.odocl + _build/default/_doc/_odocls/foo/foo_byte.odocl + _build/default/_doc/_odocls/foo/page-index.odocl + $ dune runtest diff --git a/test/blackbox-tests/test-cases/odoc/odoc-unique-mlds.t/run.t b/test/blackbox-tests/test-cases/odoc/odoc-unique-mlds.t/run.t index a462c563c7a..6c621ba8f34 100644 --- a/test/blackbox-tests/test-cases/odoc/odoc-unique-mlds.t/run.t +++ b/test/blackbox-tests/test-cases/odoc/odoc-unique-mlds.t/run.t @@ -7,6 +7,9 @@ Duplicate mld's in the same scope ocamlc lib2/.root_lib2.objs/byte/root_lib2.{cmi,cmo,cmt} odoc lib1/.root_lib1.objs/byte/root_lib1.odoc odoc lib2/.root_lib2.objs/byte/root_lib2.odoc + odoc _doc/_odocls/root/root_lib1.odocl + odoc _doc/_odocls/root/root_lib2.odocl + odoc _doc/_odocls/root/page-index.odocl odoc _doc/_html/root/Root_lib1/.dummy,_doc/_html/root/Root_lib1/index.html odoc _doc/_html/root/Root_lib2/.dummy,_doc/_html/root/Root_lib2/index.html odoc _doc/_html/root/index.html @@ -22,6 +25,10 @@ Duplicate mld's in different scope ocamlc scope2/.scope2.objs/byte/scope2.{cmi,cmo,cmt} odoc scope1/.scope1.objs/byte/scope1.odoc odoc scope2/.scope2.objs/byte/scope2.odoc + odoc _doc/_odocls/scope1/scope1.odocl + odoc _doc/_odocls/scope1/page-index.odocl + odoc _doc/_odocls/scope2/scope2.odocl + odoc _doc/_odocls/scope2/page-index.odocl odoc _doc/_html/scope1/Scope1/.dummy,_doc/_html/scope1/Scope1/index.html odoc _doc/_html/scope1/index.html odoc _doc/_html/scope2/Scope2/.dummy,_doc/_html/scope2/Scope2/index.html diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/bar.ml b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/bar.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune new file mode 100644 index 00000000000..ea90126b018 --- /dev/null +++ b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune @@ -0,0 +1,2 @@ +(library + (public_name foo)) diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune-project b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune-project new file mode 100644 index 00000000000..42c0c167431 --- /dev/null +++ b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/dune-project @@ -0,0 +1 @@ +(lang dune 1.10) diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/foo.ml b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/foo.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/foo.opam b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/foo.opam new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/run.t b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/run.t new file mode 100644 index 00000000000..e90119d8398 --- /dev/null +++ b/test/blackbox-tests/test-cases/odoc/odoc-wrapped-lib.t/run.t @@ -0,0 +1,21 @@ +This test generates documentation for non-hidden modules only for a library: + + $ dune build @doc + + Hidden modules should be compiled + $ find _build/default -name '*.odoc' | sort -n + _build/default/.foo.objs/byte/foo.odoc + _build/default/.foo.objs/byte/foo__.odoc + _build/default/.foo.objs/byte/foo__Bar.odoc + _build/default/_doc/_odoc/pkg/foo/page-index.odoc + + Hidden modules should not be linked + $ find _build/default -name '*.odocl' | sort -n + _build/default/_doc/_odocls/foo/foo.odocl + _build/default/_doc/_odocls/foo/page-index.odocl + + We don't expect html for hidden modules + $ find _build/default -name '*.html' | sort -n + _build/default/_doc/_html/foo/Foo/index.html + _build/default/_doc/_html/foo/index.html + _build/default/_doc/_html/index.html