Skip to content

Commit 07c9dbc

Browse files
committed
Fixes following PR review
1 parent bdd5ccc commit 07c9dbc

File tree

8 files changed

+15
-18
lines changed

8 files changed

+15
-18
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
@@ -122,7 +122,7 @@ let of_dune_build dir =
122122
[]
123123
(* When dune has a notion of doc assets, do something *);
124124
pkg_dir;
125-
other_docs = Fpath.Set.empty;
125+
other_docs = [];
126126
config = Global_config.empty;
127127
} )
128128
| _ -> None)

src/driver/odoc.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,7 @@ let compile_md ~output_dir ~input_file:file ~parent_id =
6161
let _, f = Fpath.split_base file in
6262
Some Fpath.(output_dir // Id.to_fpath parent_id // set_ext "odoc" f)
6363
in
64-
let cmd = !odoc_md % Fpath.to_string file % "--output-dir" % p output_dir in
64+
let cmd = !odoc_md % p file % "--output-dir" % p output_dir in
6565
let cmd = cmd % "--parent-id" % Id.to_string parent_id in
6666
let desc = Printf.sprintf "Compiling Markdown %s" (Fpath.to_string file) in
6767
let lines = Cmd_outputs.submit desc cmd output_file in

src/driver/odoc_unit.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -387,9 +387,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir ~extra_libs_paths
387387
let lib_units :> t list list = List.map (of_lib pkg) pkg.libraries in
388388
let mld_units :> t list list = List.map (of_mld pkg) pkg.mlds in
389389
let asset_units :> t list list = List.map (of_asset pkg) pkg.assets in
390-
let md_units :> t list list =
391-
Fpath.Set.fold (fun md acc -> of_md pkg md :: acc) pkg.other_docs []
392-
in
390+
let md_units :> t list list = List.map (of_md pkg) pkg.other_docs in
393391
List.concat (lib_units @ mld_units @ asset_units @ md_units)
394392
in
395393
List.concat_map of_package pkgs

src/driver/packages.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ type t = {
8585
libraries : libty list;
8686
mlds : mld list;
8787
assets : asset list;
88-
other_docs : Fpath.Set.t;
88+
other_docs : Fpath.t list;
8989
pkg_dir : Fpath.t;
9090
config : Global_config.t;
9191
}
@@ -103,8 +103,7 @@ let pp fmt t =
103103
}@]"
104104
t.name t.version (Fmt.Dump.list pp_libty) t.libraries (Fmt.Dump.list pp_mld)
105105
t.mlds (Fmt.Dump.list pp_asset) t.assets (Fmt.Dump.list Fpath.pp)
106-
(Fpath.Set.elements t.other_docs)
107-
Fpath.pp t.pkg_dir
106+
t.other_docs Fpath.pp t.pkg_dir
108107

109108
let maybe_prepend_top top_dir dir =
110109
match top_dir with None -> dir | Some d -> Fpath.(d // dir)
@@ -476,6 +475,7 @@ let of_libs ~packages_dir libs =
476475
m "%d mlds for package %s (from %d odoc_pages)"
477476
(List.length mlds) pkg.name
478477
(Fpath.Set.cardinal odoc_pages));
478+
let other_docs = Fpath.Set.elements other_docs in
479479
Some
480480
{
481481
name = pkg.name;

src/driver/packages.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ type t = {
7373
libraries : libty list;
7474
mlds : mld list;
7575
assets : asset list;
76-
other_docs : Fpath.Set.t;
76+
other_docs : Fpath.t list;
7777
pkg_dir : Fpath.t;
7878
config : Global_config.t;
7979
}

src/driver/voodoo.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,7 @@ let process_package pkg =
208208
libraries;
209209
mlds;
210210
assets;
211-
other_docs = Fpath.Set.empty;
211+
other_docs = [];
212212
pkg_dir = top_dir pkg;
213213
config;
214214
}

src/markdown/odoc_md.ml

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,15 +9,15 @@ 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 = Doc_of_md.parse_comment ~location ~text:str () in
13+
let ((content, ()), semantics_warnings) =
1414
Semantics.ast_to_comment ~internal_tags:Expect_none ~sections_allowed:`All
15-
~tags_allowed:true
15+
~tags_allowed:false
1616
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t)
1717
content []
18-
|> Error.raise_warnings
18+
|> Error.unpack_warnings
1919
in
20-
content
20+
(content, List.map Error.t_of_parser_t parser_warnings @ semantics_warnings)
2121

2222
let mk_page input_s id content =
2323
(* Construct the output file representation *)
@@ -48,13 +48,13 @@ let run input_s parent_id_str odoc_dir =
4848
(parent_id, Odoc_model.Names.PageName.make_std page_name)
4949
in
5050

51-
let content = parse id input_s in
51+
let content, warnings = parse id input_s in
5252
let page = mk_page input_s id content in
5353

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

5959
open Cmdliner
6060

0 commit comments

Comments
 (0)