Skip to content

Commit b22f49d

Browse files
authored
Merge pull request #9280 from Alizter/ps/branch/feature_coq___coqdoc_flags_in_env_stanza
feature(coq): coqdoc_flags in env stanza
2 parents 6aa9d74 + b3d2bf1 commit b22f49d

File tree

16 files changed

+174
-43
lines changed

16 files changed

+174
-43
lines changed

bin/printenv.ml

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ let dump sctx ~dir =
1313
let foreign_flags = node >>| Env_node.foreign_flags in
1414
let link_flags = node >>= Env_node.link_flags in
1515
let menhir_flags = node >>| Env_node.menhir_flags in
16-
let coq_flags = node >>= Env_node.coq in
16+
let coq_flags = node >>= Env_node.coq_flags in
1717
let js_of_ocaml = node >>= Env_node.js_of_ocaml in
1818
let open Action_builder.O in
1919
let+ o_dump =
@@ -32,9 +32,7 @@ let dump sctx ~dir =
3232
and+ menhir_dump =
3333
let+ flags = Action_builder.of_memo_join menhir_flags in
3434
[ "menhir_flags", flags ] |> List.map ~f:Dune_lang.Encoder.(pair string (list string))
35-
and+ coq_dump =
36-
let+ flags = Action_builder.of_memo_join coq_flags in
37-
[ "coq_flags", flags ] |> List.map ~f:Dune_lang.Encoder.(pair string (list string))
35+
and+ coq_dump = Action_builder.of_memo_join coq_flags >>| Dune_rules.Coq_flags.dump
3836
and+ jsoo_dump =
3937
let* jsoo = Action_builder.of_memo js_of_ocaml in
4038
Js_of_ocaml.Flags.dump jsoo.flags

