Skip to content

Commit 63a8b6e

Browse files
authoredSep 6, 2022
Record the fact that odoc reads ODOC_SYNTAX (#6010)
This controls the syntax of the output. Closes #1117 Signed-off-by: Etienne Millon <me@emillon.org>
1 parent e58b375 commit 63a8b6e

File tree

3 files changed

+107
-63
lines changed

3 files changed

+107
-63
lines changed
 

‎CHANGES.md

+3
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,9 @@
4545
- Improve error message when parsing several licenses in `(license)` (#6114,
4646
fixes #6103, @emillon)
4747

48+
- odoc rules now about `ODOC_SYNTAX` and will re-run accordingly (#6010, fixes
49+
#1117, @emillon)
50+
4851
3.4.1 (26-07-2022)
4952
------------------
5053

‎src/dune_rules/odoc.ml

+70-63
Original file line numberDiff line numberDiff line change
@@ -186,18 +186,30 @@ end = struct
186186
let odoc_input t = t
187187
end
188188

189-
let odoc sctx =
190-
let dir = (Super_context.context sctx).build_dir in
191-
Super_context.resolve_program sctx ~dir "odoc" ~loc:None
192-
~hint:"opam install odoc"
193-
194189
let odoc_base_flags sctx build_dir =
195190
let open Memo.O in
196191
let+ conf = Super_context.odoc sctx ~dir:build_dir in
197192
match conf.Env_node.Odoc.warnings with
198193
| Fatal -> Command.Args.A "--warn-error"
199194
| Nonfatal -> S []
200195

196+
let run_odoc sctx ~dir command ~flags_for args =
197+
let build_dir = (Super_context.context sctx).build_dir in
198+
let open Memo.O in
199+
let* program =
200+
Super_context.resolve_program sctx ~dir:build_dir "odoc" ~loc:None
201+
~hint:"opam install odoc"
202+
in
203+
let+ base_flags =
204+
match flags_for with
205+
| None -> Memo.return Command.Args.empty
206+
| Some path -> odoc_base_flags sctx path
207+
in
208+
let deps = Action_builder.env_var "ODOC_SYNTAX" in
209+
let open Action_builder.With_targets.O in
210+
Action_builder.with_no_targets deps
211+
>>> Command.run ~dir program [ A command; base_flags; S args ]
212+
201213
let module_deps (m : Module.t) ~obj_dir ~(dep_graphs : Dep_graph.Ml_kind.t) =
202214
Action_builder.dyn_paths_unit
203215
(let open Action_builder.O in
@@ -216,22 +228,21 @@ let compile_module sctx ~obj_dir (m : Module.t) ~includes:(file_deps, iflags)
216228
let+ () =
217229
let* action_with_targets =
218230
let doc_dir = Path.build (Obj_dir.odoc_dir obj_dir) in
219-
let* odoc = odoc sctx in
220-
let+ odoc_base_flags = odoc_base_flags sctx odoc_file in
231+
let+ run_odoc =
232+
run_odoc sctx ~dir:doc_dir "compile" ~flags_for:(Some odoc_file)
233+
[ A "-I"
234+
; Path doc_dir
235+
; iflags
236+
; As [ "--pkg"; pkg_or_lnu ]
237+
; A "-o"
238+
; Target odoc_file
239+
; Dep (Path.build (Obj_dir.Module.cmti_file obj_dir m))
240+
]
241+
in
221242
let open Action_builder.With_targets.O in
222243
Action_builder.with_no_targets file_deps
223244
>>> Action_builder.with_no_targets (module_deps m ~obj_dir ~dep_graphs)
224-
>>> Command.run ~dir:doc_dir odoc
225-
[ A "compile"
226-
; odoc_base_flags
227-
; A "-I"
228-
; Path doc_dir
229-
; iflags
230-
; As [ "--pkg"; pkg_or_lnu ]
231-
; A "-o"
232-
; Target odoc_file
233-
; Dep (Path.build (Obj_dir.Module.cmti_file obj_dir m))
234-
]
245+
>>> run_odoc
235246
in
236247
add_rule sctx action_with_targets
237248
in
@@ -241,20 +252,17 @@ let compile_mld sctx (m : Mld.t) ~includes ~doc_dir ~pkg =
241252
let open Memo.O in
242253
let odoc_file = Mld.odoc_file m ~doc_dir in
243254
let odoc_input = Mld.odoc_input m in
244-
let* odoc = odoc sctx in
245-
let* odoc_base_flags = odoc_base_flags sctx odoc_input in
246-
let+ () =
247-
add_rule sctx
248-
(Command.run ~dir:(Path.build doc_dir) odoc
249-
[ A "compile"
250-
; odoc_base_flags
251-
; Command.Args.dyn includes
252-
; As [ "--pkg"; Package.Name.to_string pkg ]
253-
; A "-o"
254-
; Target odoc_file
255-
; Dep (Path.build odoc_input)
256-
])
255+
let* run_odoc =
256+
run_odoc sctx ~dir:(Path.build doc_dir) "compile"
257+
~flags_for:(Some odoc_input)
258+
[ Command.Args.dyn includes
259+
; As [ "--pkg"; Package.Name.to_string pkg ]
260+
; A "-o"
261+
; Target odoc_file
262+
; Dep (Path.build odoc_input)
263+
]
257264
in
265+
let+ () = add_rule sctx run_odoc in
258266
odoc_file
259267

260268
let odoc_include_flags ctx pkg requires =
@@ -281,21 +289,19 @@ let link_odoc_rules sctx (odoc_file : odoc_artefact) ~pkg ~requires =
281289
let ctx = Super_context.context sctx in
282290
let deps = Dep.deps ctx pkg requires in
283291
let open Memo.O in
284-
let* odoc = odoc sctx
285-
and* odoc_base_flags = odoc_base_flags sctx odoc_file.odoc_file in
292+
let* run_odoc =
293+
run_odoc sctx
294+
~dir:(Path.build (Paths.html_root ctx))
295+
"link" ~flags_for:(Some odoc_file.odoc_file)
296+
[ odoc_include_flags ctx pkg requires
297+
; A "-o"
298+
; Target odoc_file.odocl_file
299+
; Dep (Path.build odoc_file.odoc_file)
300+
]
301+
in
286302
add_rule sctx
287303
(let open Action_builder.With_targets.O in
288-
Action_builder.with_no_targets deps
289-
>>> Command.run
290-
~dir:(Path.build (Paths.html_root ctx))
291-
odoc
292-
[ A "link"
293-
; odoc_base_flags
294-
; odoc_include_flags ctx pkg requires
295-
; A "-o"
296-
; Target odoc_file.odocl_file
297-
; Dep (Path.build odoc_file.odoc_file)
298-
])
304+
Action_builder.with_no_targets deps >>> run_odoc)
299305

300306
let setup_library_odoc_rules cctx (local_lib : Lib.Local.t) =
301307
let open Memo.O in
@@ -339,7 +345,16 @@ let setup_html sctx (odoc_file : odoc_artefact) =
339345
(odoc_file.html_dir, [ dummy ])
340346
in
341347
let open Memo.O in
342-
let* odoc = odoc sctx in
348+
let* run_odoc =
349+
run_odoc sctx
350+
~dir:(Path.build (Paths.html_root ctx))
351+
"html-generate" ~flags_for:None
352+
[ A "-o"
353+
; Path (Path.build (Paths.html_root ctx))
354+
; Dep (Path.build odoc_file.odocl_file)
355+
; Hidden_targets [ odoc_file.html_file ]
356+
]
357+
in
343358
add_rule sctx
344359
(Action_builder.progn
345360
(Action_builder.with_no_targets
@@ -349,28 +364,20 @@ let setup_html sctx (odoc_file : odoc_artefact) =
349364
[ Action.Remove_tree to_remove
350365
; Action.Mkdir (Path.build odoc_file.html_dir)
351366
])))
352-
:: Command.run
353-
~dir:(Path.build (Paths.html_root ctx))
354-
odoc
355-
[ A "html-generate"
356-
; A "-o"
357-
; Path (Path.build (Paths.html_root ctx))
358-
; Dep (Path.build odoc_file.odocl_file)
359-
; Hidden_targets [ odoc_file.html_file ]
360-
]
361-
:: dummy))
367+
:: run_odoc :: dummy))
362368

