Skip to content

Commit 4e044e3

Browse files
authored
Merge pull request #11131 from rlepigre/coqdoc-header-footer
Add "coqdoc_header" and "coqdoc_footer" fields.
2 parents 59dd56f + 5fbfdd4 commit 4e044e3

File tree

15 files changed

+225
-9
lines changed

15 files changed

+225
-9
lines changed

bin/printenv.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,9 @@ let dump sctx ~dir =
2626
Dune_rules.Menhir_rules.menhir_env ~dir
2727
|> Action_builder.of_memo
2828
>>= Dune_lang.Menhir_env.dump
29-
and+ coq_dump = Dune_rules.Coq.Coq_rules.coq_env ~dir >>| Dune_rules.Coq.Coq_flags.dump
29+
and+ coq_dump =
30+
Dune_rules.Coq.Coq_rules.coq_env ~dir
31+
>>| Dune_rules.Coq.Coq_flags.dump ~dir:(Path.build dir)
3032
and+ jsoo_js_dump =
3133
let module Js_of_ocaml = Dune_lang.Js_of_ocaml in
3234
let* jsoo = Action_builder.of_memo (Dune_rules.Jsoo_rules.jsoo_env ~dir ~mode:JS) in

doc/changes/added/11131.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
- Add `coqdoc_header` and `coqdoc_footer` fields to the `coq` field of the
2+
`env` stanza, and to the `coq.theory` stanza, allowing to configure a
3+
custom header or footer respectively in the HTML output of `coqdoc`.
4+
(#11131, @rlepigre)

doc/coq.rst

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,8 @@ The Coq theory stanza is very similar in form to the OCaml
6969
(modules_flags <flags_map>)
7070
(coqdep_flags <coqdep_flags>)
7171
(coqdoc_flags <coqdoc_flags>)
72+
(coqdoc_header <coqdoc_header>)
73+
(coqdoc_footer <coqdoc_footer>)
7274
(stdlib <stdlib_included>)
7375
(mode <coq_native_mode>)
7476
(theories <coq_theories>))
@@ -146,6 +148,14 @@ The semantics of the fields are:
146148
flags are passed separately depending on which mode is target. See the section
147149
on :ref:`documentation using coqdoc<coqdoc>` for more information.
148150

151+
- ``<coqdoc_header>`` is a file passed to ``coqdoc`` using the ``--with-header``
152+
option, to configure a custom HTML header for the generated HTML pages.
153+
(Appeared in :ref:`Coq lang 0.10<coq-lang>`)
154+
155+
- ``<coqdoc_footer>`` is a file passed to ``coqdoc`` using the ``--with-footer``
156+
option, to configure a custom HTML footer for the generated HTML pages.
157+
(Appeared in :ref:`Coq lang 0.10<coq-lang>`)
158+
149159
- ``<stdlib_included>`` can either be ``yes`` or ``no``, currently defaulting to
150160
``yes``. When set to ``no``, Coq's standard library won't be visible from this
151161
theory, which means the ``Coq`` prefix won't be bound, and
@@ -212,6 +222,10 @@ Further flags can also be configured using the ``(coqdoc_flags)`` field in the
212222
is ``:standard`` which is ``--toc``. Extra flags can therefore be passed by
213223
writing ``(coqdoc_flags :standard --body-only)`` for example.
214224

225+
When building the HTML documentation, flags ``(coqdoc_header)`` and
226+
``(coqdoc_footer)`` can also be used to configure a custom HTML header or
227+
footer respectively.
228+
215229
.. _include-subdirs-coq:
216230

217231
Recursive Qualification of Modules
@@ -354,6 +368,8 @@ The Coq lang can be modified by adding the following to a
354368
355369
The supported Coq language versions (not the version of Coq) are:
356370

