@@ -141,6 +141,15 @@ let coq_env =
141141 x.coq_flags
142142 in
143143 Expander. expand_and_eval_set expander (Coq_env. flags config.coq) ~standard
144+ and + coqdep_flags =
145+ let standard =
146+ let + x = Action_builder. of_memo_join parent in
147+ x.coqdep_flags
148+ in
149+ Expander. expand_and_eval_set
150+ expander
151+ (Coq_env. coqdep_flags config.coq)
152+ ~standard
144153 and + coqdoc_flags =
145154 let standard =
146155 let + x = Action_builder. of_memo_join parent in
@@ -151,7 +160,7 @@ let coq_env =
151160 (Coq_env. coqdoc_flags config.coq)
152161 ~standard
153162 in
154- { Coq_flags. coq_flags; coqdoc_flags })
163+ { Coq_flags. coq_flags; coqdep_flags; coqdoc_flags })
155164 in
156165 fun ~dir ->
157166 (let * () = Memo. return () in
@@ -176,6 +185,16 @@ let coq_flags ~dir ~stanza_flags ~per_file_flags ~expander =
176185 Expander. expand_and_eval_set expander flags_to_expand ~standard
177186;;
178187
188+ let coqdep_flags ~dir ~stanza_coqdep_flags ~expander =
189+ Expander. expand_and_eval_set
190+ expander
191+ stanza_coqdep_flags
192+ ~standard:
193+ (Action_builder. map
194+ ~f: (fun { Coq_flags. coqdep_flags; _ } -> coqdep_flags)
195+ (coq_env ~dir ))
196+ ;;
197+
179198let coqdoc_flags ~dir ~stanza_coqdoc_flags ~expander =
180199 Expander. expand_and_eval_set
181200 expander
@@ -474,6 +493,7 @@ let setup_coqdep_for_theory_rule
474493 ~ml_flags
475494 ~mlpack_rule
476495 ~boot_flags
496+ ~stanza_coqdep_flags
477497 coq_modules
478498 =
479499 (* coqdep needs the full source + plugin's mlpack to be present :( *)
@@ -484,7 +504,15 @@ let setup_coqdep_for_theory_rule
484504 ; Deps sources
485505 ]
486506 in
487- let coqdep_flags = Command.Args. Dyn boot_flags :: file_flags in
507+ let extra_coqdep_flags =
508+ (* Standard flags for coqdep *)
509+ let open Action_builder.O in
510+ let * expander = Action_builder. of_memo @@ Super_context. expander sctx ~dir in
511+ coqdep_flags ~dir ~stanza_coqdep_flags ~expander
512+ in
513+ let coqdep_flags =
514+ Command.Args. Dyn boot_flags :: Command.Args. dyn extra_coqdep_flags :: file_flags
515+ in
488516 let stdout_to = dep_theory_file ~dir ~wrapper_name in
489517 let * coqdep =
490518 Super_context. resolve_program_memo
@@ -968,6 +996,7 @@ let setup_theory_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Theory.t) =
968996 ~ml_flags
969997 ~mlpack_rule
970998 ~boot_flags
999+ ~stanza_coqdep_flags: s.coqdep_flags
9711000 coq_modules
9721001 >>> Memo. parallel_iter
9731002 coq_modules
@@ -1189,6 +1218,7 @@ let setup_extraction_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Extraction.t
11891218 ~ml_flags
11901219 ~mlpack_rule
11911220 ~boot_flags
1221+ ~stanza_coqdep_flags: Ordered_set_lang.Unexpanded. standard
11921222 [ coq_module ]
11931223 >>> setup_coqc_rule
11941224 ~scope
0 commit comments