Skip to content

Commit 38c2300

Browse files
authored
Merge pull request #11094 from rlepigre/coqdep-flags
Add support for `coqdep` flags.
2 parents f7af2d0 + b2c3d93 commit 38c2300

File tree

19 files changed

+120
-9
lines changed

19 files changed

+120
-9
lines changed

doc/changes/11094.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Add a `coqdep_flags` field to the `coq` field of the `env` stanza, and to the `coq.theory` stanza, allowing to configure `coqdep` flags.
2+
(#11094, @rlepigre)

doc/coq.rst

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,7 @@ The Coq theory stanza is very similar in form to the OCaml
6767
(plugins <ocaml_plugins>)
6868
(flags <coq_flags>)
6969
(modules_flags <flags_map>)
70+
(coqdep_flags <coqdep_flags>)
7071
(coqdoc_flags <coqdoc_flags>)
7172
(stdlib <stdlib_included>)
7273
(mode <coq_native_mode>)
@@ -134,6 +135,12 @@ The semantics of the fields are:
134135
...)`` as to propagate the default flags. (Appeared in :ref:`Coq
135136
lang 0.9<coq-lang>`)
136137

138+
- ``<coqdep_flags>`` are extra user-configurable flags passed to ``coqdep``. The
139+
default value for ``:standard`` is empty. This field exists for transient
140+
use-cases, in particular disabling ``coqdep`` warnings, but it should not be
141+
used in normal operations. (Appeared in :ref:`Coq lang 0.10<coq-lang>`)
142+
143+
137144
- ``<coqdoc_flags>`` are extra user-configurable flags passed to ``coqdoc``. The
138145
default value for ``:standard`` is ``--toc``. The ``--html`` or ``--latex``
139146
flags are passed separately depending on which mode is target. See the section
@@ -347,6 +354,7 @@ The Coq lang can be modified by adding the following to a
347354
348355
The supported Coq language versions (not the version of Coq) are:
349356