doc/changes/9280_coq_env.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Add `coqdoc_flags` field to `coq` field of `env` stanza allowing the setting of
2+
workspace-wide defaults for `coqdoc_flags`. (#9280, fixes #9139, @Alizter)

doc/coq.rst

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -788,3 +788,19 @@ configuration. These are:
788788

789789
See :doc:`concepts/variables` for more information on variables supported by
790790
Dune.
791+
792+
793+
.. _coq-env:
794+
795+
Coq Environment Fields
796+
----------------------
797+
798+
The :ref:`dune-env` stanza has a ``(coq <coq_fields>)`` field with the following
799+
values for ``<coq_fields>``:
800+
801+
- ``(flags <flags>)``: The default flags passed to ``coqc``. The default value
802+
is ``-q``. Values set here become the ``:standard`` value in the
803+
``(coq.theory (flags <flags>))`` field.
804+
- ``(coqdoc_flags <flags>)``: The default flags passed to ``coqdoc``. The default
805+
value is ``--toc``. Values set here become the ``:standard`` value in the
806+
``(coq.theory (coqdoc_flags <flags>))`` field.

doc/stanzas/env.rst

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ Fields supported in ``<settings>`` are:
6262
- ``(odoc <fields>)`` allows passing options to ``odoc``. See
6363
:ref:`odoc-options` for more details.
6464

65-
- ``(coq (flags <flags>))`` allows passing options to Coq. See :ref:`coq-theory`
65+
- ``(coq <coq_fields>)`` allow passing options to Coq. See :ref:`coq-env`
6666
for more details.
6767

6868
- ``(formatting <settings>)`` allows the user to set auto-formatting in the

src/dune_rules/coq/coq_env.ml

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
open Import
2+
open Dune_lang.Decoder
3+
4+
type t =
5+
{ flags : Ordered_set_lang.Unexpanded.t
6+
; coqdoc_flags : Ordered_set_lang.Unexpanded.t
7+
}
8+
9+
let default =
10+
{ flags = Ordered_set_lang.Unexpanded.standard
11+
; coqdoc_flags = Ordered_set_lang.Unexpanded.standard
12+
}
13+
;;
14+
15+
let flags t = t.flags
16+
let coqdoc_flags t = t.coqdoc_flags
17+
18+
let decode =
19+
field
20+
"coq"
21+
~default
22+
(fields
23+
(let+ flags =
24+
Ordered_set_lang.Unexpanded.field
25+
"flags"
26+
~check:(Dune_lang.Syntax.since Stanza.syntax (2, 7))
27+
and+ coqdoc_flags =
28+
Ordered_set_lang.Unexpanded.field
29+
"coqdoc_flags"
30+
~check:(Dune_lang.Syntax.since Stanza.syntax (3, 13))
31+
in
32+
{ flags; coqdoc_flags }))
33+
;;
34+
35+
let equal { flags; coqdoc_flags } t =
36+
Ordered_set_lang.Unexpanded.equal flags t.flags
37+
&& Ordered_set_lang.Unexpanded.equal coqdoc_flags t.coqdoc_flags
38+
;;

src/dune_rules/coq/coq_env.mli

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
open Import
2+
3+
(** Environment for Coq. *)
4+
type t
5+
6+
val equal : t -> t -> bool
7+
8+
(** Default environment for Coq. *)
9+
val default : t
10+
11+
(** Flags for Coq binaries. *)
12+
val flags : t -> Ordered_set_lang.Unexpanded.t
13+
14+
(** Flags for coqdoc *)
15+
val coqdoc_flags : t -> Ordered_set_lang.Unexpanded.t
16+
17+
(** Parser for env stanza. *)
18+
val decode : t Dune_lang.Decoder.fields_parser

src/dune_rules/coq/coq_flags.ml

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
open Import
2+
3+
type t =
4+
{ coq_flags : string list
5+
; coqdoc_flags : string list
6+
}
7+
8+
let default = { coq_flags = [ "-q" ]; coqdoc_flags = [ "--toc" ] }
9+
10+
let dump { coq_flags; coqdoc_flags } =
11+
List.map
12+
~f:Dune_lang.Encoder.(pair string (list string))
13+
[ "coq_flags", coq_flags; "coqdoc_flags", coqdoc_flags ]
14+
;;

src/dune_rules/coq/coq_flags.mli

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
type t =
2+
{ coq_flags : string list
3+
; coqdoc_flags : string list
4+
}
5+
6+
val default : t
7+
val dump : t -> Dune_lang.t list

src/dune_rules/coq/coq_rules.ml

Lines changed: 23 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -126,12 +126,27 @@ let select_native_mode ~sctx ~dir (buildable : Coq_stanza.Buildable.t) =
126126
;;
127127

128128
let coq_flags ~dir ~stanza_flags ~expander ~sctx =
129-
let open Action_builder.O in
130-
let* standard =
131-
Action_builder.of_memo
132-
@@ (Super_context.env_node ~dir sctx |> Memo.bind ~f:Env_node.coq)
129+
let standard =
130+
let open Memo.O in
131+
Super_context.env_node ~dir sctx >>= Env_node.coq_flags |> Action_builder.of_memo_join
132+
in
133+
Expander.expand_and_eval_set
134+
expander
135+
stanza_flags
136+
~standard:
137+
(Action_builder.map ~f:(fun { Coq_flags.coq_flags; _ } -> coq_flags) standard)
138+
;;
139+
140+
let coqdoc_flags ~dir ~stanza_coqdoc_flags ~expander ~sctx =
141+
let standard =
142+
let open Memo.O in
143+
Super_context.env_node ~dir sctx >>= Env_node.coq_flags |> Action_builder.of_memo_join
133144
in
134-
Expander.expand_and_eval_set expander stanza_flags ~standard
145+
Expander.expand_and_eval_set
146+
expander
147+
stanza_coqdoc_flags
148+
~standard:
149+
(Action_builder.map ~f:(fun { Coq_flags.coqdoc_flags; _ } -> coqdoc_flags) standard)
135150
;;
136151

137152
let theory_coqc_flag lib =
@@ -697,9 +712,11 @@ let setup_coqdoc_rules ~sctx ~dir ~theories_deps (s : Coq_stanza.Theory.t) coq_m
697712
in
698713
let extra_coqdoc_flags =
699714
(* Standard flags for coqdoc *)
700-
let standard = Action_builder.return [ "--toc" ] in
701715
let open Action_builder.O in
702716
let* expander = Action_builder.of_memo @@ Super_context.expander sctx ~dir in
717+
let standard =
718+
coqdoc_flags ~dir ~stanza_coqdoc_flags:s.coqdoc_flags ~expander ~sctx
719+
in
703720
Expander.expand_and_eval_set expander s.coqdoc_flags ~standard
704721
in
705722
[ Command.Args.S file_flags

src/dune_rules/dune_env.ml

Lines changed: 4 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ module Stanza = struct
8282
; menhir_flags : Ordered_set_lang.Unexpanded.t option
8383
; odoc : Odoc.t
8484
; js_of_ocaml : Ordered_set_lang.Unexpanded.t Js_of_ocaml.Env.t
85-
; coq : Ordered_set_lang.Unexpanded.t
85+
; coq : Coq_env.t
8686
; format_config : Format_config.t option
8787
; error_on_use : User_message.t option
8888
; warn_on_load : User_message.t option
@@ -123,7 +123,7 @@ module Stanza = struct
123123
&& Option.equal Inline_tests.equal inline_tests t.inline_tests
124124
&& Option.equal Ordered_set_lang.Unexpanded.equal menhir_flags t.menhir_flags
125125
&& Odoc.equal odoc t.odoc
126-
&& Ordered_set_lang.Unexpanded.equal coq t.coq
126+
&& Coq_env.equal coq t.coq
127127
&& Option.equal Format_config.equal format_config t.format_config
128128
&& Js_of_ocaml.Env.equal js_of_ocaml t.js_of_ocaml
129129
&& Option.equal User_message.equal error_on_use t.error_on_use
@@ -143,7 +143,7 @@ module Stanza = struct
143143
; menhir_flags = None
144144
; odoc = Odoc.empty
145145
; js_of_ocaml = Js_of_ocaml.Env.empty
146-
; coq = Ordered_set_lang.Unexpanded.standard
146+
; coq = Coq_env.default
147147
; format_config = None
148148
; error_on_use = None
149149
; warn_on_load = None
@@ -220,15 +220,6 @@ module Stanza = struct
220220
(Dune_lang.Syntax.since Stanza.syntax (3, 0) >>> Js_of_ocaml.Env.decode)
221221
;;
222222

223-
let coq_flags = Ordered_set_lang.Unexpanded.field "flags"
224-
225-
let coq_field =
226-
field
227-
"coq"
228-
~default:Ordered_set_lang.Unexpanded.standard
229-
(Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields coq_flags)
230-
;;
231-
232223
let bin_annot =
233224
field_o "bin_annot" (Dune_lang.Syntax.since Stanza.syntax (3, 8) >>> bool)
234225
;;
@@ -248,7 +239,7 @@ module Stanza = struct
248239
and+ menhir_flags = menhir_flags ~since:(Some (2, 1))
249240
and+ odoc = odoc_field
250241
and+ js_of_ocaml = js_of_ocaml_field
251-
and+ coq = coq_field
242+
and+ coq = Coq_env.decode
252243
and+ format_config = Format_config.field ~since:(2, 8)
253244
and+ bin_annot = bin_annot in
254245
{ flags

0 commit comments

Comments
 (0)