@@ -7,27 +7,6 @@ open Memo.O
77(* Written by: Emilio Jesús Gallego Arias *)
88(* Written by: Rudi Grinberg *)
99
10- module Bootstrap = struct
11- (* the internal boot flag determines if the Coq "standard library" is being
12- built, in case we need to explicitly tell Coq where the build artifacts are
13- and add `Init.Prelude.vo` as a dependency; there is a further special case
14- when compiling the prelude, in this case we also need to tell Coq not to
15- try to load the prelude. *)
16- type t =
17- | No_boot (* * Coq's stdlib is installed globally *)
18- | Bootstrap of Coq_lib .t
19- (* * Coq's stdlib is in scope of the composed build *)
20- | Bootstrap_prelude
21- (* * We are compiling the prelude itself
22- [should be replaced with (per_file ...) flags] *)
23-
24- let flags t : _ Command.Args.t =
25- match t with
26- | No_boot -> Command.Args. empty
27- | Bootstrap _ -> A " -boot"
28- | Bootstrap_prelude -> As [ " -boot" ; " -noinit" ]
29- end
30-
3110let coqc ~loc ~dir ~sctx =
3211 Super_context. resolve_program sctx " coqc" ~dir ~loc: (Some loc)
3312 ~hint: " opam install coq"
@@ -87,6 +66,21 @@ let theories_flags ~theories_deps =
8766 let + libs = theories_deps in
8867 Command.Args. S (List. map ~f: theory_coqc_flag libs))
8968
69+ let boot_flags t : _ Command.Args.t =
70+ (* the internal boot flag determines if the Coq "standard library" is being
71+ built, in case we need to explicitly tell Coq where the build artifacts are
72+ and add `Init.Prelude.vo` as a dependency; there is a further special case
73+ when compiling the prelude, in this case we also need to tell Coq not to
74+ try to load the prelude. *)
75+ match t with
76+ (* Coq's stdlib is installed globally *)
77+ | `No_boot -> Command.Args. empty
78+ (* Coq's stdlib is in scope of the composed build *)
79+ | `Bootstrap _ -> A " -boot"
80+ (* We are compiling the prelude itself
81+ [should be replaced with (per_file ...) flags] *)
82+ | `Bootstrap_prelude -> As [ " -boot" ; " -noinit" ]
83+
9084let coqc_file_flags ~dir ~theories_deps ~wrapper_name ~boot_type ~ml_flags :
9185 _ Command.Args. t list =
9286 let file_flags : _ Command.Args.t list =
@@ -97,7 +91,7 @@ let coqc_file_flags ~dir ~theories_deps ~wrapper_name ~boot_type ~ml_flags :
9791 ; A wrapper_name
9892 ]
9993 in
100- [ Bootstrap. flags boot_type; S file_flags ]
94+ [ boot_flags boot_type; S file_flags ]
10195
10296let native_includes ~dir =
10397 let * scope = Scope.DB. find_by_dir dir in
@@ -256,8 +250,7 @@ let plugins_of_buildable ~context ~lib_db ~theories_deps
256250 in
257251 (ml_flags, mlpack_rule)
258252
259- let parse_coqdep ~dir ~(boot_type : Bootstrap.t ) ~coq_module
260- (lines : string list ) =
253+ let parse_coqdep ~dir ~boot_type ~coq_module (lines : string list ) =
261254 let source = Coq_module. source coq_module in
262255 let invalid phase =
263256 User_error. raise
@@ -291,8 +284,8 @@ let parse_coqdep ~dir ~(boot_type : Bootstrap.t) ~coq_module
291284 compiling the prelude *)
292285 let deps = List. map ~f: (Path. relative (Path. build dir)) deps in
293286 match boot_type with
294- | No_boot | Bootstrap_prelude -> deps
295- | Bootstrap lib ->
287+ | ` No_boot | ` Bootstrap_prelude -> deps
288+ | ` Bootstrap lib ->
296289 Path. relative (Path. build (Coq_lib. src_root lib)) " Init/Prelude.vo"
297290 :: deps)
298291
@@ -303,7 +296,7 @@ let boot_type ~dir ~use_stdlib ~wrapper_name coq_module =
303296 in
304297 if use_stdlib then
305298 match boot_lib with
306- | None -> Bootstrap. No_boot
299+ | None -> ` No_boot
307300 | Some (_loc , lib ) ->
308301 (* This is here as an optimization, TODO; replace with per_file flags *)
309302 let init =
@@ -312,8 +305,8 @@ let boot_type ~dir ~use_stdlib ~wrapper_name coq_module =
312305 (List. hd_opt (Coq_module. prefix coq_module))
313306 (Some " Init" )
314307 in
315- if init then Bootstrap. Bootstrap_prelude else Bootstrap lib
316- else Bootstrap. Bootstrap_prelude
308+ if init then ` Bootstrap_prelude else ` Bootstrap lib
309+ else ` Bootstrap_prelude
317310
318311let setup_coqdep_rule ~sctx ~dir ~loc ~theories_deps ~wrapper_name ~use_stdlib
319312 ~source_rule ~ml_flags ~mlpack_rule coq_module =
@@ -358,8 +351,13 @@ let coqc_rule ~sctx ~theories_deps ~theory_dirs ~dir ~coq_flags ~file_flags
358351 sandboxing *)
359352 >> | Action.Full. add_sandbox Sandbox_config. no_sandboxing
360353
361- let deps_of ~dir ~boot_type coq_module =
354+ let deps_of ~dir ~use_stdlib ~ wrapper_name coq_module =
362355 let stdout_to = Coq_module. dep_file ~obj_dir: dir coq_module in
356+ let open Action_builder.O in
357+ let * boot_type =
358+ Action_builder. of_memo
359+ @@ boot_type ~dir ~use_stdlib ~wrapper_name coq_module
360+ in
363361 Action_builder. dyn_paths_unit
364362 (Action_builder. map
365363 (Action_builder. lines_of (Path. build stdout_to))
@@ -370,7 +368,7 @@ let setup_coqc_rule ~loc ~dir ~sctx ~coqc_dir ~file_targets ~stanza_flags
370368 coq_module =
371369 (* Process coqdep and generate rules *)
372370 let * boot_type = boot_type ~dir ~use_stdlib ~wrapper_name coq_module in
373- let deps_of = deps_of ~dir ~boot_type coq_module in
371+ let deps_of = deps_of ~dir ~use_stdlib ~wrapper_name coq_module in
374372 let file_flags =
375373 coqc_file_flags ~dir ~theories_deps ~wrapper_name ~boot_type ~ml_flags
376374 in
0 commit comments