357+
- ``0.10``: Support for the ``(coqdep_flags ...)`` field.
350358
- ``0.9``: Support for per-module flags with the ``(module_flags ...)``` field.
351359
- ``0.8``: Support for composition with installed Coq theories;
352360
support for ``vos`` builds.
@@ -833,6 +841,11 @@ with the following values for ``<coq_fields>``:
833841
- ``(flags <flags>)``: The default flags passed to ``coqc``. The default value
834842
is ``-q``. Values set here become the ``:standard`` value in the
835843
``(coq.theory (flags <flags>))`` field.
844+
- ``(coqdep_flags <flags>)``: The default flags passed to ``coqdep``. The default
845+
value is empty. Values set here become the ``:standard`` value in the
846+
``(coq.theory (coqdep_flags <flags>))`` field. As noted in the documentation
847+
of the ``(coq.theory (coqdep_flags <flags>))`` field, changing the ``coqdep``
848+
flags is discouraged.
836849
- ``(coqdoc_flags <flags>)``: The default flags passed to ``coqdoc``. The default
837850
value is ``--toc``. Values set here become the ``:standard`` value in the
838851
``(coq.theory (coqdoc_flags <flags>))`` field.

src/dune_rules/coq/coq_env.ml

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,16 +3,19 @@ open Dune_lang.Decoder
33

44
type t =
55
{ flags : Ordered_set_lang.Unexpanded.t
6+
; coqdep_flags : Ordered_set_lang.Unexpanded.t
67
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
78
}
89

910
let default =
1011
{ flags = Ordered_set_lang.Unexpanded.standard
12+
; coqdep_flags = Ordered_set_lang.Unexpanded.standard
1113
; coqdoc_flags = Ordered_set_lang.Unexpanded.standard
1214
}
1315
;;
1416

1517
let flags t = t.flags
18+
let coqdep_flags t = t.coqdep_flags
1619
let coqdoc_flags t = t.coqdoc_flags
1720

1821
let decode =
@@ -24,15 +27,20 @@ let decode =
2427
Ordered_set_lang.Unexpanded.field
2528
"flags"
2629
~check:(Dune_lang.Syntax.since Stanza.syntax (2, 7))
30+
and+ coqdep_flags =
31+
Ordered_set_lang.Unexpanded.field
32+
"coqdep_flags"
33+
~check:(Dune_lang.Syntax.since Stanza.syntax (3, 17))
2734
and+ coqdoc_flags =
2835
Ordered_set_lang.Unexpanded.field
2936
"coqdoc_flags"
3037
~check:(Dune_lang.Syntax.since Stanza.syntax (3, 13))
3138
in
32-
{ flags; coqdoc_flags }))
39+
{ flags; coqdep_flags; coqdoc_flags }))
3340
;;
3441

35-
let equal { flags; coqdoc_flags } t =
42+
let equal { flags; coqdep_flags; coqdoc_flags } t =
3643
Ordered_set_lang.Unexpanded.equal flags t.flags
44+
&& Ordered_set_lang.Unexpanded.equal coqdep_flags t.coqdep_flags
3745
&& Ordered_set_lang.Unexpanded.equal coqdoc_flags t.coqdoc_flags
3846
;;

src/dune_rules/coq/coq_env.mli

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,9 @@ val default : t
1111
(** Flags for Coq binaries. *)
1212
val flags : t -> Ordered_set_lang.Unexpanded.t
1313

14+
(** Flags for coqdep *)
15+
val coqdep_flags : t -> Ordered_set_lang.Unexpanded.t
16+
1417
(** Flags for coqdoc *)
1518
val coqdoc_flags : t -> Ordered_set_lang.Unexpanded.t
1619

src/dune_rules/coq/coq_flags.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,14 @@ open Import
22

33
type t =
44
{ coq_flags : string list
5+
; coqdep_flags : string list
56
; coqdoc_flags : string list
67
}
78

8-
let default = { coq_flags = [ "-q" ]; coqdoc_flags = [ "--toc" ] }
9+
let default = { coq_flags = [ "-q" ]; coqdep_flags = []; coqdoc_flags = [ "--toc" ] }
910

10-
let dump { coq_flags; coqdoc_flags } =
11+
let dump { coq_flags; coqdep_flags; coqdoc_flags } =
1112
List.map
1213
~f:Dune_lang.Encoder.(pair string (list string))
13-
[ "coq_flags", coq_flags; "coqdoc_flags", coqdoc_flags ]
14+
[ "coq_flags", coq_flags; "coqdep_flags", coqdep_flags; "coqdoc_flags", coqdoc_flags ]
1415
;;

src/dune_rules/coq/coq_flags.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
type t =
22
{ coq_flags : string list
3+
; coqdep_flags : string list
34
; coqdoc_flags : string list
45
}
56

src/dune_rules/coq/coq_rules.ml

Lines changed: 32 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -141,6 +141,15 @@ let coq_env =
141141
x.coq_flags
142142
in
143143
Expander.expand_and_eval_set expander (Coq_env.flags config.coq) ~standard
144+
and+ coqdep_flags =
145+
let standard =
146+
let+ x = Action_builder.of_memo_join parent in
147+
x.coqdep_flags
148+
in
149+
Expander.expand_and_eval_set
150+
expander
151+
(Coq_env.coqdep_flags config.coq)
152+
~standard
144153
and+ coqdoc_flags =
145154
let standard =
146155
let+ x = Action_builder.of_memo_join parent in
@@ -151,7 +160,7 @@ let coq_env =
151160
(Coq_env.coqdoc_flags config.coq)
152161
~standard
153162
in
154-
{ Coq_flags.coq_flags; coqdoc_flags })
163+
{ Coq_flags.coq_flags; coqdep_flags; coqdoc_flags })
155164
in
156165
fun ~dir ->
157166
(let* () = Memo.return () in
@@ -176,6 +185,16 @@ let coq_flags ~dir ~stanza_flags ~per_file_flags ~expander =
176185
Expander.expand_and_eval_set expander flags_to_expand ~standard
177186
;;
178187

188+
let coqdep_flags ~dir ~stanza_coqdep_flags ~expander =
189+
Expander.expand_and_eval_set
190+
expander
191+
stanza_coqdep_flags
192+
~standard:
193+
(Action_builder.map
194+
~f:(fun { Coq_flags.coqdep_flags; _ } -> coqdep_flags)
195+
(coq_env ~dir))
196+
;;
197+
179198
let coqdoc_flags ~dir ~stanza_coqdoc_flags ~expander =
180199
Expander.expand_and_eval_set
181200
expander
@@ -474,6 +493,7 @@ let setup_coqdep_for_theory_rule
474493
~ml_flags
475494
~mlpack_rule
476495
~boot_flags
496+
~stanza_coqdep_flags
477497
coq_modules
478498
=
479499
(* coqdep needs the full source + plugin's mlpack to be present :( *)
@@ -484,7 +504,15 @@ let setup_coqdep_for_theory_rule
484504
; Deps sources
485505
]
486506
in
487-
let coqdep_flags = Command.Args.Dyn boot_flags :: file_flags in
507+
let extra_coqdep_flags =
508+
(* Standard flags for coqdep *)
509+
let open Action_builder.O in
510+
let* expander = Action_builder.of_memo @@ Super_context.expander sctx ~dir in
511+
coqdep_flags ~dir ~stanza_coqdep_flags ~expander
512+
in
513+
let coqdep_flags =
514+
Command.Args.Dyn boot_flags :: Command.Args.dyn extra_coqdep_flags :: file_flags
515+
in
488516
let stdout_to = dep_theory_file ~dir ~wrapper_name in
489517
let* coqdep =
490518
Super_context.resolve_program_memo
@@ -968,6 +996,7 @@ let setup_theory_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Theory.t) =
968996
~ml_flags
969997
~mlpack_rule
970998
~boot_flags
999+
~stanza_coqdep_flags:s.coqdep_flags
9711000
coq_modules
9721001
>>> Memo.parallel_iter
9731002
coq_modules
@@ -1189,6 +1218,7 @@ let setup_extraction_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Extraction.t
11891218
~ml_flags
11901219
~mlpack_rule
11911220
~boot_flags
1221+
~stanza_coqdep_flags:Ordered_set_lang.Unexpanded.standard
11921222
[ coq_module ]
11931223
>>> setup_coqc_rule
11941224
~scope

src/dune_rules/coq/coq_stanza.ml

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ let coq_syntax =
1414
; (0, 7), `Since (3, 7)
1515
; (0, 8), `Since (3, 8)
1616
; (0, 9), `Since (3, 16)
17+
; (0, 10), `Since (3, 17)
1718
]
1819
;;
1920

@@ -169,6 +170,7 @@ module Theory = struct
169170
; boot : bool
170171
; enabled_if : Blang.t
171172
; buildable : Buildable.t
173+
; coqdep_flags : Ordered_set_lang.Unexpanded.t
172174
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
173175
}
174176

@@ -249,6 +251,10 @@ module Theory = struct
249251
(Dune_lang.Syntax.since coq_syntax (0, 9) >>> Per_file.decode)
250252
and+ enabled_if = Enabled_if.decode ~allowed_vars:Any ~since:None ()
251253
and+ buildable = Buildable.decode
254+
and+ coqdep_flags =
255+
Ordered_set_lang.Unexpanded.field
256+
"coqdep_flags"
257+
~check:(Dune_lang.Syntax.since coq_syntax (0, 10))
252258
and+ coqdoc_flags =
253259
Ordered_set_lang.Unexpanded.field
254260
"coqdoc_flags"
@@ -266,6 +272,7 @@ module Theory = struct
266272
; boot
267273
; buildable
268274
; enabled_if
275+
; coqdep_flags
269276
; coqdoc_flags
270277
})
271278
;;

src/dune_rules/coq/coq_stanza.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ module Theory : sig
3535
; boot : bool
3636
; enabled_if : Blang.t
3737
; buildable : Buildable.t
38+
; coqdep_flags : Ordered_set_lang.Unexpanded.t
3839
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
3940
}
4041

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
(lang dune 3.17)
2+
(using coq 0.10)

0 commit comments

Comments
 (0)