Skip to content

Commit

Permalink
Record the fact that odoc reads ODOC_SYNTAX
Browse files Browse the repository at this point in the history
This controls the syntax of the output.

Closes #1117

Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Sep 6, 2022
1 parent e58b375 commit a9d0791
Show file tree
Hide file tree
Showing 3 changed files with 107 additions and 63 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,9 @@
- Improve error message when parsing several licenses in `(license)` (#6114,
fixes #6103, @emillon)

- odoc rules now about `ODOC_SYNTAX` and will re-run accordingly (#6010, fixes
#1117, @emillon)

3.4.1 (26-07-2022)
------------------

Expand Down
133 changes: 70 additions & 63 deletions src/dune_rules/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -186,18 +186,30 @@ end = struct
let odoc_input t = t
end

let odoc sctx =
let dir = (Super_context.context sctx).build_dir in
Super_context.resolve_program sctx ~dir "odoc" ~loc:None
~hint:"opam install odoc"

let odoc_base_flags sctx build_dir =
let open Memo.O in
let+ conf = Super_context.odoc sctx ~dir:build_dir in
match conf.Env_node.Odoc.warnings with
| Fatal -> Command.Args.A "--warn-error"
| Nonfatal -> S []

let run_odoc sctx ~dir command ~flags_for args =
let build_dir = (Super_context.context sctx).build_dir in
let open Memo.O in
let* program =
Super_context.resolve_program sctx ~dir:build_dir "odoc" ~loc:None
~hint:"opam install odoc"
in
let+ base_flags =
match flags_for with
| None -> Memo.return Command.Args.empty
| Some path -> odoc_base_flags sctx path
in
let deps = Action_builder.env_var "ODOC_SYNTAX" in
let open Action_builder.With_targets.O in
Action_builder.with_no_targets deps
>>> Command.run ~dir program [ A command; base_flags; S args ]

let module_deps (m : Module.t) ~obj_dir ~(dep_graphs : Dep_graph.Ml_kind.t) =
Action_builder.dyn_paths_unit
(let open Action_builder.O in
Expand All @@ -216,22 +228,21 @@ let compile_module sctx ~obj_dir (m : Module.t) ~includes:(file_deps, iflags)
let+ () =
let* action_with_targets =
let doc_dir = Path.build (Obj_dir.odoc_dir obj_dir) in
let* odoc = odoc sctx in
let+ odoc_base_flags = odoc_base_flags sctx odoc_file in
let+ run_odoc =
run_odoc sctx ~dir:doc_dir "compile" ~flags_for:(Some odoc_file)
[ A "-I"
; Path doc_dir
; iflags
; As [ "--pkg"; pkg_or_lnu ]
; A "-o"
; Target odoc_file
; Dep (Path.build (Obj_dir.Module.cmti_file obj_dir m))
]
in
let open Action_builder.With_targets.O in
Action_builder.with_no_targets file_deps
>>> Action_builder.with_no_targets (module_deps m ~obj_dir ~dep_graphs)
>>> Command.run ~dir:doc_dir odoc
[ A "compile"
; odoc_base_flags
; A "-I"
; Path doc_dir
; iflags
; As [ "--pkg"; pkg_or_lnu ]
; A "-o"
; Target odoc_file
; Dep (Path.build (Obj_dir.Module.cmti_file obj_dir m))
]
>>> run_odoc
in
add_rule sctx action_with_targets
in
Expand All @@ -241,20 +252,17 @@ let compile_mld sctx (m : Mld.t) ~includes ~doc_dir ~pkg =
let open Memo.O in
let odoc_file = Mld.odoc_file m ~doc_dir in
let odoc_input = Mld.odoc_input m in
let* odoc = odoc sctx in
let* odoc_base_flags = odoc_base_flags sctx odoc_input in
let+ () =
add_rule sctx
(Command.run ~dir:(Path.build doc_dir) odoc
[ A "compile"
; odoc_base_flags
; Command.Args.dyn includes
; As [ "--pkg"; Package.Name.to_string pkg ]
; A "-o"
; Target odoc_file
; Dep (Path.build odoc_input)
])
let* run_odoc =
run_odoc sctx ~dir:(Path.build doc_dir) "compile"
~flags_for:(Some odoc_input)
[ Command.Args.dyn includes
; As [ "--pkg"; Package.Name.to_string pkg ]
; A "-o"
; Target odoc_file
; Dep (Path.build odoc_input)
]
in
let+ () = add_rule sctx run_odoc in
odoc_file

let odoc_include_flags ctx pkg requires =
Expand All @@ -281,21 +289,19 @@ let link_odoc_rules sctx (odoc_file : odoc_artefact) ~pkg ~requires =
let ctx = Super_context.context sctx in
let deps = Dep.deps ctx pkg requires in
let open Memo.O in
let* odoc = odoc sctx
and* odoc_base_flags = odoc_base_flags sctx odoc_file.odoc_file in
let* run_odoc =
run_odoc sctx
~dir:(Path.build (Paths.html_root ctx))
"link" ~flags_for:(Some odoc_file.odoc_file)
[ odoc_include_flags ctx pkg requires
; A "-o"
; Target odoc_file.odocl_file
; Dep (Path.build odoc_file.odoc_file)
]
in
add_rule sctx
(let open Action_builder.With_targets.O in
Action_builder.with_no_targets deps
>>> Command.run
~dir:(Path.build (Paths.html_root ctx))
odoc
[ A "link"
; odoc_base_flags
; odoc_include_flags ctx pkg requires
; A "-o"
; Target odoc_file.odocl_file
; Dep (Path.build odoc_file.odoc_file)
])
Action_builder.with_no_targets deps >>> run_odoc)

let setup_library_odoc_rules cctx (local_lib : Lib.Local.t) =
let open Memo.O in
Expand Down Expand Up @@ -339,7 +345,16 @@ let setup_html sctx (odoc_file : odoc_artefact) =
(odoc_file.html_dir, [ dummy ])
in
let open Memo.O in
let* odoc = odoc sctx in
let* run_odoc =
run_odoc sctx
~dir:(Path.build (Paths.html_root ctx))
"html-generate" ~flags_for:None
[ A "-o"
; Path (Path.build (Paths.html_root ctx))
; Dep (Path.build odoc_file.odocl_file)
; Hidden_targets [ odoc_file.html_file ]
]
in
add_rule sctx
(Action_builder.progn
(Action_builder.with_no_targets
Expand All @@ -349,28 +364,20 @@ let setup_html sctx (odoc_file : odoc_artefact) =
[ Action.Remove_tree to_remove
; Action.Mkdir (Path.build odoc_file.html_dir)
])))
:: Command.run
~dir:(Path.build (Paths.html_root ctx))
odoc
[ A "html-generate"
; A "-o"
; Path (Path.build (Paths.html_root ctx))
; Dep (Path.build odoc_file.odocl_file)
; Hidden_targets [ odoc_file.html_file ]
]
:: dummy))
:: run_odoc :: dummy))

