From 7a26c18e201b2b73348bd31c46773c87e9dafe8b Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Fri, 16 Mar 2018 13:24:45 +0800 Subject: [PATCH] New odoc rules --- src/gen_rules.ml | 20 +- src/odoc.boot.ml | 10 + src/odoc.ml | 738 +++++++++++------- src/odoc.mli | 28 +- .../test-cases/gen-opam-install-file/doc.mld | 0 .../test-cases/gen-opam-install-file/jbuild | 3 + .../test-cases/gen-opam-install-file/run.t | 3 + .../test-cases/multiple-private-libs/run.t | 11 +- .../test-cases/odoc-unique-mlds/run.t | 42 +- test/blackbox-tests/test-cases/odoc/jbuild | 4 +- test/blackbox-tests/test-cases/odoc/run.t | 30 +- 11 files changed, 538 insertions(+), 351 deletions(-) create mode 100644 src/odoc.boot.ml create mode 100644 test/blackbox-tests/test-cases/gen-opam-install-file/doc.mld diff --git a/src/gen_rules.ml b/src/gen_rules.ml index 72564e66..ef0694a5 100644 --- a/src/gen_rules.ml +++ b/src/gen_rules.ml @@ -11,6 +11,8 @@ open! No_io module Gen(P : Install_rules.Params) = struct module Alias = Build_system.Alias module SC = Super_context + module Odoc = Odoc.Gen(P) + open P let ctx = SC.context sctx @@ -760,13 +762,7 @@ module Gen(P : Install_rules.Params) = struct SC.add_rule sctx build ); - (* Odoc *) - let mld_files = - String_set.fold files ~init:[] ~f:(fun fn acc -> - if Filename.check_suffix fn ".mld" then fn :: acc else acc) - in - Odoc.setup_library_rules sctx lib ~dir ~requires ~modules ~dep_graphs - ~mld_files ~scope + Odoc.setup_library_odoc_rules lib ~dir ~requires ~modules ~dep_graphs ~scope ; let flags = @@ -983,7 +979,7 @@ module Gen(P : Install_rules.Params) = struct (match components with | ".js" :: rest -> Js_of_ocaml_rules.setup_separate_compilation_rules sctx rest - | "_doc" :: rest -> Odoc.gen_rules sctx rest ~dir + | "_doc" :: rest -> Odoc.gen_rules rest ~dir | ".ppx" :: rest -> Preprocessing.gen_rules sctx rest | _ -> match Path.Map.find stanzas_per_dir dir with @@ -1006,7 +1002,13 @@ module Gen(P : Install_rules.Params) = struct let module_names_of_lib = module_names_of_lib let mlds_of_dir = mlds_of_dir end) in - Install_rules.init () + Install_rules.init (); + Odoc.init ~modules_by_lib:(fun ~dir lib -> + let m = modules_by_lib ~dir lib in + match m.alias_module with + | Some m -> [m] + | None -> Module.Name.Map.values m.modules + ) ~mlds_of_dir end module type Gen = sig diff --git a/src/odoc.boot.ml b/src/odoc.boot.ml new file mode 100644 index 00000000..fe731c5b --- /dev/null +++ b/src/odoc.boot.ml @@ -0,0 +1,10 @@ + +module Gen (S : sig val sctx : Super_context.t end) = struct + + let setup_library_odoc_rules _ ~dir:_ ~scope:_ ~modules:_ ~requires:_ + ~dep_graphs:_ = () + + let init ~modules_by_lib:_ ~mlds_of_dir:_ = () + + let gen_rules ~dir:_ _ = () +end diff --git a/src/odoc.ml b/src/odoc.ml index 6b665833..ee8b4a19 100644 --- a/src/odoc.ml +++ b/src/odoc.ml @@ -4,113 +4,100 @@ open Build.O module SC = Super_context -module Doc = struct - let root sctx = Path.relative (SC.context sctx).Context.build_dir "_doc" +let (++) = Path.relative - type origin = - | Public of string - | Private of string * Scope_info.Name.t +let lib_unique_name lib = + let name = Lib.name lib in + match Lib.status lib with + | Installed -> assert false + | Public _ -> name + | Private scope_name -> SC.Scope_key.to_string name scope_name - let dir_internal t origin = - let name = - match origin with - | Public n -> n - | Private (n, s) -> sprintf "%s@%s" n (Scope_info.Name.to_string s) - in - Path.relative (root t) name +let pkg_or_lnu lib = + match Lib.package lib with + | Some p -> Package.Name.to_string p + | None -> lib_unique_name lib - let dir t (lib : Library.t) = - dir_internal t - (match lib.public with - | Some { name; _ } -> Public name - | None -> Private (lib.name, lib.scope_name)) +type target = + | Lib of Lib.t + | Pkg of Package.Name.t - let alias = Build_system.Alias.make ".doc-all" +module Gen (S : sig val sctx : SC.t end) = struct + open S - let deps t = - Build.dyn_paths (Build.arr ( - List.fold_left ~init:[] ~f:(fun acc (lib : Lib.t) -> - if Lib.is_local lib then ( - let dir = - dir_internal t - (match Lib.status lib with - | Installed -> assert false - | Public _ -> Public (Lib.name lib) - | Private s -> Private (Lib.name lib, s)) - in - Build_system.Alias.stamp_file (alias ~dir) :: acc - ) else ( - acc - ) - ))) + let context = SC.context sctx - let alias t lib = alias ~dir:(dir t lib) + module Paths = struct + let root = context.Context.build_dir ++ "_doc" - let static_deps t lib = Build_system.Alias.dep (alias t lib) + let odocs m = + root ++ ( + match m with + | Lib lib -> sprintf "_odoc/lib/%s" (lib_unique_name lib) + | Pkg pkg -> sprintf "_odoc/pkg/%s" (Package.Name.to_string pkg) + ) - let setup_deps t lib files = SC.add_alias_deps t (alias t lib) files + let html_root = root ++ "_html" - let dir t lib = dir t lib -end + let html m = + html_root ++ ( + match m with + | Pkg pkg -> Package.Name.to_string pkg + | Lib lib -> pkg_or_lnu lib + ) + let gen_mld_dir (pkg : Package.t) = + root ++ "_mlds" ++ (Package.Name.to_string pkg.name) + end -let ( ++ ) = Path.relative + module Dep = struct + let html_alias m = + Build_system.Alias.doc ~dir:(Paths.html m) -let get_odoc sctx = SC.resolve_program sctx "odoc" ~hint:"opam install odoc" -let odoc_ext = ".odoc" + let alias = Build_system.Alias.make ".odoc-all" -module Mld : sig - type t - val create : name:string -> t + let deps = + Build.dyn_paths (Build.arr ( + List.fold_left ~init:[] ~f:(fun acc (lib : Lib.t) -> + if Lib.is_local lib then ( + let dir = Paths.odocs (Lib lib) in + Build_system.Alias.stamp_file (alias ~dir) :: acc + ) else ( + acc + ) + ))) - val odoc_file : doc_dir:Path.t -> t -> Path.t - val odoc_input : doc_dir:Path.t -> t -> Path.t + let alias m = alias ~dir:(Paths.odocs m) - val html_filename : t -> string -end = struct - type t = string (** source file name without the extension. *) + (* let static_deps t lib = Build_system.Alias.dep (alias t lib) *) - let create ~name = name + let setup_deps m files = SC.add_alias_deps sctx (alias m) files + end - let odoc_file ~doc_dir t = - Path.relative doc_dir (sprintf "page-%s%s" t odoc_ext) + let odoc = SC.resolve_program sctx "odoc" ~hint:"opam install odoc" + let odoc_ext = ".odoc" - let odoc_input ~doc_dir t = - Path.relative doc_dir (sprintf "%s-generated.mld" t) + module Mld : sig + type t - let html_filename t = - sprintf "%s.html" t -end + val create : Path.t -> t -module Module_or_mld = struct - type t = - | Mld of Mld.t - | Module of Module.t + val odoc_file : doc_dir:Path.t -> t -> Path.t + val odoc_input : t -> Path.t - let odoc_file ~doc_dir = function - | Mld m -> Mld.odoc_file ~doc_dir m - | Module m -> Module.odoc_file ~doc_dir m + end = struct + type t = Path.t - let odoc_input ~obj_dir ~doc_dir = function - | Mld m -> Mld.odoc_input ~doc_dir m - | Module m -> Module.cmti_file m ~obj_dir + let create p = p - let html_dir ~doc_dir = function - | Mld _ -> doc_dir - | Module m -> doc_dir ++ String.capitalize m.obj_name + let odoc_file ~doc_dir t = + let t = Filename.chop_extension (Path.basename t) in + Path.relative doc_dir (sprintf "page-%s%s" t odoc_ext) - let html_file ~doc_dir t = - match t with - | Mld m -> html_dir ~doc_dir t ++ Mld.html_filename m - | Module _ -> html_dir ~doc_dir t ++ "index.html" -end + let odoc_input t = t + end -let module_or_mld_deps (m : Module_or_mld.t) ~doc_dir - ~(dep_graphs:Ocamldep.Dep_graphs.t) = - match m with - | Mld _ -> - Build.arr (fun x -> x) - | Module m -> + let module_deps (m : Module.t) ~doc_dir ~(dep_graphs:Ocamldep.Dep_graphs.t) = Build.dyn_paths ((match m.intf with | Some _ -> @@ -120,194 +107,140 @@ let module_or_mld_deps (m : Module_or_mld.t) ~doc_dir Ocamldep.Dep_graph.deps_of dep_graphs.impl m) >>^ List.map ~f:(Module.odoc_file ~doc_dir)) -let compile sctx (m : Module_or_mld.t) ~odoc ~dir ~obj_dir ~includes ~dep_graphs - ~doc_dir ~lib_unique_name = - let context = SC.context sctx in - let odoc_file = Module_or_mld.odoc_file m ~doc_dir in - SC.add_rule sctx - (module_or_mld_deps m ~doc_dir ~dep_graphs - >>> - includes - >>> - Build.run ~context ~dir:doc_dir odoc - [ A "compile" - ; A "-I"; Path dir - ; Dyn (fun x -> x) - ; As ["--pkg"; lib_unique_name] - ; A "-o"; Target odoc_file - ; Dep (Module_or_mld.odoc_input m ~obj_dir ~doc_dir) - ]); - (m, odoc_file) - -let to_html sctx (m : Module_or_mld.t) odoc_file ~doc_dir ~odoc ~dir ~includes - ~(lib : Library.t) = - let context = SC.context sctx in - let html_dir = Module_or_mld.html_dir ~doc_dir m in - let html_file = Module_or_mld.html_file ~doc_dir m in - let to_remove, jbuilder_keep = - match m with - | Mld _ -> html_file, [] - | Module _ -> - let jbuilder_keep = - Build.create_file (html_dir ++ Config.jbuilder_keep_fname) in - html_dir, [jbuilder_keep] - in - SC.add_rule sctx - (Doc.static_deps sctx lib - >>> - includes - >>> - Build.progn ( - Build.remove_tree to_remove - :: Build.mkdir html_dir - :: Build.run ~context ~dir odoc ~extra_targets:[html_file] - [ A "html" - ; A "-I"; Path doc_dir - ; Dyn (fun x -> x) - ; A "-o"; Path (Path.parent doc_dir) - ; Dep odoc_file - ] - :: jbuilder_keep - ) - ); - html_file - -let all_mld_files sctx ~(lib : Library.t) ~modules ~dir files = - let all_files = - if List.mem "index.mld" ~set:files then files else "index.mld" :: files - in - let lib_name = Library.best_name lib in - let doc_dir = Doc.dir sctx lib in - List.map all_files ~f:(fun file -> - let name = Filename.chop_extension file in - let mld = Mld.create ~name in - let generated_mld = Mld.odoc_input ~doc_dir mld in - let source_mld = dir ++ file in + let compile_module (m : Module.t) ~dir ~obj_dir ~includes ~dep_graphs + ~doc_dir ~pkg_or_lnu = + let odoc_file = Module.odoc_file m ~doc_dir in SC.add_rule sctx - (Build.if_file_exists source_mld - ~then_:(Build.contents source_mld) - ~else_:(Build.arr (fun () -> - (if lib.wrapped then - sprintf - "{1 Library %s}\n\ - The entry point for this library is module {!module:%s}." - lib_name - (String.capitalize lib.name) - else - sprintf - "{1 Library %s}\n\ - This library exposes the following toplevel modules: {!modules:%s}." - lib_name - ((Module.Name.Map.keys modules :> string list) - |> String.concat ~sep:" ")))) + (module_deps m ~doc_dir ~dep_graphs >>> - Build.write_file_dyn generated_mld); - mld - ) + includes + >>> + Build.run ~context ~dir:doc_dir odoc + [ A "compile" + ; A "-I"; Path dir + ; Dyn (fun x -> x) + ; As ["--pkg"; pkg_or_lnu] + ; A "-o"; Target odoc_file + ; Dep (Module.cmti_file m ~obj_dir) + ]); + (m, odoc_file) -let css_file ~doc_dir = doc_dir ++ "odoc.css" + let compile_mld (m : Mld.t) ~includes ~doc_dir ~pkg = + let odoc_file = Mld.odoc_file m ~doc_dir in + SC.add_rule sctx + (includes + >>> + Build.run ~context ~dir:doc_dir odoc + [ A "compile" + ; Dyn (fun x -> x) + ; As ["--pkg"; Package.Name.to_string pkg] + ; A "-o"; Target odoc_file + ; Dep (Mld.odoc_input m) + ]); + odoc_file -let toplevel_index ~doc_dir = doc_dir ++ "index.html" + type odoc = + { odoc_input: Path.t + ; html_dir: Path.t + ; html_file: Path.t + ; html_alias: Build_system.Alias.t + ; typ: [`Module | `Mld] + } -let setup_library_rules sctx (lib : Library.t) ~dir ~scope ~modules ~mld_files - ~requires ~(dep_graphs:Ocamldep.Dep_graph.t Ml_kind.Dict.t) = - let doc_dir = Doc.dir sctx lib in - let obj_dir, lib_unique_name = + let odoc_include_flags libs = + let paths = + libs |> List.fold_left ~f:(fun paths lib -> + if Lib.is_local lib then ( + Path.Set.add paths (Paths.odocs (Lib lib)) + ) else ( + paths + ) + ) ~init:Path.Set.empty in + Arg_spec.S (List.concat_map (Path.Set.to_list paths) + ~f:(fun dir -> [Arg_spec.A "-I"; Path dir])) + + let to_html (odoc_file : odoc) ~deps = + let to_remove, jbuilder_keep = + match odoc_file.typ with + | `Mld -> odoc_file.html_file, [] + | `Module -> + let jbuilder_keep = + Build.create_file (odoc_file.html_dir ++ Config.jbuilder_keep_fname) in + odoc_file.html_dir, [jbuilder_keep] + in + SC.add_rule sctx + (deps + >>> Build.progn ( + Build.remove_tree to_remove + :: Build.mkdir odoc_file.html_dir + :: Build.run ~context ~dir:Paths.html_root + odoc ~extra_targets:[odoc_file.html_file] + [ A "html" + ; Dyn odoc_include_flags + ; A "-o"; Path Paths.html_root + ; Dep odoc_file.odoc_input + ] + :: jbuilder_keep + ) + ); + odoc_file.html_file + + let css_file = Paths.html_root ++ "odoc.css" + + let toplevel_index = Paths.html_root ++ "index.html" + + let setup_library_odoc_rules (library : Library.t) ~dir ~scope ~modules + ~requires ~(dep_graphs:Ocamldep.Dep_graph.t Ml_kind.Dict.t) = let lib = - Option.value_exn (Lib.DB.find_even_when_hidden (Scope.libs scope) lib.name) + Option.value_exn (Lib.DB.find_even_when_hidden (Scope.libs scope) + library.name) in + (* Using the proper package name doesn't actually work since odoc assumes + that a package contains only 1 library *) + let pkg_or_lnu = pkg_or_lnu lib in + let doc_dir = Paths.odocs (Lib lib) in + let obj_dir = Lib.obj_dir lib in + let includes = + Build.memoize "includes" + (requires + >>> Dep.deps + >>^ Lib.L.include_flags ~stdlib_dir:context.stdlib_dir) in - let name = - let name = Lib.name lib in - match Lib.status lib with - | Installed -> assert false - | Public _ -> name - | Private scope_name -> - sprintf "%s@%s" name (Scope_info.Name.to_string scope_name) + let modules_and_odoc_files = + List.map (Module.Name.Map.values modules) ~f:( + compile_module ~dir ~obj_dir ~includes ~dep_graphs + ~doc_dir ~pkg_or_lnu) in - (Lib.obj_dir lib, name) - in - let odoc = get_odoc sctx in - let includes = - let ctx = SC.context sctx in - Build.memoize "includes" - (requires - >>> Doc.deps sctx - >>^ Lib.L.include_flags ~stdlib_dir:ctx.stdlib_dir) - in - let mld_files = - all_mld_files sctx ~dir ~lib ~modules mld_files - in - let mld_and_odoc_files = - List.map mld_files ~f:(fun m -> - compile sctx ~odoc ~dir ~obj_dir ~includes ~dep_graphs - ~doc_dir ~lib_unique_name (Mld m)) - in - let modules_and_odoc_files = - List.map (Module.Name.Map.values modules) ~f:(fun m -> - compile sctx ~odoc ~dir ~obj_dir ~includes ~dep_graphs - ~doc_dir ~lib_unique_name (Module m)) - in - let inputs_and_odoc_files = modules_and_odoc_files @ mld_and_odoc_files in - Doc.setup_deps sctx lib (List.map inputs_and_odoc_files ~f:snd); - (* - let modules_and_odoc_files = - if lib.wrapped then - let main_module_name = String.capitalize lib.name in - List.filter modules_and_odoc_files - ~f:(fun (m, _) -> m.Module.name = main_module_name) - else - modules_and_odoc_files - in*) - let html_files = - List.map inputs_and_odoc_files ~f:(fun (m, odoc_file) -> - to_html sctx m odoc_file ~doc_dir ~odoc ~dir ~includes ~lib) - in - let doc_root = Doc.root sctx in - let alias = - match lib.public with - | None -> Build_system.Alias.private_doc ~dir - | Some _ -> Build_system.Alias.doc ~dir in - SC.add_alias_deps sctx alias - (css_file ~doc_dir:doc_root - :: toplevel_index ~doc_dir:doc_root - :: html_files) + Dep.setup_deps (Lib lib) (List.map modules_and_odoc_files ~f:snd) -let setup_css_rule sctx = - let context = SC.context sctx in - let doc_dir = Doc.root sctx in - SC.add_rule sctx - (Build.run ~context - ~dir:context.build_dir - ~extra_targets:[css_file ~doc_dir] - (get_odoc sctx) - [ A "css"; A "-o"; Path doc_dir ]) + let setup_css_rule () = + SC.add_rule sctx + (Build.run ~context + ~dir:context.build_dir + ~extra_targets:[css_file] + odoc + [ A "css"; A "-o"; Path Paths.html_root ]) -let sp = Printf.sprintf + let sp = Printf.sprintf -let setup_toplevel_index_rule sctx = - let list_items = - Super_context.stanzas_to_consider_for_install sctx - |> List.filter_map ~f:(fun (_path, _scope, stanza) -> - match stanza with - | Stanza.Library - {Library.kind = Library.Kind.Normal; public = Some public_info; _} -> - let name = public_info.name in + let setup_toplevel_index_rule () = + let list_items = + Super_context.packages sctx + |> Package.Name.Map.to_list + |> List.filter_map ~f:(fun (name, pkg) -> + let name = Package.Name.to_string name in let link = sp {|%s|} name name in let version_suffix = - match public_info.package.Package.version_from_opam_file with + match pkg.Package.version_from_opam_file with | None -> "" | Some v -> sp {| %s|} v in - Some (sp "
  • %s%s
  • " link version_suffix) - - | _ -> - None) - in - let list_items = String.concat ~sep:"\n " list_items in - let html = - sp {| + Some (sp "
  • %s%s
  • " link version_suffix)) + in + let list_items = String.concat ~sep:"\n " list_items in + let html = sp +{| index @@ -321,28 +254,281 @@ let setup_toplevel_index_rule sctx =
      %s
    - - -|} list_items - in - let doc_dir = Doc.root sctx in - SC.add_rule sctx @@ Build.write_file (toplevel_index ~doc_dir) html - -let gen_rules sctx ~dir:_ rest = - match rest with - | [] -> - setup_css_rule sctx; - setup_toplevel_index_rule sctx - | lib :: _ -> - let lib, lib_db = - match String.rsplit2 lib ~on:'@' with - | None -> - (lib, SC.public_libs sctx) - | Some (lib, name) -> - (lib, - Scope.libs - (SC.find_scope_by_name sctx (Scope_info.Name.of_string name))) + + +|} list_items in - match Lib.DB.find lib_db lib with - | Error _ -> () - | Ok lib -> SC.load_dir sctx ~dir:(Lib.src_dir lib) + SC.add_rule sctx @@ Build.write_file toplevel_index html + + + let html_alias pkg = + Build_system.Alias.doc ~dir:( + Path.append context.build_dir pkg.Package.path + ) + + let libs_of_pkg ~pkg = + match Package.Name.Map.find (SC.libs_by_package sctx) pkg with + | None -> Lib.Set.empty + | Some (_, libs) -> libs + + let load_all_odoc_rules_pkg ~pkg = + let pkg_libs = libs_of_pkg ~pkg in + SC.load_dir sctx ~dir:(Paths.odocs (Pkg pkg)); + Lib.Set.iter pkg_libs ~f:(fun lib -> + SC.load_dir sctx ~dir:(Paths.odocs (Lib lib))); + pkg_libs + + let create_odoc ~target odoc_input = + let html_alias = Dep.html_alias target in + let html_base = Paths.html target in + match target with + | Lib _ -> + let html_dir = + html_base ++ ( + Path.basename odoc_input + |> Filename.chop_extension + |> Stdune.String.capitalize + ) in + { odoc_input + ; html_dir + ; html_file = html_dir ++ "index.html" + ; typ = `Module + ; html_alias + } + | Pkg _ -> + { odoc_input + ; html_dir = html_base + ; html_file = html_base ++ sprintf "%s.html" ( + Path.basename odoc_input + |> Filename.chop_extension + |> String.drop_prefix ~prefix:"page-" + |> Option.value_exn + ) + ; typ = `Mld + ; html_alias + } + + let setup_pkg_html_rules = + let loaded = Package.Name.Table.create ~default_value:None in + let odoc_glob = + Re.compile (Re.seq [Re.(rep1 any) ; Re.str ".odoc" ; Re.eos]) in + fun ~pkg ~libs -> + if Package.Name.Table.get loaded pkg = None then begin + Package.Name.Table.set loaded ~key:pkg ~data:(Some ()); + let odocs = + let odocs target = + let dir = Paths.odocs target in + SC.eval_glob sctx ~dir odoc_glob + |> List.map ~f:(fun d -> create_odoc (Path.relative dir d) ~target) + in + List.concat ( + odocs (Pkg pkg) + :: (List.map libs ~f:(fun lib -> odocs (Lib lib))) + ) in + let html_files = + let closure = + match Lib.closure libs with + | Ok closure -> closure + | Error _ -> libs in + let deps = Build.return closure >>> Dep.deps in + List.map odocs ~f:(to_html ~deps) in + List.iter ( + Dep.html_alias (Pkg pkg) + :: List.map ~f:(fun lib -> Dep.html_alias (Lib lib)) libs + ) ~f:(fun alias -> + SC.add_alias_deps sctx alias + [ css_file + ; toplevel_index + ] + ); + List.combine odocs html_files + |> List.iter ~f:(fun (odoc, html) -> + SC.add_alias_deps sctx odoc.html_alias [html] + ); + end + + let gen_rules ~dir:_ rest = + match rest with + | ["_html"] -> + setup_css_rule (); + setup_toplevel_index_rule () + | "_mlds" :: _pkg :: _ + | "_odoc" :: "pkg" :: _pkg :: _ -> + () (* rules were already setup lazily in gen_rules *) + | "_odoc" :: "lib" :: lib :: _ -> + let lib, lib_db = SC.Scope_key.of_string sctx lib in + begin match Lib.DB.find lib_db lib with + | Error _ -> () + | Ok lib -> SC.load_dir sctx ~dir:(Lib.src_dir lib) + end + | "_html" :: lib_unique_name_or_pkg :: _ -> + let setup_html_rules pkg = + setup_pkg_html_rules ~pkg ~libs:( + Lib.Set.to_list (load_all_odoc_rules_pkg ~pkg) + ) in + (* 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 = SC.Scope_key.of_string sctx lib_unique_name_or_pkg in + begin match Lib.DB.find lib_db lib with + | Error _ -> () + | Ok lib -> Option.iter (Lib.package lib) ~f:setup_html_rules + end; + Option.iter + (Package.Name.Map.find (SC.packages sctx) + (Package.Name.of_string lib_unique_name_or_pkg)) + ~f:(fun pkg -> setup_html_rules pkg.name) + | _ -> () + + let setup_package_aliases (pkg : Package.t) = + let alias = html_alias pkg in + SC.add_alias_deps sctx alias ( + Dep.html_alias (Pkg pkg.name) + :: (libs_of_pkg ~pkg:pkg.name + |> Lib.Set.to_list + |> List.map ~f:(fun lib -> Dep.html_alias (Lib lib))) + |> List.map ~f:Build_system.Alias.stamp_file + ) + + let pkg_odoc (pkg : Package.t) = Paths.odocs (Pkg pkg.name) + + let entry_modules ~(pkg : Package.t) ~entry_modules_by_lib = + libs_of_pkg ~pkg:pkg.name + |> Lib.Set.to_list + |> List.filter_map ~f:(fun l -> + if Lib.is_local l then ( + Some (l, entry_modules_by_lib l) + ) else ( + None + )) + |> Lib.Map.of_list_exn + + let default_index entry_modules = + let b = Buffer.create 512 in + Lib.Map.iteri entry_modules ~f:(fun lib modules -> + Buffer.add_string b ( + sprintf + "{1 Library %s}\n\ + This library exposes the following toplevel modules: \ + {!modules:%s}.\n" + (Lib.name lib) + (modules + |> List.map ~f:(fun m -> Module.Name.to_string (Module.name m)) + |> String.concat ~sep:" ") + ) + ); + Buffer.contents b + + let check_mlds_no_dupes ~pkg ~mlds = + match + List.map mlds ~f:(fun mld -> (Path.basename mld, mld)) + |> String_map.of_list + with + | Ok m -> m + | Error (_, p1, p2) -> + die "Package %s has two mld's with the same basename %s, %s" + (Package.Name.to_string pkg.Package.name) + (Path.to_string_maybe_quoted p1) + (Path.to_string_maybe_quoted p2) + + let setup_package_odoc_rules ~pkg ~mlds ~entry_modules_by_lib = + let mlds = check_mlds_no_dupes ~pkg ~mlds in + let mlds = + if String_map.mem mlds "index" then + mlds + else + let entry_modules = entry_modules ~pkg ~entry_modules_by_lib in + let gen_mld = Paths.gen_mld_dir pkg ++ "index.mld" in + SC.add_rule sctx ( + Build.write_file gen_mld (default_index entry_modules) + ); + String_map.add mlds "index" gen_mld in + let odocs = List.map (String_map.values mlds) ~f:(fun mld -> + compile_mld + (Mld.create mld) + ~pkg:pkg.name + ~doc_dir:(Paths.odocs (Pkg pkg.name)) + ~includes:(Build.arr (fun _ -> Arg_spec.As [])) + ) in + Dep.setup_deps (Pkg pkg.name) odocs + + let init ~modules_by_lib ~mlds_of_dir = + let docs_by_package = + let map = lazy ( + SC.stanzas sctx + |> List.concat_map ~f:(fun (w : SC.Dir_with_jbuild.t) -> + List.filter_map w.stanzas ~f:(function + | Jbuild.Stanza.Documentation (d : Jbuild.Documentation.t) -> + Some (d.package.name, (w.ctx_dir, d)) + | _ -> + None + )) + |> Package.Name.Map.of_list_multi + ) in + fun (p : Package.t) -> + Option.value (Package.Name.Map.find (Lazy.force map) p.name) ~default:[] + in + let modules_by_lib = + let module M = Map.Make( + struct + type t = Path.t * string + let compare (d1, l1) (d2, l2) = + match Path.compare d1 d2 with + | Ordering.Eq -> String.compare l1 l2 + | o -> o + end) in + let lib_to_library = lazy ( + SC.stanzas sctx + |> List.concat_map ~f:(fun (w : SC.Dir_with_jbuild.t) -> + List.filter_map w.stanzas ~f:(function + | Jbuild.Stanza.Library (l : Library.t) -> + Some ((w.ctx_dir, Library.best_name l), l) + | _ -> + None + )) + |> M.of_list_exn + ) in + fun lib -> + let dir = Lib.src_dir lib in + let library = Option.value_exn ( + M.find (Lazy.force lib_to_library) (dir, Lib.name lib) + ) in + modules_by_lib ~dir library + in + SC.packages sctx + |> Package.Name.Map.iter ~f:(fun (pkg : Package.t) -> + SC.on_load_dir sctx + ~dir:(pkg_odoc pkg) + ~f:(fun () -> + setup_package_odoc_rules + ~pkg + ~mlds:( + docs_by_package pkg + |> List.concat_map ~f:(fun (dir, doc) -> mlds_of_dir doc ~dir) + ) + ~entry_modules_by_lib:modules_by_lib + ); + (* setup @doc to build the correct html for the package *) + setup_package_aliases pkg; + ); + Super_context.add_alias_deps + sctx + (Build_system.Alias.private_doc ~dir:context.build_dir) + (SC.stanzas sctx + |> List.concat_map ~f:(fun (w : SC.Dir_with_jbuild.t) -> + List.filter_map w.stanzas ~f:(function + | Jbuild.Stanza.Library (l : Jbuild.Library.t) -> + begin match l.public with + | Some _ -> None + | None -> + let scope = SC.find_scope_by_dir sctx w.ctx_dir in + Some (Option.value_exn ( + Lib.DB.find_even_when_hidden (Scope.libs scope) l.name) + ) + end + | (_ : Jbuild.Stanza.t) -> None + )) + |> List.map ~f:(fun (lib : Lib.t) -> + Build_system.Alias.stamp_file (Dep.alias (Lib lib))) + ) + +end diff --git a/src/odoc.mli b/src/odoc.mli index 655d05e1..b8e78192 100644 --- a/src/odoc.mli +++ b/src/odoc.mli @@ -2,15 +2,21 @@ open Jbuild -val setup_library_rules - : Super_context.t - -> Library.t - -> dir:Path.t - -> scope:Scope.t - -> modules:Module.t Module.Name.Map.t - -> mld_files:string list - -> requires:(unit, Lib.t list) Build.t - -> dep_graphs:Ocamldep.Dep_graphs.t - -> unit +module Gen (S : sig val sctx : Super_context.t end) : sig -val gen_rules : Super_context.t -> dir:Path.t -> string list -> unit + val setup_library_odoc_rules + : Library.t + -> dir:Path.t + -> scope:Scope.t + -> modules:Module.t Module.Name.Map.t + -> requires:(unit, Lib.t list) Build.t + -> dep_graphs:Ocamldep.Dep_graphs.t + -> unit + + val init + : modules_by_lib:(dir:Path.t -> Library.t -> Module.t list) + -> mlds_of_dir:(Documentation.t -> dir:Path.t -> Path.t list) + -> unit + + val gen_rules : dir:Path.t -> string list -> unit +end diff --git a/test/blackbox-tests/test-cases/gen-opam-install-file/doc.mld b/test/blackbox-tests/test-cases/gen-opam-install-file/doc.mld new file mode 100644 index 00000000..e69de29b diff --git a/test/blackbox-tests/test-cases/gen-opam-install-file/jbuild b/test/blackbox-tests/test-cases/gen-opam-install-file/jbuild index 479f2462..2fceb68a 100644 --- a/test/blackbox-tests/test-cases/gen-opam-install-file/jbuild +++ b/test/blackbox-tests/test-cases/gen-opam-install-file/jbuild @@ -28,3 +28,6 @@ ((name runtest) (deps (foo.install)) (action (echo "${read:foo.install}")))) + +(documentation + ((mld_files (doc)))) diff --git a/test/blackbox-tests/test-cases/gen-opam-install-file/run.t b/test/blackbox-tests/test-cases/gen-opam-install-file/run.t index 2f122c84..9030708d 100644 --- a/test/blackbox-tests/test-cases/gen-opam-install-file/run.t +++ b/test/blackbox-tests/test-cases/gen-opam-install-file/run.t @@ -43,3 +43,6 @@ "_build/install/default/share/foo/bar.ml" "_build/install/default/share/foo/baz.ml" {"baz.ml"} ] + doc: [ + "_build/install/default/doc/foo/odoc-pages/doc.mld" {"odoc-pages/doc.mld"} + ] diff --git a/test/blackbox-tests/test-cases/multiple-private-libs/run.t b/test/blackbox-tests/test-cases/multiple-private-libs/run.t index 96427e5d..32182621 100644 --- a/test/blackbox-tests/test-cases/multiple-private-libs/run.t +++ b/test/blackbox-tests/test-cases/multiple-private-libs/run.t @@ -1,16 +1,9 @@ This test checks that there is no clash when two private libraries have the same name $ $JBUILDER build -j1 --display short --root . @doc-private - odoc _doc/odoc.css - odoc _doc/test@a/page-index.odoc ocamldep a/test.ml.d ocamlc a/.test.objs/test.{cmi,cmo,cmt} - odoc _doc/test@a/test.odoc - odoc _doc/test@a/index.html - odoc _doc/test@b/page-index.odoc + odoc _doc/_odoc/lib/test@a/test.odoc ocamldep b/test.ml.d ocamlc b/.test.objs/test.{cmi,cmo,cmt} - odoc _doc/test@b/test.odoc - odoc _doc/test@b/index.html - odoc _doc/test@a/Test/.jbuilder-keep,_doc/test@a/Test/index.html - odoc _doc/test@b/Test/.jbuilder-keep,_doc/test@b/Test/index.html + odoc _doc/_odoc/lib/test@b/test.odoc diff --git a/test/blackbox-tests/test-cases/odoc-unique-mlds/run.t b/test/blackbox-tests/test-cases/odoc-unique-mlds/run.t index a513aa15..301920f1 100644 --- a/test/blackbox-tests/test-cases/odoc-unique-mlds/run.t +++ b/test/blackbox-tests/test-cases/odoc-unique-mlds/run.t @@ -1,36 +1,26 @@ Duplicate mld's in the same scope $ $JBUILDER build @doc -j1 --display short --root ./same-scope 2>&1 | grep -v Entering - odoc _doc/odoc.css - odoc _doc/root.lib1/page-index.odoc - odoc _doc/root.lib1/page-test.odoc + odoc _doc/_html/odoc.css ocamlc lib1/.root_lib1.objs/root_lib1.{cmi,cmo,cmt} - odoc _doc/root.lib1/root_lib1.odoc - odoc _doc/root.lib1/index.html - odoc _doc/root.lib2/page-index.odoc - odoc _doc/root.lib2/page-test.odoc + odoc _doc/_odoc/lib/root.lib1/root_lib1.odoc ocamlc lib2/.root_lib2.objs/root_lib2.{cmi,cmo,cmt} - odoc _doc/root.lib2/root_lib2.odoc - odoc _doc/root.lib2/index.html - odoc _doc/root.lib1/test.html - odoc _doc/root.lib1/Root_lib1/.jbuilder-keep,_doc/root.lib1/Root_lib1/index.html - odoc _doc/root.lib2/test.html - odoc _doc/root.lib2/Root_lib2/.jbuilder-keep,_doc/root.lib2/Root_lib2/index.html + odoc _doc/_odoc/lib/root.lib2/root_lib2.odoc + odoc _doc/_html/root/Root_lib1/.jbuilder-keep,_doc/_html/root/Root_lib1/index.html + odoc _doc/_odoc/pkg/root/page-index.odoc + odoc _doc/_html/root/index.html + odoc _doc/_html/root/Root_lib2/.jbuilder-keep,_doc/_html/root/Root_lib2/index.html Duplicate mld's in different scope $ rm -rf diff-scope/_build $ $JBUILDER build @doc -j1 --display short --root ./diff-scope 2>&1 | grep -v Entering - odoc _doc/odoc.css - odoc _doc/scope1/page-foo.odoc - odoc _doc/scope1/page-index.odoc + odoc _doc/_html/odoc.css ocamlc scope1/.scope1.objs/scope1.{cmi,cmo,cmt} - odoc _doc/scope1/scope1.odoc - odoc _doc/scope1/foo.html - odoc _doc/scope2/page-foo.odoc - odoc _doc/scope2/page-index.odoc + odoc _doc/_odoc/lib/scope1/scope1.odoc + odoc _doc/_html/scope1/Scope1/.jbuilder-keep,_doc/_html/scope1/Scope1/index.html + odoc _doc/_odoc/pkg/scope1/page-index.odoc + odoc _doc/_html/scope1/index.html ocamlc scope2/.scope2.objs/scope2.{cmi,cmo,cmt} - odoc _doc/scope2/scope2.odoc - odoc _doc/scope2/foo.html - odoc _doc/scope1/index.html - odoc _doc/scope1/Scope1/.jbuilder-keep,_doc/scope1/Scope1/index.html - odoc _doc/scope2/index.html - odoc _doc/scope2/Scope2/.jbuilder-keep,_doc/scope2/Scope2/index.html + odoc _doc/_odoc/lib/scope2/scope2.odoc + odoc _doc/_html/scope2/Scope2/.jbuilder-keep,_doc/_html/scope2/Scope2/index.html + odoc _doc/_odoc/pkg/scope2/page-index.odoc + odoc _doc/_html/scope2/index.html diff --git a/test/blackbox-tests/test-cases/odoc/jbuild b/test/blackbox-tests/test-cases/odoc/jbuild index 72539fb9..29118d65 100644 --- a/test/blackbox-tests/test-cases/odoc/jbuild +++ b/test/blackbox-tests/test-cases/odoc/jbuild @@ -20,5 +20,5 @@ (alias ((name runtest) - (deps (_doc/index.html)) - (action (echo "${read:_doc/index.html}")))) + (deps (_doc/_html/index.html)) + (action (echo "${read:_doc/_html/index.html}")))) diff --git a/test/blackbox-tests/test-cases/odoc/run.t b/test/blackbox-tests/test-cases/odoc/run.t index d8abd1dd..5dd7849c 100644 --- a/test/blackbox-tests/test-cases/odoc/run.t +++ b/test/blackbox-tests/test-cases/odoc/run.t @@ -1,21 +1,15 @@ $ $JBUILDER build @doc -j1 --display short --root . - ocamldep foo_byte.ml.d - ocamlc .foo_byte.objs/foo_byte.{cmi,cmo,cmt} - odoc _doc/foo.byte/foo_byte.odoc - odoc _doc/foo.byte/page-index.odoc - odoc _doc/foo.byte/page-test.odoc - odoc _doc/foo.byte/Foo_byte/.jbuilder-keep,_doc/foo.byte/Foo_byte/index.html ocamldep foo.ml.d ocamlc .foo.objs/foo.{cmi,cmo,cmt} - odoc _doc/foo/foo.odoc - odoc _doc/foo/page-index.odoc - odoc _doc/foo/page-test.odoc - odoc _doc/foo/Foo/.jbuilder-keep,_doc/foo/Foo/index.html - odoc _doc/odoc.css - odoc _doc/foo.byte/index.html - odoc _doc/foo.byte/test.html - odoc _doc/foo/index.html - odoc _doc/foo/test.html + odoc _doc/_odoc/lib/foo/foo.odoc + ocamldep foo_byte.ml.d + ocamlc .foo_byte.objs/foo_byte.{cmi,cmo,cmt} + odoc _doc/_odoc/lib/foo.byte/foo_byte.odoc + odoc _doc/_html/foo/Foo/.jbuilder-keep,_doc/_html/foo/Foo/index.html + odoc _doc/_odoc/pkg/foo/page-index.odoc + odoc _doc/_html/foo/index.html + odoc _doc/_html/odoc.css + odoc _doc/_html/foo/Foo_byte/.jbuilder-keep,_doc/_html/foo/Foo_byte/index.html $ $JBUILDER runtest -j1 --display short --root . @@ -30,7 +24,7 @@

    OCaml package documentation

    1. foo
    2. -
    3. foo.byte
    - - + + +