Skip to content

Commit

Permalink
Merge pull request #2016 from jonludlam/fix-2007
Browse files Browse the repository at this point in the history
Add package-level mlds to odoc include path
  • Loading branch information
jonludlam authored Apr 10, 2019
2 parents a72db2f + 907177a commit 56c4570
Show file tree
Hide file tree
Showing 12 changed files with 72 additions and 19 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
unreleased
----------

- Fix invocation of odoc to add previously missing include paths, impacting
mld files that are not in directories containing libraries (#2016, fixes
#2007, @jonludlam)

1.9.0 (09/04/2019)
------------------

Expand Down
33 changes: 23 additions & 10 deletions src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,10 +71,17 @@ module Dep = struct

let alias = Alias.make ".odoc-all"

let deps ctx requires =
let deps ctx pkg requires =
Build.of_result_map requires ~f:(fun libs ->
Build.deps (
List.fold_left libs ~init:Dep.Set.empty ~f:(fun acc (lib : Lib.t) ->
let init =
match pkg with
| Some p ->
Dep.Set.singleton
(Dep.alias (alias ~dir:(Paths.odocs ctx (Pkg p))))
| None -> Dep.Set.empty
in
List.fold_left libs ~init ~f:(fun acc (lib : Lib.t) ->
if Lib.is_local lib then
let dir = Paths.odocs ctx (Lib lib) in
let alias = alias ~dir in
Expand Down Expand Up @@ -156,7 +163,7 @@ let compile_mld sctx (m : Mld.t) ~includes ~doc_dir ~pkg =
]);
odoc_file

let odoc_include_flags ctx requires =
let odoc_include_flags ctx pkg requires =
Arg_spec.of_result_map requires ~f:(fun libs ->
let paths =
libs |> List.fold_left ~f:(fun paths lib ->
Expand All @@ -166,12 +173,17 @@ let odoc_include_flags ctx requires =
paths
)
) ~init:Path.Set.empty in
let paths =
match pkg with
| Some p -> Path.Set.add paths (Paths.odocs ctx (Pkg p))
| None -> paths
in
Arg_spec.S (List.concat_map (Path.Set.to_list paths)
~f:(fun dir -> [Arg_spec.A "-I"; Path dir])))

let setup_html sctx (odoc_file : odoc) ~requires =
let setup_html sctx (odoc_file : odoc) ~pkg ~requires =
let ctx = Super_context.context sctx in
let deps = Dep.deps ctx requires in
let deps = Dep.deps ctx pkg requires in
let to_remove, dune_keep =
match odoc_file.source with
| Mld -> odoc_file.html_file, []
Expand All @@ -189,7 +201,7 @@ let setup_html sctx (odoc_file : odoc) ~requires =
:: Build.run ~dir:(Paths.html_root ctx)
(odoc sctx)
[ A "html"
; odoc_include_flags ctx requires
; odoc_include_flags ctx pkg requires
; A "-o"; Path (Paths.html_root ctx)
; Dep odoc_file.odoc_input
; Hidden_targets [odoc_file.html_file]
Expand All @@ -206,8 +218,8 @@ let setup_library_odoc_rules sctx (library : Library.t) ~scope ~modules
let pkg_or_lnu = pkg_or_lnu lib in
let ctx = Super_context.context sctx in
let doc_dir = Paths.odocs ctx (Lib lib) in
let odoc_include_flags = odoc_include_flags ctx requires in
let includes = (Dep.deps ctx requires, odoc_include_flags) in
let odoc_include_flags = odoc_include_flags ctx (Lib.package lib) requires in
let includes = (Dep.deps ctx (Lib.package lib) requires, odoc_include_flags) in
let modules_and_odoc_files =
List.map (Module.Name.Map.values modules) ~f:(
compile_module sctx ~includes ~dep_graphs
Expand Down Expand Up @@ -353,7 +365,8 @@ let setup_lib_html_rules_def =
let f (sctx, lib, requires) =
let ctx = Super_context.context sctx in
let odocs = odocs ctx (Lib lib) in
List.iter odocs ~f:(setup_html sctx ~requires);
let pkg = Lib.package lib in
List.iter odocs ~f:(setup_html sctx ~pkg ~requires);
let html_files = List.map ~f:(fun o -> o.html_file) odocs in
let static_html = static_html ctx in
Build_system.Alias.add_deps (Dep.html_alias ctx (Lib lib))
Expand Down Expand Up @@ -408,7 +421,7 @@ let setup_pkg_html_rules_def =
let ctx = Super_context.context sctx in
List.iter libs ~f:(setup_lib_html_rules sctx ~requires);
let pkg_odocs = odocs ctx (Pkg pkg) in
List.iter pkg_odocs ~f:(setup_html sctx ~requires);
List.iter pkg_odocs ~f:(setup_html sctx ~pkg:(Some pkg) ~requires);
let odocs =
List.concat (
pkg_odocs
Expand Down
11 changes: 11 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -992,6 +992,16 @@
(run %{exe:cram.exe} -skip-versions 4.02.3 -test run.t)
(diff? run.t run.t.corrected)))))

(alias
(name odoc-package-mld-link)
(deps (package dune) (source_tree test-cases/odoc-package-mld-link))
(action
(chdir
test-cases/odoc-package-mld-link
(progn
(run %{exe:cram.exe} -skip-versions 4.02.3 -test run.t)
(diff? run.t run.t.corrected)))))

(alias
(name odoc-unique-mlds)
(deps (package dune) (source_tree test-cases/odoc-unique-mlds))
Expand Down Expand Up @@ -1498,6 +1508,7 @@
(alias ocamldep-multi-stanzas)
(alias ocamllex-jbuild)
(alias odoc)
(alias odoc-package-mld-link)
(alias odoc-unique-mlds)
(alias old-dune-subsystem)
(alias optional)
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/gen_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -128,6 +128,7 @@ let exclusions =
; make "coq" ~external_deps:true ~coq:true
; make "github25" ~env:("OCAMLPATH", Dune_lang.atom "./findlib-packages")
; odoc "odoc"
; odoc "odoc-package-mld-link"
; odoc "odoc-unique-mlds"
; odoc "github717-odoc-index"
; odoc "multiple-private-libs"
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/odoc-package-mld-link/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(documentation)
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(lang dune 1.5)
(name ocaml-labs)
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
{0 Big title}

Let's test a link to {{!page-otherpage}Other page} and see if it works.

Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
{0 The other page}

This is the other page. Congratulations!

10 changes: 10 additions & 0 deletions test/blackbox-tests/test-cases/odoc-package-mld-link/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
Make sure that links between mld files are resolved even when there is
no library associated with the project

This test case is based on code provided by @vphantom, ocaml/dune#2007

$ dune build _doc/_html/odoc_page_link_bug/index.html

$ grep -r xref-unresolved _build/default/_doc/_html/odoc_page_link_bug/index.html
[1]

10 changes: 5 additions & 5 deletions test/blackbox-tests/test-cases/odoc-unique-mlds/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@ Duplicate mld's in the same scope
Entering directory 'same-scope'
odoc _doc/_html/highlight.pack.js,_doc/_html/odoc.css
ocamlc lib1/.root_lib1.objs/byte/root_lib1.{cmi,cmo,cmt}
odoc _doc/_odoc/pkg/root/page-index.odoc
odoc _doc/_odoc/lib/root.lib1/root_lib1.odoc
ocamlc lib2/.root_lib2.objs/byte/root_lib2.{cmi,cmo,cmt}
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
odoc _doc/_html/root/index.html
odoc _doc/_html/root/Root_lib1/.dune-keep,_doc/_html/root/Root_lib1/index.html

Expand All @@ -17,12 +17,12 @@ Duplicate mld's in different scope
Entering directory 'diff-scope'
odoc _doc/_html/highlight.pack.js,_doc/_html/odoc.css
ocamlc scope1/.scope1.objs/byte/scope1.{cmi,cmo,cmt}
odoc _doc/_odoc/lib/scope1/scope1.odoc
odoc _doc/_html/scope1/Scope1/.dune-keep,_doc/_html/scope1/Scope1/index.html
odoc _doc/_odoc/pkg/scope1/page-index.odoc
odoc _doc/_odoc/lib/scope1/scope1.odoc
odoc _doc/_html/scope1/index.html
ocamlc scope2/.scope2.objs/byte/scope2.{cmi,cmo,cmt}
odoc _doc/_odoc/lib/scope2/scope2.odoc
odoc _doc/_html/scope2/Scope2/.dune-keep,_doc/_html/scope2/Scope2/index.html
odoc _doc/_odoc/pkg/scope2/page-index.odoc
odoc _doc/_odoc/lib/scope2/scope2.odoc
odoc _doc/_html/scope2/index.html
odoc _doc/_html/scope1/Scope1/.dune-keep,_doc/_html/scope1/Scope1/index.html
odoc _doc/_html/scope2/Scope2/.dune-keep,_doc/_html/scope2/Scope2/index.html
8 changes: 4 additions & 4 deletions test/blackbox-tests/test-cases/odoc/run.t
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
$ dune build @doc --display short
ocamldep .bar.objs/bar.ml.d
ocamlc .bar.objs/byte/bar.{cmi,cmo,cmt}
odoc _doc/_odoc/lib/bar/bar.odoc
odoc _doc/_html/bar/Bar/.dune-keep,_doc/_html/bar/Bar/index.html
odoc _doc/_odoc/pkg/bar/page-index.odoc
odoc _doc/_odoc/lib/bar/bar.odoc
odoc _doc/_html/bar/index.html
odoc _doc/_html/highlight.pack.js,_doc/_html/odoc.css
ocamldep .foo.objs/foo.ml.d
ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt}
odoc _doc/_odoc/pkg/foo/page-index.odoc
odoc _doc/_odoc/lib/foo/foo.odoc
ocamldep .foo.objs/foo2.ml.d
ocamlc .foo.objs/byte/foo2.{cmi,cmo,cmt}
Expand All @@ -19,9 +19,9 @@
ocamlc .foo_byte.objs/byte/foo_byte.{cmi,cmo,cmt}
odoc _doc/_odoc/lib/foo.byte/foo_byte.odoc
odoc _doc/_html/foo/Foo2/.dune-keep,_doc/_html/foo/Foo2/index.html
odoc _doc/_odoc/pkg/foo/page-index.odoc
odoc _doc/_html/foo/index.html
odoc _doc/_html/bar/Bar/.dune-keep,_doc/_html/bar/Bar/index.html
odoc _doc/_html/foo/Foo_byte/.dune-keep,_doc/_html/foo/Foo_byte/index.html
odoc _doc/_html/foo/index.html
odoc _doc/_html/foo/Foo/.dune-keep,_doc/_html/foo/Foo/index.html
$ dune runtest --display short
<!DOCTYPE html>
Expand Down

0 comments on commit 56c4570

Please sign in to comment.