Skip to content

Commit 7bfd201

Browse files
authored
Merge pull request #11752 from rlepigre/coqproject
Generate "_CoqProject" files for Coq theories
2 parents ae776d3 + 9d5ada5 commit 7bfd201

File tree

8 files changed

+255
-16
lines changed

8 files changed

+255
-16
lines changed

doc/changes/added/11752.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
- Support for generating `_CoqProject` files for `coq.theory` stanzas.
2+
(#11752, @rlepigre)

doc/coq.rst

Lines changed: 13 additions & 4 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+
(generate_project_file)
7071
(coqdep_flags <coqdep_flags>)
7172
(coqdoc_flags <coqdoc_flags>)
7273
(coqdoc_header <coqdoc_header>)
@@ -190,8 +191,16 @@ The semantics of the fields are:
190191
- If the ``(mode vos)`` field is present, only Coq compiled interface files
191192
``.vos`` will be produced for the theory. This is mainly useful in conjunction
192193
with ``dune coq top``, since this makes the compilation of dependencies much
193-
faster, at the cost of skipping proof checking. (Appeared in :ref:`Coq lang
194-
0.8<coq-lang>`).
194+
faster, at the cost of skipping proof checking.
195+
(Appeared in :ref:`Coq lang 0.8<coq-lang>`)
196+
197+
- If the ``(generate_project_file)`` is present, a ``_CoqProject`` file is
198+
generated in the Coq theory's directory (it is promoted to the source tree).
199+
This file should be suitable for editor compatibility, and it provides an
200+
alternative to using ``dune coq top``. It is however limited in two ways: it
201+
is incompatible with the ``(modules_flags ...)`` field, and it cannot be
202+
used for two Coq theories declared in the same directory.
203+
(Appeared in :ref:`Coq lang 0.11<coq-lang>`)
195204

196205
Coq Dependencies
197206
~~~~~~~~~~~~~~~~
@@ -369,9 +378,9 @@ The Coq lang can be modified by adding the following to a
369378
The supported Coq language versions (not the version of Coq) are:
370379

371380
- ``0.11``: Support for the ``(coqdoc_header ...)`` and ``(coqdoc_footer ...)``
372-
fields.
381+
fields, and for ``_CoqProject`` file generation.
373382
- ``0.10``: Support for the ``(coqdep_flags ...)`` field.
374-
- ``0.9``: Support for per-module flags with the ``(module_flags ...)``` field.
383+
- ``0.9``: Support for per-module flags with the ``(modules_flags ...)``` field.
375384
- ``0.8``: Support for composition with installed Coq theories;
376385
support for ``vos`` builds.
377386

src/dune_rules/coq/coq_rules.ml

Lines changed: 153 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -520,6 +520,131 @@ let dep_theory_file ~dir ~wrapper_name =
520520
|> Path.Build.set_extension ~ext:".theory.d"
521521
;;
522522

523+
let theory_coq_args
524+
~sctx
525+
~dir
526+
~wrapper_name
527+
~boot_flags
528+
~stanza_flags
529+
~ml_flags
530+
~theories_deps
531+
~theory_dirs
532+
=
533+
let+ coq_stanza_flags =
534+
let+ expander = Super_context.expander sctx ~dir in
535+
let coq_flags =
536+
let coq_flags = coq_flags ~expander ~dir ~stanza_flags ~per_file_flags:None in
537+
(* By default we have the -q flag. We don't want to pass this to coqtop to
538+
allow users to load their .coqrc files for interactive development.
539+
Therefore we manually scrub the -q setting when passing arguments to
540+
coqtop. *)
541+
let rec remove_q = function
542+
| "-q" :: l -> remove_q l
543+
| x :: l -> x :: remove_q l
544+
| [] -> []
545+
in
546+
let open Action_builder.O in
547+
coq_flags >>| remove_q
548+
in
549+
Command.Args.dyn coq_flags (* stanza flags *)
550+
in
551+
let coq_native_flags =
552+
let mode = Coq_mode.VoOnly in
553+
coqc_native_flags ~sctx ~dir ~theories_deps ~theory_dirs ~mode
554+
in
555+
let file_flags = coqc_file_flags ~dir ~theories_deps ~wrapper_name ~ml_flags in
556+
[ coq_stanza_flags; coq_native_flags; Dyn boot_flags; S file_flags ]
557+
;;
558+
559+
let setup_coqproject_for_theory_rule
560+
~scope
561+
~sctx
562+
~dir
563+
~loc
564+
~theories_deps
565+
~wrapper_name
566+
~use_stdlib
567+
~ml_flags
568+
~coq_lang_version
569+
~stanza_flags
570+
~theory_dirs
571+
coq_modules
572+
=
573+
(* Process coqdep and generate rules *)
574+
let boot_type =
575+
match coq_modules with
576+
| [] -> Resolve.Memo.return Bootstrap.empty
577+
| m :: _ -> Bootstrap.make ~scope ~use_stdlib ~wrapper_name ~coq_lang_version m
578+
in
579+
let boot_flags = Resolve.Memo.read boot_type |> Action_builder.map ~f:Bootstrap.flags in
580+
let* args =
581+
theory_coq_args
582+
~sctx
583+
~dir
584+
~wrapper_name
585+
~boot_flags
586+
~stanza_flags
587+
~ml_flags
588+
~theories_deps
589+
~theory_dirs
590+
in
591+
let contents : string With_targets.t =
592+
let open With_targets.O in
593+
let dir = Path.build dir in
594+
let+ args_bld = Command.expand ~dir (Command.Args.S args)
595+
and+ args_src =
596+
let dir = Path.source (Path.drop_build_context_exn dir) in
597+
Command.expand ~dir (Command.Args.S args)
598+
in
599+
let contents = Buffer.create 73 in
600+
let rec add_args args_bld args_src =
601+
match args_bld, args_src with
602+
| (("-R" | "-Q") as o) :: db :: mb :: args_bld, _ :: ds :: ms :: args_src ->
603+
Buffer.add_string contents o;
604+
Buffer.add_char contents ' ';
605+
Buffer.add_string contents db;
606+
Buffer.add_char contents ' ';
607+
Buffer.add_string contents mb;
608+
Buffer.add_char contents '\n';
609+
if db <> ds
610+
then (
611+
Buffer.add_string contents o;
612+
Buffer.add_char contents ' ';
613+
Buffer.add_string contents ds;
614+
Buffer.add_char contents ' ';
615+
Buffer.add_string contents ms;
616+
Buffer.add_char contents '\n');
617+
add_args args_bld args_src
618+
| "-I" :: _ :: args_bld, "-I" :: d :: args_src ->
619+
Buffer.add_string contents "-I ";
620+
Buffer.add_string contents d;
621+
Buffer.add_char contents '\n';
622+
add_args args_bld args_src
623+
| o :: args_bld, _ :: args_src ->
624+
Buffer.add_string contents "-arg ";
625+
Buffer.add_string contents o;
626+
Buffer.add_char contents '\n';
627+
add_args args_bld args_src
628+
| [], [] -> ()
629+
| _, _ -> assert false
630+
in
631+
add_args args_bld args_src;
632+
Buffer.contents contents
633+
in
634+
let mode =
635+
let open Rule.Promote in
636+
let lifetime = Lifetime.Until_clean in
637+
Rule.Mode.Promote { lifetime; into = None; only = None }
638+
in
639+
let coqproject = Path.Build.relative dir "_CoqProject" in
640+
Super_context.add_rule
641+
~mode
642+
~loc
643+
sctx
644+
~dir
645+
(Action_builder.write_file_dyn coqproject contents.build)
646+
;;
647+
523648
let setup_coqdep_for_theory_rule
524649
~sctx
525650
~dir
@@ -1050,18 +1175,34 @@ let setup_theory_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Theory.t) =
10501175
| m :: _ -> Bootstrap.make ~scope ~use_stdlib ~wrapper_name ~coq_lang_version m
10511176
in
10521177
let boot_flags = Resolve.Memo.read boot_type |> Action_builder.map ~f:Bootstrap.flags in
1053-
setup_coqdep_for_theory_rule
1054-
~sctx
1055-
~dir
1056-
~loc
1057-
~theories_deps
1058-
~wrapper_name
1059-
~source_rule
1060-
~ml_flags
1061-
~mlpack_rule
1062-
~boot_flags
1063-
~stanza_coqdep_flags:s.coqdep_flags
1064-
coq_modules
1178+
(if not (snd s.generate_project_file)
1179+
then Memo.return ()
1180+
else
1181+
setup_coqproject_for_theory_rule
1182+
~scope
1183+
~sctx
1184+
~dir
1185+
~loc
1186+
~theories_deps
1187+
~wrapper_name
1188+
~use_stdlib
1189+
~ml_flags
1190+
~coq_lang_version
1191+
~stanza_flags
1192+
~theory_dirs
1193+
coq_modules)
1194+
>>> setup_coqdep_for_theory_rule
1195+
~sctx
1196+
~dir
1197+
~loc
1198+
~theories_deps
1199+
~wrapper_name
1200+
~source_rule
1201+
~ml_flags
1202+
~mlpack_rule
1203+
~boot_flags
1204+
~stanza_coqdep_flags:s.coqdep_flags
1205+
coq_modules
10651206
>>> Memo.parallel_iter
10661207
coq_modules
10671208
~f:

