File tree Expand file tree Collapse file tree 2 files changed +9
-6
lines changed Expand file tree Collapse file tree 2 files changed +9
-6
lines changed Original file line number Diff line number Diff line change @@ -44,6 +44,9 @@ Unreleased
4444- In opam constraints, reject ` (and) ` and ` (or) ` with no arguments at parse
4545 time (#7730 , @emillon )
4646
47+ - Fix ` -boot ` flag being passed to ` coqdep ` when composing with Coq stdlib
48+ (#7942 , @Alizter )
49+
47503.8.1 (2023-06-05)
4851------------------
4952
Original file line number Diff line number Diff line change @@ -130,14 +130,14 @@ let theories_flags ~theories_deps =
130130 let + libs = theories_deps in
131131 Command.Args. S (List. map ~f: theory_coqc_flag libs))
132132
133- let boot_flags ~coq_lang_version t : _ Command.Args.t =
134- let boot_flag = if coq_lang_version > = (0 , 8 ) then [ " -boot" ] else [] in
135- match t with
133+ let boot_flags ~coq_lang_version : _ -> _ Command.Args. t = function
134+ | `Bootstrap _ -> A " -boot"
136135 (* We are compiling the prelude itself
137136 [should be replaced with (per_file ...) flags] *)
138- | `Bootstrap_prelude -> As (" -noinit" :: boot_flag)
139- (* No special case *)
140- | `No_boot | `Bootstrap _ -> As boot_flag
137+ | `Bootstrap_prelude -> As [ " -boot" ; " -noinit" ]
138+ (* On >= 0.8 we always need to pass -boot *)
139+ | `No_boot ->
140+ if coq_lang_version > = (0 , 8 ) then A " -boot" else Command.Args. empty
141141
142142let coqc_file_flags ~dir ~theories_deps ~wrapper_name ~boot_type ~ml_flags
143143 ~coq_lang_version : _ Command.Args. t list =
You can’t perform that action at this time.
0 commit comments