Skip to content

Commit 9d2e2e2

Browse files
committed
[coq] Move mode to buildable, guard with coq 0.3 lang version
1 parent 2ba301d commit 9d2e2e2

File tree

4 files changed

+16
-15
lines changed

4 files changed

+16
-15
lines changed

src/dune_engine/stanza.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module Parser = struct
66
type nonrec t = string * t list Dune_lang.Decoder.t
77
end
88

9-
let latest_version = (2, 7)
9+
let latest_version = (2, 8)
1010

1111
let since v = (v, `Since v)
1212

src/dune_rules/coq_rules.ml

+6-7
Original file line numberDiff line numberDiff line change
@@ -163,7 +163,7 @@ module Context = struct
163163
(* If the mlpack files don't exist, don't fail *)
164164
Build.paths_existing (List.concat_map ~f:Util.ml_pack_files libs)) )
165165

166-
let create ~coqc_dir sctx ~dir ~wrapper_name ~theories_deps ~mode
166+
let create ~coqc_dir sctx ~dir ~wrapper_name ~theories_deps
167167
~native_includes (buildable : Buildable.t) =
168168
let loc = buildable.loc in
169169
let rr = resolve_program sctx ~dir ~loc in
@@ -188,7 +188,7 @@ module Context = struct
188188
; boot_type = Bootstrap.No_boot
189189
; build_dir
190190
; profile_flags = Super_context.coq sctx ~dir
191-
; mode
191+
; mode = snd buildable.mode
192192
; native_includes
193193
}
194194

@@ -369,12 +369,11 @@ let setup_rules ~sctx ~dir ~dir_contents (s : Theory.t) =
369369
(* Coq flags for depending libraries *)
370370
let theories_deps = Coq_lib.DB.requires coq_lib_db theory in
371371
let coqc_dir = (Super_context.context sctx).build_dir in
372-
let mode = snd s.mode in
373372
let native_includes =
374373
Lib.DB.resolve lib_db (Loc.none, Lib_name.of_string "coq.kernel")
375374
|> Result.map ~f:(fun lib -> Util.native_paths [ lib ])
376375
in
377-
Context.create sctx ~coqc_dir ~dir ~wrapper_name ~theories_deps ~mode
376+
Context.create sctx ~coqc_dir ~dir ~wrapper_name ~theories_deps
378377
~native_includes s.buildable
379378
in
380379

@@ -434,7 +433,7 @@ let coq_plugins_install_rules ~scope ~package ~dst_dir (s : Theory.t) =
434433
let install_rules ~sctx ~dir s =
435434
match s with
436435
| { Theory.package = None; _ } -> []
437-
| { Theory.package = Some package; mode; _ } ->
436+
| { Theory.package = Some package; buildable = { mode; _} ; _ } ->
438437
let loc = s.buildable.loc in
439438
let scope = SC.find_scope_by_dir sctx dir in
440439
let dir_contents = Dir_contents.get sctx ~dir in
@@ -502,8 +501,8 @@ let extraction_rules ~sctx ~dir ~dir_contents (s : Extraction.t) =
502501
let coq_lib_db = Scope.coq_libs scope in
503502
Coq_lib.DB.requires_for_user_written coq_lib_db s.buildable.theories
504503
in
505-
let mode, native_includes = (Coq_mode.VoOnly, Ok Path.Set.empty) in
506-
Context.create sctx ~coqc_dir:dir ~dir ~wrapper_name ~theories_deps ~mode
504+
let native_includes = Ok Path.Set.empty in
505+
Context.create sctx ~coqc_dir:dir ~dir ~wrapper_name ~theories_deps
507506
~native_includes s.buildable
508507
in
509508
let coq_module =

src/dune_rules/coq_stanza.ml

+8-6
Original file line numberDiff line numberDiff line change
@@ -22,11 +22,14 @@ end
2222

2323
let coq_syntax =
2424
Dune_lang.Syntax.create ~name:"coq" ~desc:"the coq extension (experimental)"
25-
[ ((0, 1), `Since (1, 9)); ((0, 2), `Since (2, 5)) ]
25+
[ ((0, 1), `Since (1, 9))
26+
; ((0, 2), `Since (2, 5))
27+
; ((0, 3), `Since (2, 8))]
2628

2729
module Buildable = struct
2830
type t =
2931
{ flags : Ordered_set_lang.Unexpanded.t
32+
; mode : Loc.t * Coq_mode.t
3033
; libraries : (Loc.t * Lib_name.t) list (** ocaml libraries *)
3134
; theories : (Loc.t * Coq_lib_name.t) list (** coq libraries *)
3235
; loc : Loc.t
@@ -35,14 +38,17 @@ module Buildable = struct
3538
let decode =
3639
let+ loc = loc
3740
and+ flags = Ordered_set_lang.Unexpanded.field "flags"
41+
and+ mode =
42+
(Dune_lang.Syntax.since coq_syntax (0, 3) >>>
43+
located (field "mode" ~default:Coq_mode.VoOnly Coq_mode.decode))
3844
and+ libraries =
3945
field "libraries" (repeat (located Lib_name.decode)) ~default:[]
4046
and+ theories =
4147
field "theories"
4248
(Dune_lang.Syntax.since coq_syntax (0, 2) >>> repeat Coq_lib_name.decode)
4349
~default:[]
4450
in
45-
{ flags; libraries; theories; loc }
51+
{ flags; mode; libraries; theories; loc }
4652
end
4753

4854
module Extraction = struct
@@ -79,7 +85,6 @@ module Theory = struct
7985
; modules : Ordered_set_lang.t
8086
; boot : bool
8187
; enabled_if : Blang.t
82-
; mode : Loc.t * Coq_mode.t
8388
; buildable : Buildable.t
8489
}
8590

@@ -129,8 +134,6 @@ module Theory = struct
129134
and+ synopsis = field_o "synopsis" string
130135
and+ boot =
131136
field_b "boot" ~check:(Dune_lang.Syntax.since coq_syntax (0, 2))
132-
and+ mode =
133-
located (field "mode" ~default:Coq_mode.VoOnly Coq_mode.decode)
134137
and+ modules = modules_field "modules"
135138
and+ enabled_if = Enabled_if.decode ~allowed_vars:Any ~since:None ()
136139
and+ buildable = Buildable.decode in
@@ -143,7 +146,6 @@ module Theory = struct
143146
; boot
144147
; buildable
145148
; enabled_if
146-
; mode
147149
})
148150

149151
type Stanza.t += T of t

src/dune_rules/coq_stanza.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ open Import
44
module Buildable : sig
55
type t =
66
{ flags : Ordered_set_lang.Unexpanded.t
7+
; mode : Loc.t * Coq_mode.t
78
; libraries : (Loc.t * Lib_name.t) list (** ocaml libraries *)
89
; theories : (Loc.t * Coq_lib_name.t) list (** coq libraries *)
910
; loc : Loc.t
@@ -31,7 +32,6 @@ module Theory : sig
3132
; modules : Ordered_set_lang.t
3233
; boot : bool
3334
; enabled_if : Blang.t
34-
; mode : Loc.t * Coq_mode.t
3535
; buildable : Buildable.t
3636
}
3737

0 commit comments

Comments
 (0)