Skip to content

Commit c1a6fde

Browse files
committed
Address PR review comments
1 parent 774a83b commit c1a6fde

File tree

8 files changed

+37
-30
lines changed

8 files changed

+37
-30
lines changed

README.md

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
# **[odoc](https://ocaml.github.io/odoc/) : OCaml Documentation Generator**
2-
</p>
32

43
<p align="center">
54
<a href="https://ocaml.ci.dev/github/ocaml/odoc">

src/driver/dune_style.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ let of_dune_build dir =
124124
(* When dune has a notion of doc assets, do something *);
125125
enable_warnings = false;
126126
pkg_dir;
127-
other_docs = Fpath.Set.empty;
127+
other_docs = [];
128128
config = Global_config.empty;
129129
} )
130130
| _ -> None)

src/driver/odoc.ml

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,12 +62,15 @@ let compile_md ~output_dir ~input_file:file ~parent_id =
6262
let _, f = Fpath.split_base file in
6363
Some Fpath.(output_dir // Id.to_fpath parent_id // set_ext "odoc" f)
6464
in
65-
let cmd = !odoc_md % Fpath.to_string file % "--output-dir" % p output_dir in
65+
let cmd = !odoc_md % p file % "--output-dir" % p output_dir in
6666
let cmd = cmd % "--parent-id" % Id.to_string parent_id in
6767
let desc = Printf.sprintf "Compiling Markdown %s" (Fpath.to_string file) in
68-
let lines = Cmd_outputs.submit desc cmd output_file in
69-
Cmd_outputs.(
70-
add_prefixed_output cmd compile_output (Fpath.to_string file) lines)
68+
let _lines =
69+
Cmd_outputs.submit
70+
(Some (`Compile, Fpath.to_string file))
71+
desc cmd output_file
72+
in
73+
()
7174

7275
let compile_asset ~output_dir ~name ~parent_id =
7376
let open Cmd in

src/driver/odoc_units_of.ml

Lines changed: 14 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -214,19 +214,23 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
214214
in
215215
[ unit ]
216216
in
217-
let of_md pkg (md :Fpath.t) : md unit list =
217+
let of_md pkg (md : Fpath.t) : md unit list =
218218
let ext = Fpath.get_ext md in
219219
match ext with
220220
| ".md" ->
221-
let rel_dir = doc_dir pkg in
222-
let kind = `Md in
223-
let name = md |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
224-
let lib_deps = Util.StringSet.empty in
225-
let unit = make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg ~include_dirs:Fpath.Set.empty ~lib_deps in
226-
[ unit ]
221+
let rel_dir = doc_dir pkg in
222+
let kind = `Md in
223+
let name = md |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
224+
let lib_deps = Util.StringSet.empty in
225+
let unit =
226+
make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg
227+
~include_dirs:Fpath.Set.empty ~lib_deps
228+
~enable_warnings:pkg.enable_warnings
229+
in
230+
[ unit ]
227231
| _ ->
228-
Logs.debug (fun m -> m "Skipping non-markdown doc file %a" Fpath.pp md);
229-
[]
232+
Logs.debug (fun m -> m "Skipping non-markdown doc file %a" Fpath.pp md);
233+
[]
230234
in
231235
let of_asset pkg (asset : Packages.asset) : asset unit list =
232236
let open Fpath in
@@ -248,7 +252,7 @@ let packages ~dirs ~extra_libs_paths (pkgs : Packages.t list) : t list =
248252
let lib_units :> t list list = List.map (of_lib pkg) pkg.libraries in
249253
let mld_units :> t list list = List.map (of_mld pkg) pkg.mlds in
250254
let asset_units :> t list list = List.map (of_asset pkg) pkg.assets in
251-
let md_units :> t list list = Fpath.Set.fold (fun md acc -> of_md pkg md :: acc) pkg.other_docs [] in
255+
let md_units :> t list list = List.map (of_md pkg) pkg.other_docs in
252256
let pkg_index :> t list =
253257
let has_index_page =
254258
List.exists

src/driver/packages.ml

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ type t = {
8787
mlds : mld list;
8888
assets : asset list;
8989
enable_warnings : bool;
90-
other_docs : Fpath.Set.t;
90+
other_docs : Fpath.t list;
9191
pkg_dir : Fpath.t;
9292
config : Global_config.t;
9393
}
@@ -106,9 +106,7 @@ let pp fmt t =
106106
}@]"
107107
t.name t.version (Fmt.Dump.list pp_libty) t.libraries (Fmt.Dump.list pp_mld)
108108
t.mlds (Fmt.Dump.list pp_asset) t.assets t.enable_warnings
109-
(Fmt.Dump.list Fpath.pp)
110-
(Fpath.Set.elements t.other_docs)
111-
Fpath.pp t.pkg_dir
109+
(Fmt.Dump.list Fpath.pp) t.other_docs Fpath.pp t.pkg_dir
112110

113111
let maybe_prepend_top top_dir dir =
114112
match top_dir with None -> dir | Some d -> Fpath.(d // dir)
@@ -405,6 +403,7 @@ let of_libs ~packages_dir libs =
405403
docs
406404
|> Fpath.Set.of_list
407405
in
406+
let other_docs = Fpath.Set.elements other_docs in
408407
Some
409408
{
410409
name = pkg.name;
@@ -470,8 +469,8 @@ let of_packages ~packages_dir packages =
470469
files.docs
471470
|> Fpath.Set.of_list
472471
in
473-
474472
let enable_warnings = List.mem pkg.name packages in
473+
let other_docs = Fpath.Set.elements other_docs in
475474
Util.StringMap.add pkg.name
476475
{
477476
name = pkg.name;

src/driver/packages.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ type t = {
7474
mlds : mld list;
7575
assets : asset list;
7676
enable_warnings : bool;
77-
other_docs : Fpath.Set.t;
77+
other_docs : Fpath.t list;
7878
pkg_dir : Fpath.t;
7979
config : Global_config.t;
8080
}

src/driver/voodoo.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -209,7 +209,7 @@ let process_package pkg =
209209
mlds;
210210
assets;
211211
enable_warnings = false;
212-
other_docs = Fpath.Set.empty;
212+
other_docs = [];
213213
pkg_dir = top_dir pkg;
214214
config;
215215
}

src/markdown/odoc_md.ml

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,15 +9,17 @@ let parse id input_s =
99
Lexing.{ pos_fname = input_s; pos_lnum = 1; pos_cnum = 0; pos_bol = 0 }
1010
in
1111
let str = In_channel.(with_open_bin input_s input_all) in
12-
let content, _warnings = Doc_of_md.parse_comment ~location ~text:str () in
13-
let content, () =
12+
let content, parser_warnings =
13+
Doc_of_md.parse_comment ~location ~text:str ()
14+
in
15+
let (content, ()), semantics_warnings =
1416
Semantics.ast_to_comment ~internal_tags:Expect_none ~sections_allowed:`All
15-
~tags_allowed:true
17+
~tags_allowed:false
1618
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t)
1719
content []
18-
|> Error.raise_warnings
20+
|> Error.unpack_warnings
1921
in
20-
content
22+
(content, List.map Error.t_of_parser_t parser_warnings @ semantics_warnings)
2123

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

51-
let content = parse id input_s in
53+
let content, warnings = parse id input_s in
5254
let page = mk_page input_s id content in
5355

5456
let output =
5557
Fpath.(v odoc_dir // v parent_id_str / ("page-" ^ page_name ^ ".odoc"))
5658
in
57-
Odoc_odoc.Odoc_file.save_page output ~warnings:[] page
59+
Odoc_odoc.Odoc_file.save_page output ~warnings page
5860

5961
open Cmdliner
6062

0 commit comments

Comments
 (0)