363369
let setup_css_rule sctx =
364370
let open Memo.O in
365371
let ctx = Super_context.context sctx in
366-
let* odoc = odoc sctx in
367-
add_rule sctx
368-
(Command.run ~dir:(Path.build ctx.build_dir) odoc
369-
[ A "support-files"
370-
; A "-o"
371-
; Path (Path.build (Paths.html_root ctx))
372-
; Hidden_targets [ Paths.css_file ctx; Paths.highlight_pack_js ctx ]
373-
])
372+
let* run_odoc =
373+
run_odoc sctx ~dir:(Path.build ctx.build_dir) "support-files"
374+
~flags_for:None
375+
[ A "-o"
376+
; Path (Path.build (Paths.html_root ctx))
377+
; Hidden_targets [ Paths.css_file ctx; Paths.highlight_pack_js ctx ]
378+
]
379+
in
380+
add_rule sctx run_odoc
374381

375382
let sp = Printf.sprintf
376383

Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
The rules that call odoc know that it is going to read the ODOC_SYNTAX
2+
variable, and can rebuild as needed.
3+
4+
$ cat > dune-project << EOF
5+
> (lang dune 1.1)
6+
> (package (name l))
7+
> EOF
8+
9+
$ cat > dune << EOF
10+
> (library
11+
> (public_name l))
12+
> EOF
13+
14+
$ cat > l.ml << EOF
15+
> module type X = sig end
16+
> EOF
17+
18+
$ detect () {
19+
> if grep -q '>sig<' $1 ; then
20+
> echo it is ocaml
21+
> elif grep -q '{ ... }' $1 ; then
22+
> echo it is reason
23+
> else
24+
> echo it is unknown
25+
> fi
26+
> }
27+
28+
$ dune build @doc
29+
$ detect _build/default/_doc/_html/l/L/index.html
30+
it is ocaml
31+
32+
$ ODOC_SYNTAX=re dune build @doc
33+
$ detect _build/default/_doc/_html/l/L/index.html
34+
it is reason

0 commit comments

Comments
 (0)
Please sign in to comment.