Skip to content

Commit

Permalink
Fix generated index.mld
Browse files Browse the repository at this point in the history
Use 0 heading for first line and 1 for subsequent lines

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Mar 10, 2019
1 parent 5d3cb4f commit cc7505c
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 10 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
1.8.2 (10/03/2019)
------------------

- Fix auto-generated `index.mld`. Use correct headings for the listing. (#1925,
@rgrinberg, @aantron)

1.8.1 (08/03/2019)
------------------

Expand Down
8 changes: 5 additions & 3 deletions src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -415,13 +415,15 @@ module Gen (S : sig val sctx : SC.t end) = struct
))
|> Lib.Map.of_list_exn

let default_index entry_modules =
let default_index ~(pkg : Package.t) entry_modules =
let b = Buffer.create 512 in
Printf.bprintf b "{0 %s index}\n"
(Package.Name.to_string pkg.name);
Lib.Map.to_list entry_modules
|> List.sort ~compare:(fun (x, _) (y, _) ->
Lib_name.compare (Lib.name x) (Lib.name y))
|> List.iter ~f:(fun (lib, modules) ->
Printf.bprintf b "{2 Library %s}\n" (Lib_name.to_string (Lib.name lib));
Printf.bprintf b "{1 Library %s}\n" (Lib_name.to_string (Lib.name lib));
Buffer.add_string b (
match modules with
| [ x ] ->
Expand Down Expand Up @@ -462,7 +464,7 @@ module Gen (S : sig val sctx : SC.t end) = struct
else
let entry_modules = entry_modules ~pkg in
let gen_mld = Paths.gen_mld_dir pkg ++ "index.mld" in
add_rule (Build.write_file gen_mld (default_index entry_modules));
add_rule (Build.write_file gen_mld (default_index ~pkg entry_modules));
String.Map.add mlds "index" gen_mld in
let odocs = List.map (String.Map.values mlds) ~f:(fun mld ->
compile_mld
Expand Down
2 changes: 0 additions & 2 deletions test/blackbox-tests/test-cases/odoc-unique-mlds/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,6 @@ Duplicate mld's in the same scope
odoc _doc/_odoc/lib/root.lib2/root_lib2.odoc
odoc _doc/_html/root/Root_lib2/.dune-keep,_doc/_html/root/Root_lib2/index.html
odoc _doc/_odoc/pkg/root/page-index.odoc
File "../../../_mlds/root/index.mld", line 3, characters 0-21:
'{2': heading level should be lower than top heading level '2'.
odoc _doc/_html/root/index.html
odoc _doc/_html/root/Root_lib1/.dune-keep,_doc/_html/root/Root_lib1/index.html

Expand Down
10 changes: 5 additions & 5 deletions test/blackbox-tests/test-cases/odoc/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,6 @@
odoc _doc/_odoc/lib/foo/foo2.odoc
odoc _doc/_html/foo/Foo2/.dune-keep,_doc/_html/foo/Foo2/index.html
odoc _doc/_odoc/pkg/foo/page-index.odoc
File "../../../_mlds/foo/index.mld", line 3, characters 0-20:
'{2': heading level should be lower than top heading level '2'.
odoc _doc/_html/foo/index.html
odoc _doc/_html/foo/Foo_byte/.dune-keep,_doc/_html/foo/Foo_byte/index.html
odoc _doc/_html/foo/Foo/.dune-keep,_doc/_html/foo/Foo/index.html
Expand All @@ -45,14 +43,16 @@
</html>

$ dune build @foo-mld --display short
{2 Library foo}
{0 foo index}
{1 Library foo}
This library exposes the following toplevel modules:
{!modules:Foo Foo2}
{2 Library foo.byte}
{1 Library foo.byte}
The entry point of this library is the module:
{!module-Foo_byte}.

$ dune build @bar-mld --display short
{2 Library bar}
{0 bar index}
{1 Library bar}
The entry point of this library is the module:
{!module-Bar}.

0 comments on commit cc7505c

Please sign in to comment.