src/dune_rules/coq/coq_stanza.ml

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -169,6 +169,7 @@ module Theory = struct
169169
; modules : Ordered_set_lang.t
170170
; modules_flags : (Coq_module.Name.t * Ordered_set_lang.Unexpanded.t) list option
171171
; boot : bool
172+
; generate_project_file : Loc.t * bool
172173
; enabled_if : Blang.t
173174
; buildable : Buildable.t
174175
; coqdep_flags : Ordered_set_lang.Unexpanded.t
@@ -230,6 +231,18 @@ module Theory = struct
230231
| (loc, _) :: _ -> boot_has_deps loc)
231232
;;
232233

234+
let check_generate_project_file (loc, generate_project_file) modules_flags =
235+
if generate_project_file
236+
then (
237+
match modules_flags with
238+
| None -> ()
239+
| Some _ ->
240+
User_error.raise
241+
~loc
242+
[ Pp.textf "(generate_project_file) is not compatible with (modules_flags ...)"
243+
])
244+
;;
245+
233246
module Per_file = struct
234247
let decode_pair =
235248
let+ mod_ = Coq_module.Name.decode
@@ -248,6 +261,11 @@ module Theory = struct
248261
and+ public = coq_public_decode
249262
and+ synopsis = field_o "synopsis" string
250263
and+ boot = field_b "boot" ~check:(Dune_lang.Syntax.since coq_syntax (0, 2))
264+
and+ generate_project_file =
265+
located
266+
@@ field_b
267+
"generate_project_file"
268+
~check:(Dune_lang.Syntax.since coq_syntax (0, 11))
251269
and+ modules = Ordered_set_lang.field "modules"
252270
and+ modules_flags =
253271
field_o
@@ -274,6 +292,8 @@ module Theory = struct
274292
in
275293
(* boot libraries cannot depend on other theories *)
276294
check_boot_has_no_deps boot buildable;
295+
(* project files can only be generated when no per-module flags are configured. *)
296+
check_generate_project_file generate_project_file modules_flags;
277297
let package = merge_package_public ~package ~public in
278298
{ name
279299
; package
@@ -282,6 +302,7 @@ module Theory = struct
282302
; modules
283303
; modules_flags
284304
; boot
305+
; generate_project_file
285306
; buildable
286307
; enabled_if
287308
; coqdep_flags

src/dune_rules/coq/coq_stanza.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ module Theory : sig
3333
; modules : Ordered_set_lang.t
3434
; modules_flags : (Coq_module.Name.t * Ordered_set_lang.Unexpanded.t) list option
3535
; boot : bool
36+
; generate_project_file : Loc.t * bool
3637
; enabled_if : Blang.t
3738
; buildable : Buildable.t
3839
; coqdep_flags : Ordered_set_lang.Unexpanded.t
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
Testing the _CoqProject generation.
2+
3+
$ cat > dune-project <<EOF
4+
> (lang dune 3.21)
5+
> (using coq 0.11)
6+
> EOF
7+
8+
$ cat > dune <<EOF
9+
> (coq.theory
10+
> (name a)
11+
> (modules foo)
12+
> (generate_project_file))
13+
>
14+
> (coq.theory
15+
> (name b)
16+
> (modules bar)
17+
> (generate_project_file))
18+
> EOF
19+
20+
$ touch foo.v bar.v
21+
22+
$ dune build
23+
Error: Multiple rules generated for _build/default/_CoqProject:
24+
- dune:6
25+
- dune:1
26+
[1]
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
Testing the _CoqProject generation.
2+
3+
$ cat > dune-project <<EOF
4+
> (lang dune 3.21)
5+
> (using coq 0.11)
6+
> EOF
7+
8+
$ cat > dune <<EOF
9+
> (coq.theory
10+
> (name a)
11+
> (modules_flags (foo (:standard -flag)))
12+
> (generate_project_file))
13+
> EOF
14+
15+
$ touch foo.v
16+
17+
$ dune build
18+
File "dune", line 4, characters 1-24:
19+
4 | (generate_project_file))
20+
^^^^^^^^^^^^^^^^^^^^^^^
21+
Error: (generate_project_file) is not compatible with (modules_flags ...)
22+
[1]
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
Testing the _CoqProject generation.
2+
3+
$ cat > dune-project <<EOF
4+
> (lang dune 3.21)
5+
> (using coq 0.11)
6+
> EOF
7+
8+
$ cat > dune <<EOF
9+
> (coq.theory
10+
> (name a)
11+
> (generate_project_file))
12+
> EOF
13+
14+
$ touch foo.v
15+
16+
$ dune build
17+
$ [ -f _CoqProject ]

0 commit comments

Comments
 (0)