let setup_css_rule sctx =
let open Memo.O in
let ctx = Super_context.context sctx in
let* odoc = odoc sctx in
add_rule sctx
(Command.run ~dir:(Path.build ctx.build_dir) odoc
[ A "support-files"
; A "-o"
; Path (Path.build (Paths.html_root ctx))
; Hidden_targets [ Paths.css_file ctx; Paths.highlight_pack_js ctx ]
])
let* run_odoc =
run_odoc sctx ~dir:(Path.build ctx.build_dir) "support-files"
~flags_for:None
[ A "-o"
; Path (Path.build (Paths.html_root ctx))
; Hidden_targets [ Paths.css_file ctx; Paths.highlight_pack_js ctx ]
]
in
add_rule sctx run_odoc

let sp = Printf.sprintf

Expand Down
34 changes: 34 additions & 0 deletions test/blackbox-tests/test-cases/odoc/github1117.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
The rules that call odoc know that it is going to read the ODOC_SYNTAX
variable, and can rebuild as needed.

$ cat > dune-project << EOF
> (lang dune 1.1)
> (package (name l))
> EOF

$ cat > dune << EOF
> (library
> (public_name l))
> EOF

$ cat > l.ml << EOF
> module type X = sig end
> EOF

$ detect () {
> if grep -q '>sig<' $1 ; then
> echo it is ocaml
> elif grep -q '{ ... }' $1 ; then
> echo it is reason
> else
> echo it is unknown
> fi
> }

$ dune build @doc
$ detect _build/default/_doc/_html/l/L/index.html
it is ocaml

$ ODOC_SYNTAX=re dune build @doc
$ detect _build/default/_doc/_html/l/L/index.html
it is reason

0 comments on commit a9d0791

Please sign in to comment.