diff --git a/src/driver/bin/odoc_driver_monorepo.ml b/src/driver/bin/odoc_driver_monorepo.ml index 985cd436fe..d3291eb1d4 100644 --- a/src/driver/bin/odoc_driver_monorepo.ml +++ b/src/driver/bin/odoc_driver_monorepo.ml @@ -46,7 +46,7 @@ let run path (fun () -> let units = let dirs = { Odoc_unit.odoc_dir; odocl_dir; index_dir; mld_dir } in - Odoc_units_of.packages ~dirs ~indices_style:Odoc_units_of.Custom + Odoc_units_of.packages ~dirs ~indices_style:Odoc_units_of.Automatic ~extra_paths ~remap:false all in Compile.init_stats units; diff --git a/src/driver/monorepo_style.ml b/src/driver/monorepo_style.ml index e8da42cebf..c5bb6f60c5 100644 --- a/src/driver/monorepo_style.ml +++ b/src/driver/monorepo_style.ml @@ -2,6 +2,9 @@ open Bos open Sexplib.Std [@@@warning "-69-30"] + +let monorepo_pkg_name = "__pkg__" + let dune = ref (Cmd.v "dune") type item = Library of library @@ -31,7 +34,7 @@ and library_list = library list and uid = string [@@deriving sexp] (* Eurgh *) -let internal_name_of_library : library -> string option = +let internal_name_of_library : library -> (string * Fpath.t) option = fun l -> match l.modules with | [] -> None @@ -42,9 +45,11 @@ let internal_name_of_library : library -> string option = | p :: _ -> ( let p' = Fpath.relativize ~root:(Fpath.v l.source_dir) (Fpath.v p) in match Option.map Fpath.segs p' with - | Some (objdir :: _ :: _) -> ( + | Some (objdir :: "byte" :: _) -> ( + (* cmt files are expected to be in [library_path/.libname.objs/byte/name.cmt]. *) match Astring.String.fields ~is_sep:(fun c -> c = '.') objdir with - | [ ""; libname; _ ] -> Some libname + | [ ""; libname; "objs" ] -> + Some (libname, Fpath.(parent (v p) |> rem_empty_seg)) | _ -> None) | _ -> None)) @@ -71,6 +76,7 @@ let of_dune_build dir = match contents with | Error _ -> [] | Ok c -> + let cset = Fpath.Set.of_list c in let libs = dune_describe dir in let local_libs = List.filter_map @@ -87,8 +93,8 @@ let of_dune_build dir = List.iter (fun (lib : library) -> Logs.debug (fun m -> - m "lib %s internal name: %a" lib.name - Fmt.(option string) + m "lib %s internal name: (%a)" lib.name + Fmt.(option (pair string Fpath.pp)) (internal_name_of_library lib))) local_libs; let uid_to_libname = @@ -100,9 +106,10 @@ let of_dune_build dir = List.fold_left (fun acc (l : library) -> Util.StringMap.add l.name - (List.filter_map - (fun uid -> Util.StringMap.find_opt uid uid_to_libname) - l.requires + ("stdlib" + :: List.filter_map + (fun uid -> Util.StringMap.find_opt uid uid_to_libname) + l.requires |> Util.StringSet.of_list) acc) Util.StringMap.empty local_libs @@ -121,7 +128,7 @@ let of_dune_build dir = | Library lib -> ( let libname_opt = internal_name_of_library lib in match libname_opt with - | Some libname -> + | Some (libname, _) -> let archive = Fpath.(append dir (v lib.source_dir / libname)) in @@ -137,14 +144,8 @@ let of_dune_build dir = (fun (Library lib) -> match internal_name_of_library lib with | None -> None - | Some libname -> - let cmtidir = - Fpath.( - append dir - (v lib.source_dir - / Printf.sprintf ".%s.objs" libname - / "byte")) - in + | Some (_, cmtidir) -> + let cmtidir = Fpath.(append dir cmtidir) in let id_override = Fpath.relativize ~root:Fpath.(v "_build/default") @@ -155,7 +156,7 @@ let of_dune_build dir = m "this should never be 'None': %a" Fmt.Dump.(option string) id_override); - if List.mem cmtidir c then + if Fpath.Set.mem cmtidir cset then Some (Packages.Lib.v ~libname_of_archive ~pkg_name:lib.name ~dir:(Fpath.append dir (Fpath.v lib.source_dir)) @@ -186,7 +187,7 @@ let of_dune_build dir = let local = [ { - Packages.name = "pkg"; + Packages.name = monorepo_pkg_name; version = "1.0"; libraries = libs; mlds; diff --git a/src/driver/monorepo_style.mli b/src/driver/monorepo_style.mli index 5376a9b58a..fc31ec3cf0 100644 --- a/src/driver/monorepo_style.mli +++ b/src/driver/monorepo_style.mli @@ -1 +1,3 @@ +val monorepo_pkg_name : string + val of_dune_build : Fpath.t -> Packages.t list diff --git a/src/driver/odoc_units_of.ml b/src/driver/odoc_units_of.ml index c4bd10d4d1..34c9ec7129 100644 --- a/src/driver/odoc_units_of.ml +++ b/src/driver/odoc_units_of.ml @@ -1,6 +1,9 @@ open Odoc_unit -type indices_style = Voodoo | Normal | Custom +type indices_style = + | Voodoo + | Normal + | Automatic let packages ~dirs ~extra_paths ~remap ~indices_style (pkgs : Packages.t list) : t list = @@ -273,22 +276,14 @@ let packages ~dirs ~extra_paths ~remap ~indices_style (pkgs : Packages.t list) : [ Landing_pages.src ~dirs ~pkg ~index ] else [] in + let std_units = mld_units @ asset_units @ md_units @ lib_units in match indices_style with - | Normal | Voodoo -> - List.concat - ((pkg_index () :: src_index () :: lib_units) - @ mld_units @ asset_units @ md_units) - | Custom -> - if pkg.name = "pkg" then - let others :> t list = - Landing_pages.make_custom dirs index_of - (List.find (fun p -> p.Packages.name = "pkg") pkgs) - in - others @ List.concat (mld_units @ asset_units @ md_units @ lib_units) - else - List.concat - ((pkg_index () :: src_index () :: lib_units) - @ mld_units @ asset_units @ md_units) + | Automatic when pkg.name = Monorepo_style.monorepo_pkg_name -> + let others :> t list = Landing_pages.make_custom dirs index_of (List.find (fun p -> p.Packages.name = Monorepo_style.monorepo_pkg_name) pkgs) in + others @ List.concat std_units + | Normal | Voodoo | Automatic -> + List.concat + (pkg_index () :: src_index () :: std_units) in if indices_style = Normal then let gen_indices :> t = Landing_pages.package_list ~dirs ~remap pkgs in diff --git a/src/driver/odoc_units_of.mli b/src/driver/odoc_units_of.mli index b88eeaf540..c3ada3b4ae 100644 --- a/src/driver/odoc_units_of.mli +++ b/src/driver/odoc_units_of.mli @@ -1,6 +1,6 @@ open Odoc_unit -type indices_style = Voodoo | Normal | Custom +type indices_style = Voodoo | Normal | Automatic val packages : dirs:dirs -> diff --git a/src/markdown/doc_of_md.ml b/src/markdown/doc_of_md.ml index 51ad9df953..29d98b1b99 100644 --- a/src/markdown/doc_of_md.ml +++ b/src/markdown/doc_of_md.ml @@ -280,14 +280,12 @@ let rec link_reference_to_inline_element ~locator defs l m (is, warns) = (text @ is, warns) | Some ld -> let replace_md_mdx s = - let root = - if String.ends_with ~suffix:".md" s then - String.sub s 0 (String.length s - 3) - else if String.ends_with ~suffix:".mdx" s then - String.sub s 0 (String.length s - 4) - else s - in - root ^ ".html" + let add_html x = x ^ ".html" in + if String.ends_with ~suffix:".md" s then + String.sub s 0 (String.length s - 3) |> add_html + else if String.ends_with ~suffix:".mdx" s then + String.sub s 0 (String.length s - 4) |> add_html + else s in let link = match Link_definition.dest ld with