Skip to content

Commit

Permalink
[coq_lib] Enforce that boot libraries depend on no theories
Browse files Browse the repository at this point in the history
Signed-off-by: Emilio Jesus Gallego Arias <e+git@x80.org>
  • Loading branch information
ejgallego committed Jun 11, 2022
1 parent f2f42dd commit 373bf6b
Show file tree
Hide file tree
Showing 12 changed files with 37 additions and 0 deletions.
1 change: 1 addition & 0 deletions src/dune_rules/coq_lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ module Error = struct
[ Pp.textf "Cannot have more than one boot theory in scope:"
; Pp.enumerate theories ~f:name
]

end

let top_closure =
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rules/coq_stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ module Extraction = struct
end

module Theory = struct

type t =
{ loc : Loc.t
; name : Coq_lib_name.t
Expand Down Expand Up @@ -133,6 +134,9 @@ module Theory = struct
1.0 version of the Coq language"
]

let boot_has_deps { Buildable.loc; _ } =
User_error.raise ~loc [ Pp.textf "(boot) libraries cannot have dependencies" ]

let decode =
fields
(let+ loc, name = field "name" Coq_lib_name.decode
Expand All @@ -145,6 +149,8 @@ module Theory = struct
and+ modules = Stanza_common.modules_field "modules"
and+ enabled_if = Enabled_if.decode ~allowed_vars:Any ~since:None ()
and+ buildable = Buildable.decode in
(* boot libraries cannot depend on other theories *)
if boot && List.is_non_empty buildable.theories then boot_has_deps buildable;
let package = select_deprecation ~package ~public in
{ loc
; name
Expand Down
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
Inductive AnotherBegining := Of | The | Universe.
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(coq.theory
(name A)
(package A)
(theories B)
(boot))
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(lang dune 2.5)

(using coq 0.2)
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
Inductive Begining := Of | The | Universe.
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(coq.theory
(name B)
(package B))


Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(lang dune 2.5)

(using coq 0.2)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 3.2)
11 changes: 11 additions & 0 deletions test/blackbox-tests/test-cases/coq/compose-boot-nodeps.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
Testing composition with two boot libraries

$ dune build
File "A/dune", line 1, characters 0-57:
1 | (coq.theory
2 | (name A)
3 | (package A)
4 | (theories B)
5 | (boot))
Error: (boot) libraries cannot have dependencies
[1]

0 comments on commit 373bf6b

Please sign in to comment.