Skip to content

Commit

Permalink
Address PR review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Nov 13, 2024
1 parent 86769e5 commit fb70f25
Show file tree
Hide file tree
Showing 8 changed files with 37 additions and 30 deletions.
1 change: 0 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
# **[odoc](https://ocaml.github.io/odoc/) : OCaml Documentation Generator**
</p>

<p align="center">
<a href="https://ocaml.ci.dev/github/ocaml/odoc">
Expand Down
2 changes: 1 addition & 1 deletion src/driver/dune_style.ml
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ let of_dune_build dir =
(* When dune has a notion of doc assets, do something *);
enable_warnings = false;
pkg_dir;
other_docs = Fpath.Set.empty;
other_docs = [];
config = Global_config.empty;
} )
| _ -> None)
Expand Down
11 changes: 7 additions & 4 deletions src/driver/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,12 +62,15 @@ let compile_md ~output_dir ~input_file:file ~parent_id =
let _, f = Fpath.split_base file in
Some Fpath.(output_dir // Id.to_fpath parent_id // set_ext "odoc" f)
in
let cmd = !odoc_md % Fpath.to_string file % "--output-dir" % p output_dir in
let cmd = !odoc_md % p file % "--output-dir" % p output_dir in
let cmd = cmd % "--parent-id" % Id.to_string parent_id in
let desc = Printf.sprintf "Compiling Markdown %s" (Fpath.to_string file) in
let lines = Cmd_outputs.submit desc cmd output_file in
Cmd_outputs.(
add_prefixed_output cmd compile_output (Fpath.to_string file) lines)
let _lines =
Cmd_outputs.submit
(Some (`Compile, Fpath.to_string file))
desc cmd output_file
in
()

let compile_asset ~output_dir ~name ~parent_id =
let open Cmd in
Expand Down
24 changes: 14 additions & 10 deletions src/driver/odoc_units_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -214,19 +214,23 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
in
[ unit ]
in
let of_md pkg (md :Fpath.t) : md unit list =
let of_md pkg (md : Fpath.t) : md unit list =
let ext = Fpath.get_ext md in
match ext with
| ".md" ->
let rel_dir = doc_dir pkg in
let kind = `Md in
let name = md |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
let lib_deps = Util.StringSet.empty in
let unit = make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg ~include_dirs:Fpath.Set.empty ~lib_deps in
[ unit ]
let rel_dir = doc_dir pkg in
let kind = `Md in
let name = md |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
let lib_deps = Util.StringSet.empty in
let unit =
make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg
~include_dirs:Fpath.Set.empty ~lib_deps
~enable_warnings:pkg.enable_warnings
in
[ unit ]
| _ ->
Logs.debug (fun m -> m "Skipping non-markdown doc file %a" Fpath.pp md);
[]
Logs.debug (fun m -> m "Skipping non-markdown doc file %a" Fpath.pp md);
[]
in
let of_asset pkg (asset : Packages.asset) : asset unit list =
let open Fpath in
Expand All @@ -248,7 +252,7 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
let lib_units :> t list list = List.map (of_lib pkg) pkg.libraries in
let mld_units :> t list list = List.map (of_mld pkg) pkg.mlds in
let asset_units :> t list list = List.map (of_asset pkg) pkg.assets in
let md_units :> t list list = Fpath.Set.fold (fun md acc -> of_md pkg md :: acc) pkg.other_docs [] in
let md_units :> t list list = List.map (of_md pkg) pkg.other_docs in
let pkg_index :> t list =
let has_index_page =
List.exists
Expand Down
9 changes: 4 additions & 5 deletions src/driver/packages.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ type t = {
mlds : mld list;
assets : asset list;
enable_warnings : bool;
other_docs : Fpath.Set.t;
other_docs : Fpath.t list;
pkg_dir : Fpath.t;
config : Global_config.t;
}
Expand All @@ -106,9 +106,7 @@ let pp fmt t =
}@]"
t.name t.version (Fmt.Dump.list pp_libty) t.libraries (Fmt.Dump.list pp_mld)
t.mlds (Fmt.Dump.list pp_asset) t.assets t.enable_warnings
(Fmt.Dump.list Fpath.pp)
(Fpath.Set.elements t.other_docs)
Fpath.pp t.pkg_dir
(Fmt.Dump.list Fpath.pp) t.other_docs Fpath.pp t.pkg_dir

let maybe_prepend_top top_dir dir =
match top_dir with None -> dir | Some d -> Fpath.(d // dir)
Expand Down Expand Up @@ -405,6 +403,7 @@ let of_libs ~packages_dir libs =
docs
|> Fpath.Set.of_list
in
let other_docs = Fpath.Set.elements other_docs in
Some
{
name = pkg.name;
Expand Down Expand Up @@ -470,8 +469,8 @@ let of_packages ~packages_dir packages =
files.docs
|> Fpath.Set.of_list
in

let enable_warnings = List.mem pkg.name packages in
let other_docs = Fpath.Set.elements other_docs in
Util.StringMap.add pkg.name
{
name = pkg.name;
Expand Down
2 changes: 1 addition & 1 deletion src/driver/packages.mli
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ type t = {
mlds : mld list;
assets : asset list;
enable_warnings : bool;
other_docs : Fpath.Set.t;
other_docs : Fpath.t list;
pkg_dir : Fpath.t;
config : Global_config.t;
}
Expand Down
2 changes: 1 addition & 1 deletion src/driver/voodoo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -209,7 +209,7 @@ let process_package pkg =
mlds;
assets;
enable_warnings = false;
other_docs = Fpath.Set.empty;
other_docs = [];
pkg_dir = top_dir pkg;
config;
}
Expand Down
16 changes: 9 additions & 7 deletions src/markdown/odoc_md.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,17 @@ let parse id input_s =
Lexing.{ pos_fname = input_s; pos_lnum = 1; pos_cnum = 0; pos_bol = 0 }
in
let str = In_channel.(with_open_bin input_s input_all) in
let content, _warnings = Doc_of_md.parse_comment ~location ~text:str () in
let content, () =
let content, parser_warnings =
Doc_of_md.parse_comment ~location ~text:str ()
in
let (content, ()), semantics_warnings =
Semantics.ast_to_comment ~internal_tags:Expect_none ~sections_allowed:`All
~tags_allowed:true
~tags_allowed:false
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t)
content []
|> Error.raise_warnings
|> Error.unpack_warnings
in
content
(content, List.map Error.t_of_parser_t parser_warnings @ semantics_warnings)

let mk_page input_s id content =
(* Construct the output file representation *)
Expand Down Expand Up @@ -48,13 +50,13 @@ let run input_s parent_id_str odoc_dir =
(parent_id, Odoc_model.Names.PageName.make_std page_name)
in

let content = parse id input_s in
let content, warnings = parse id input_s in
let page = mk_page input_s id content in

let output =
Fpath.(v odoc_dir // v parent_id_str / ("page-" ^ page_name ^ ".odoc"))
in
Odoc_odoc.Odoc_file.save_page output ~warnings:[] page
Odoc_odoc.Odoc_file.save_page output ~warnings page

open Cmdliner

Expand Down

0 comments on commit fb70f25

Please sign in to comment.