Skip to content

Commit

Permalink
Don't build docs for implementations of virtual libraries
Browse files Browse the repository at this point in the history
Fixes #2138

Signed-off-by: Jon Ludlam <jon@recoil.org>
  • Loading branch information
jonludlam committed May 9, 2019
1 parent 9ff3c88 commit 9237488
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 1 deletion.
1 change: 1 addition & 0 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -268,6 +268,7 @@ let modes t = t.info.modes

let virtual_ t = t.info.virtual_

let implements t = t.implements
let src_dir t = t.info.src_dir
let orig_src_dir t = Option.value ~default:t.info.src_dir t.info.orig_src_dir
let obj_dir t = t.info.obj_dir
Expand Down
1 change: 1 addition & 0 deletions src/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ val main_module_name : t -> Module.Name.t option Or_exn.t
val wrapped : t -> Wrapped.t option Or_exn.t

val virtual_ : t -> Lib_modules.t Lib_info.Source.t option
val implements : t -> t Or_exn.t option

val special_builtin_support
: t -> Dune_file.Library.Special_builtin_support.t option
Expand Down
4 changes: 3 additions & 1 deletion src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -287,7 +287,9 @@ let setup_toplevel_index_rule sctx =
let libs_of_pkg sctx ~pkg =
match Package.Name.Map.find (SC.libs_by_package sctx) pkg with
| None -> Lib.Set.empty
| Some (_, libs) -> libs
| Some (_, libs) ->
Lib.Set.filter ~f:(fun lib ->
Option.is_none (Lib.implements lib)) libs

let load_all_odoc_rules_pkg sctx ~pkg =
let pkg_libs = libs_of_pkg sctx ~pkg in
Expand Down

0 comments on commit 9237488

Please sign in to comment.