Skip to content

Commit

Permalink
Merge pull request #521 from rgrinberg/build-only-public-docs
Browse files Browse the repository at this point in the history
Change @doc to only build public docs
  • Loading branch information
rgrinberg committed Feb 19, 2018
2 parents 4666359 + c067a63 commit a6e6136
Show file tree
Hide file tree
Showing 5 changed files with 30 additions and 18 deletions.
6 changes: 5 additions & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
1.0+beta18 (14/02/2018)
1.0+beta18 (next)
-----------------------

- Let the parser distinguish quoted strings from atoms. This makes
Expand Down Expand Up @@ -38,6 +38,10 @@
- Fix a regression in `external-lib-deps` introduced in 1.0+beta17
(#512, fixes #485)

- `@doc` alias will now build only documentation for public libraries. A new
`@doc-private` alias has been added to build documentation for private
libraries.

1.0+beta17 (01/02/2018)
-----------------------

Expand Down
13 changes: 7 additions & 6 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,7 @@ module Alias0 = struct
let dep t = Build.path (stamp_file t)

let is_standard = function
| "runtest" | "install" | "doc" | "lint" -> true
| "runtest" | "install" | "doc" | "doc-private" | "lint" -> true
| _ -> false

open Build.O
Expand Down Expand Up @@ -272,11 +272,12 @@ module Alias0 = struct
It is not defined in %s or any of its descendants."
name (Path.to_string_maybe_quoted src_dir)

let default = make "DEFAULT"
let runtest = make "runtest"
let install = make "install"
let doc = make "doc"
let lint = make "lint"
let default = make "DEFAULT"
let runtest = make "runtest"
let install = make "install"
let doc = make "doc"
let private_doc = make "doc-private"
let lint = make "lint"
end

module Dir_status = struct
Expand Down
11 changes: 6 additions & 5 deletions src/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -100,11 +100,12 @@ module Alias : sig

val fully_qualified_name : t -> Path.t

val default : dir:Path.t -> t
val runtest : dir:Path.t -> t
val install : dir:Path.t -> t
val doc : dir:Path.t -> t
val lint : dir:Path.t -> t
val default : dir:Path.t -> t
val runtest : dir:Path.t -> t
val install : dir:Path.t -> t
val doc : dir:Path.t -> t
val private_doc : dir:Path.t -> t
val lint : dir:Path.t -> t

(** Return the underlying stamp file *)
val stamp_file : t -> Path.t
Expand Down
16 changes: 11 additions & 5 deletions src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -200,7 +200,11 @@ let setup_library_rules sctx (lib : Library.t) ~dir ~modules ~mld_files
to_html sctx m odoc_file ~doc_dir ~odoc ~dir ~includes ~lib)
in
let doc_root = SC.Doc.root sctx in
SC.add_alias_deps sctx (Build_system.Alias.doc ~dir)
let alias =
match lib.public with
| None -> Build_system.Alias.private_doc ~dir
| Some _ -> Build_system.Alias.doc ~dir in
SC.add_alias_deps sctx alias
(css_file ~doc_dir:doc_root
:: toplevel_index ~doc_dir:doc_root
:: html_files)
Expand Down Expand Up @@ -268,15 +272,17 @@ let gen_rules sctx ~dir:_ rest =
setup_toplevel_index_rule sctx
| lib :: _ ->
let libs = SC.libs sctx in
let (lib, scope) =
let (lib, scope, alias) =
match String.rsplit2 lib ~on:'@' with
| None -> (lib, Lib_db.external_scope libs)
| Some (lib, name) -> (lib, Lib_db.find_scope_by_name_exn libs ~name)
| None ->
(lib, Lib_db.external_scope libs, "doc")
| Some (lib, name) ->
(lib, Lib_db.find_scope_by_name_exn libs ~name, "doc-private")
in
let scope =
{ With_required_by.
data = scope
; required_by = [Alias (Path.of_string "doc")]
; required_by = [Alias (Path.of_string alias)]
} in
let open Option.Infix in
Option.iter (Lib_db.Scope.find scope lib >>= Lib.src_dir)
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/multiple-private-libs/run.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
This test checks that there is no clash when two private libraries have the same name

$ $JBUILDER build -j1 --display short --root . @doc
$ $JBUILDER build -j1 --display short --root . @doc-private
odoc _doc/odoc.css
odoc _doc/test@a/page-index.odoc
ocamldep a/test.ml.d
Expand Down

0 comments on commit a6e6136

Please sign in to comment.