371+
- ``0.11``: Support for the ``(coqdoc_header ...)`` and ``(coqdoc_footer ...)``
372+
fields.
357373
- ``0.10``: Support for the ``(coqdep_flags ...)`` field.
358374
- ``0.9``: Support for per-module flags with the ``(module_flags ...)``` field.
359375
- ``0.8``: Support for composition with installed Coq theories;
@@ -849,3 +865,9 @@ with the following values for ``<coq_fields>``:
849865
- ``(coqdoc_flags <flags>)``: The default flags passed to ``coqdoc``. The default
850866
value is ``--toc``. Values set here become the ``:standard`` value in the
851867
``(coq.theory (coqdoc_flags <flags>))`` field.
868+
- ``(coqdoc_header <file>)``: The default HTML header passed to ``coqdoc`` via
869+
the ``--with-header`` flag. Values set here become the ``:standard`` value in the
870+
``(coq.theory (coqdoc_header <file>))`` field.
871+
- ``(coqdoc_footer <file>)``: The default HTML footer passed to ``coqdoc`` via
872+
the ``--with-footer`` flag. Values set here become the ``:standard`` value in the
873+
``(coq.theory (coqdoc_footer <file>))`` field.

src/dune_lang/coq_env.ml

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,18 +5,24 @@ type t =
55
{ flags : Ordered_set_lang.Unexpanded.t
66
; coqdep_flags : Ordered_set_lang.Unexpanded.t
77
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
8+
; coqdoc_header : String_with_vars.t option
9+
; coqdoc_footer : String_with_vars.t option
810
}
911

1012
let default =
1113
{ flags = Ordered_set_lang.Unexpanded.standard
1214
; coqdep_flags = Ordered_set_lang.Unexpanded.standard
1315
; coqdoc_flags = Ordered_set_lang.Unexpanded.standard
16+
; coqdoc_header = None
17+
; coqdoc_footer = None
1418
}
1519
;;
1620

1721
let flags t = t.flags
1822
let coqdep_flags t = t.coqdep_flags
1923
let coqdoc_flags t = t.coqdoc_flags
24+
let coqdoc_header t = t.coqdoc_header
25+
let coqdoc_footer t = t.coqdoc_footer
2026

2127
let decode =
2228
field
@@ -35,12 +41,22 @@ let decode =
3541
Ordered_set_lang.Unexpanded.field
3642
"coqdoc_flags"
3743
~check:(Syntax.since Stanza.syntax (3, 13))
44+
and+ coqdoc_header =
45+
field_o
46+
"coqdoc_header"
47+
(Syntax.since Stanza.syntax (3, 21) >>> String_with_vars.decode)
48+
and+ coqdoc_footer =
49+
field_o
50+
"coqdoc_footer"
51+
(Syntax.since Stanza.syntax (3, 21) >>> String_with_vars.decode)
3852
in
39-
{ flags; coqdep_flags; coqdoc_flags }))
53+
{ flags; coqdep_flags; coqdoc_flags; coqdoc_header; coqdoc_footer }))
4054
;;
4155

42-
let equal { flags; coqdep_flags; coqdoc_flags } t =
56+
let equal { flags; coqdep_flags; coqdoc_flags; coqdoc_header; coqdoc_footer } t =
4357
Ordered_set_lang.Unexpanded.equal flags t.flags
4458
&& Ordered_set_lang.Unexpanded.equal coqdep_flags t.coqdep_flags
4559
&& Ordered_set_lang.Unexpanded.equal coqdoc_flags t.coqdoc_flags
60+
&& Option.equal String_with_vars.equal coqdoc_header t.coqdoc_header
61+
&& Option.equal String_with_vars.equal coqdoc_footer t.coqdoc_footer
4662
;;

src/dune_lang/coq_env.mli

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,5 +17,11 @@ val coqdep_flags : t -> Ordered_set_lang.Unexpanded.t
1717
(** Flags for coqdoc *)
1818
val coqdoc_flags : t -> Ordered_set_lang.Unexpanded.t
1919

20+
(** Coqdoc header config. *)
21+
val coqdoc_header : t -> String_with_vars.t option
22+
23+
(** Coqdoc footer config. *)
24+
val coqdoc_footer : t -> String_with_vars.t option
25+
2026
(** Parser for env stanza. *)
2127
val decode : t Decoder.fields_parser

src/dune_rules/coq/coq_flags.ml

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,24 @@ type t =
44
{ coq_flags : string list
55
; coqdep_flags : string list
66
; coqdoc_flags : string list
7+
; coqdoc_header : Path.t option
8+
; coqdoc_footer : Path.t option
79
}
810

9-
let default = { coq_flags = [ "-q" ]; coqdep_flags = []; coqdoc_flags = [ "--toc" ] }
11+
let default =
12+
{ coq_flags = [ "-q" ]
13+
; coqdep_flags = []
14+
; coqdoc_flags = [ "--toc" ]
15+
; coqdoc_header = None
16+
; coqdoc_footer = None
17+
}
18+
;;
1019

11-
let dump { coq_flags; coqdep_flags; coqdoc_flags } =
20+
let dump ~dir { coq_flags; coqdep_flags; coqdoc_flags; coqdoc_header; coqdoc_footer } =
1221
List.map
1322
~f:Dune_lang.Encoder.(pair string (list string))
1423
[ "coq_flags", coq_flags; "coqdep_flags", coqdep_flags; "coqdoc_flags", coqdoc_flags ]
24+
@ List.map
25+
~f:Dune_lang.Encoder.(pair string (option (Dune_lang.Path.Local.encode ~dir)))
26+
[ "coqdoc_header", coqdoc_header; "coqdoc_footer", coqdoc_footer ]
1527
;;

src/dune_rules/coq/coq_flags.mli

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,12 @@
1+
open Import
2+
13
type t =
24
{ coq_flags : string list
35
; coqdep_flags : string list
46
; coqdoc_flags : string list
7+
; coqdoc_header : Path.t option
8+
; coqdoc_footer : Path.t option
59
}
610

711
val default : t
8-
val dump : t -> Dune_lang.t list
12+
val dump : dir:Path.t -> t -> Dune_lang.t list

src/dune_rules/coq/coq_rules.ml

Lines changed: 62 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -160,8 +160,24 @@ let coq_env =
160160
expander
161161
(Coq_env.coqdoc_flags config.coq)
162162
~standard
163+
and+ coqdoc_header =
164+
match Coq_env.coqdoc_header config.coq with
165+
| None ->
166+
let+ x = Action_builder.of_memo_join parent in
167+
x.coqdoc_header
168+
| Some s ->
169+
let+ path = Expander.expand_path expander s in
170+
Some path
171+
and+ coqdoc_footer =
172+
match Coq_env.coqdoc_footer config.coq with
173+
| None ->
174+
let+ x = Action_builder.of_memo_join parent in
175+
x.coqdoc_footer
176+
| Some s ->
177+
let+ path = Expander.expand_path expander s in
178+
Some path
163179
in
164-
{ Coq_flags.coq_flags; coqdep_flags; coqdoc_flags })
180+
{ Coq_flags.coq_flags; coqdep_flags; coqdoc_flags; coqdoc_header; coqdoc_footer })
165181
in
166182
fun ~dir ->
167183
(let* () = Memo.return () in
@@ -206,6 +222,24 @@ let coqdoc_flags ~dir ~stanza_coqdoc_flags ~expander =
206222
(coq_env ~dir))
207223
;;
208224

225+
let coqdoc_header ~dir ~stanza_coqdoc_header ~expander =
226+
match stanza_coqdoc_header with
227+
| None ->
228+
Action_builder.map
229+
~f:(fun { Coq_flags.coqdoc_header; _ } -> coqdoc_header)
230+
(coq_env ~dir)
231+
| Some s -> Action_builder.map ~f:Option.some (Expander.expand_path expander s)
232+
;;
233+
234+
let coqdoc_footer ~dir ~stanza_coqdoc_footer ~expander =
235+
match stanza_coqdoc_footer with
236+
| None ->
237+
Action_builder.map
238+
~f:(fun { Coq_flags.coqdoc_footer; _ } -> coqdoc_footer)
239+
(coq_env ~dir)
240+
| Some s -> Action_builder.map ~f:Option.some (Expander.expand_path expander s)
241+
;;
242+
209243
let theory_coqc_flag lib =
210244
let name = Coq_lib_name.wrapper (Coq_lib.name lib) in
211245
let dir = Coq_lib.obj_root lib in
@@ -855,8 +889,35 @@ let setup_coqdoc_rules ~sctx ~dir ~theories_deps (s : Coq_stanza.Theory.t) coq_m
855889
in
856890
Expander.expand_and_eval_set expander s.coqdoc_flags ~standard
857891
in
892+
let header =
893+
let open Action_builder.O in
894+
let* expander = Action_builder.of_memo @@ Super_context.expander sctx ~dir in
895+
let+ header =
896+
coqdoc_header ~dir ~stanza_coqdoc_header:s.coqdoc_header ~expander
897+
in
898+
match header with
899+
| None -> Command.Args.empty
900+
| Some path -> Command.Args.S [ A "--with-header"; Dep path ]
901+
in
902+
let footer =
903+
let open Action_builder.O in
904+
let* expander = Action_builder.of_memo @@ Super_context.expander sctx ~dir in
905+
let+ footer =
906+
coqdoc_footer ~dir ~stanza_coqdoc_footer:s.coqdoc_footer ~expander
907+
in
908+
match footer with
909+
| None -> Command.Args.empty
910+
| Some path -> Command.Args.S [ A "--with-footer"; Dep path ]
911+
in
912+
let when_html dyn =
913+
match mode with
914+
| `Html -> Command.Args.Dyn dyn
915+
| `Latex -> Command.Args.empty
916+
in
858917
[ Command.Args.S file_flags
859918
; Command.Args.dyn extra_coqdoc_flags
919+
; when_html header
920+
; when_html footer
860921
; A mode_flag
861922
; A "-d"
862923
; Path (Path.build doc_dir)

src/dune_rules/coq/coq_stanza.ml

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ let coq_syntax =
1515
; (0, 8), `Since (3, 8)
1616
; (0, 9), `Since (3, 16)
1717
; (0, 10), `Since (3, 17)
18+
; (0, 11), `Since (3, 21)
1819
]
1920
;;
2021

@@ -172,6 +173,8 @@ module Theory = struct
172173
; buildable : Buildable.t
173174
; coqdep_flags : Ordered_set_lang.Unexpanded.t
174175
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
176+
; coqdoc_header : String_with_vars.t option
177+
; coqdoc_footer : String_with_vars.t option
175178
}
176179

177180
let coq_public_decode =
@@ -260,6 +263,14 @@ module Theory = struct
260263
Ordered_set_lang.Unexpanded.field
261264
"coqdoc_flags"
262265
~check:(Dune_lang.Syntax.since coq_syntax (0, 8))
266+
and+ coqdoc_header =
267+
field_o
268+
"coqdoc_header"
269+
(Dune_lang.Syntax.since coq_syntax (0, 11) >>> String_with_vars.decode)
270+
and+ coqdoc_footer =
271+
field_o
272+
"coqdoc_footer"
273+
(Dune_lang.Syntax.since coq_syntax (0, 11) >>> String_with_vars.decode)
263274
in
264275
(* boot libraries cannot depend on other theories *)
265276
check_boot_has_no_deps boot buildable;
@@ -275,6 +286,8 @@ module Theory = struct
275286
; enabled_if
276287
; coqdep_flags
277288
; coqdoc_flags
289+
; coqdoc_header
290+
; coqdoc_footer
278291
})
279292
;;
280293

src/dune_rules/coq/coq_stanza.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,8 @@ module Theory : sig
3737
; buildable : Buildable.t
3838
; coqdep_flags : Ordered_set_lang.Unexpanded.t
3939
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
40+
; coqdoc_header : String_with_vars.t option
41+
; coqdoc_footer : String_with_vars.t option
4042
}
4143

4244
include Stanza.S with type t := t

0 commit comments

Comments
 (0)