@@ -520,6 +520,131 @@ let dep_theory_file ~dir ~wrapper_name =
520520 |> Path.Build. set_extension ~ext: " .theory.d"
521521;;
522522
523+ let theory_coq_args
524+ ~sctx
525+ ~dir
526+ ~wrapper_name
527+ ~boot_flags
528+ ~stanza_flags
529+ ~ml_flags
530+ ~theories_deps
531+ ~theory_dirs
532+ =
533+ let + coq_stanza_flags =
534+ let + expander = Super_context. expander sctx ~dir in
535+ let coq_flags =
536+ let coq_flags = coq_flags ~expander ~dir ~stanza_flags ~per_file_flags: None in
537+ (* By default we have the -q flag. We don't want to pass this to coqtop to
538+ allow users to load their .coqrc files for interactive development.
539+ Therefore we manually scrub the -q setting when passing arguments to
540+ coqtop. *)
541+ let rec remove_q = function
542+ | "-q" :: l -> remove_q l
543+ | x :: l -> x :: remove_q l
544+ | [] -> []
545+ in
546+ let open Action_builder.O in
547+ coq_flags >> | remove_q
548+ in
549+ Command.Args. dyn coq_flags (* stanza flags *)
550+ in
551+ let coq_native_flags =
552+ let mode = Coq_mode. VoOnly in
553+ coqc_native_flags ~sctx ~dir ~theories_deps ~theory_dirs ~mode
554+ in
555+ let file_flags = coqc_file_flags ~dir ~theories_deps ~wrapper_name ~ml_flags in
556+ [ coq_stanza_flags; coq_native_flags; Dyn boot_flags; S file_flags ]
557+ ;;
558+
559+ let setup_coqproject_for_theory_rule
560+ ~scope
561+ ~sctx
562+ ~dir
563+ ~loc
564+ ~theories_deps
565+ ~wrapper_name
566+ ~use_stdlib
567+ ~ml_flags
568+ ~coq_lang_version
569+ ~stanza_flags
570+ ~theory_dirs
571+ coq_modules
572+ =
573+ (* Process coqdep and generate rules *)
574+ let boot_type =
575+ match coq_modules with
576+ | [] -> Resolve.Memo. return Bootstrap. empty
577+ | m :: _ -> Bootstrap. make ~scope ~use_stdlib ~wrapper_name ~coq_lang_version m
578+ in
579+ let boot_flags = Resolve.Memo. read boot_type |> Action_builder. map ~f: Bootstrap. flags in
580+ let * args =
581+ theory_coq_args
582+ ~sctx
583+ ~dir
584+ ~wrapper_name
585+ ~boot_flags
586+ ~stanza_flags
587+ ~ml_flags
588+ ~theories_deps
589+ ~theory_dirs
590+ in
591+ let contents : string With_targets.t =
592+ let open With_targets.O in
593+ let dir = Path. build dir in
594+ let + args_bld = Command. expand ~dir (Command.Args. S args)
595+ and + args_src =
596+ let dir = Path. source (Path. drop_build_context_exn dir) in
597+ Command. expand ~dir (Command.Args. S args)
598+ in
599+ let contents = Buffer. create 73 in
600+ let rec add_args args_bld args_src =
601+ match args_bld, args_src with
602+ | (("-R" | "-Q" ) as o ) :: db :: mb :: args_bld , _ :: ds :: ms :: args_src ->
603+ Buffer. add_string contents o;
604+ Buffer. add_char contents ' ' ;
605+ Buffer. add_string contents db;
606+ Buffer. add_char contents ' ' ;
607+ Buffer. add_string contents mb;
608+ Buffer. add_char contents '\n' ;
609+ if db <> ds
610+ then (
611+ Buffer. add_string contents o;
612+ Buffer. add_char contents ' ' ;
613+ Buffer. add_string contents ds;
614+ Buffer. add_char contents ' ' ;
615+ Buffer. add_string contents ms;
616+ Buffer. add_char contents '\n' );
617+ add_args args_bld args_src
618+ | "-I" :: _ :: args_bld , "-I" :: d :: args_src ->
619+ Buffer. add_string contents " -I " ;
620+ Buffer. add_string contents d;
621+ Buffer. add_char contents '\n' ;
622+ add_args args_bld args_src
623+ | o :: args_bld , _ :: args_src ->
624+ Buffer. add_string contents " -arg " ;
625+ Buffer. add_string contents o;
626+ Buffer. add_char contents '\n' ;
627+ add_args args_bld args_src
628+ | [] , [] -> ()
629+ | _ , _ -> assert false
630+ in
631+ add_args args_bld args_src;
632+ Buffer. contents contents
633+ in
634+ let mode =
635+ let open Rule.Promote in
636+ let lifetime = Lifetime. Until_clean in
637+ Rule.Mode. Promote { lifetime; into = None ; only = None }
638+ in
639+ let coqproject = Path.Build. relative dir " _CoqProject" in
640+ Super_context. add_rule
641+ ~mode
642+ ~loc
643+ sctx
644+ ~dir
645+ (Action_builder. write_file_dyn coqproject contents.build)
646+ ;;
647+
523648let setup_coqdep_for_theory_rule
524649 ~sctx
525650 ~dir
@@ -1050,18 +1175,34 @@ let setup_theory_rules ~sctx ~dir ~dir_contents (s : Coq_stanza.Theory.t) =
10501175 | m :: _ -> Bootstrap. make ~scope ~use_stdlib ~wrapper_name ~coq_lang_version m
10511176 in
10521177 let boot_flags = Resolve.Memo. read boot_type |> Action_builder. map ~f: Bootstrap. flags in
1053- setup_coqdep_for_theory_rule
1054- ~sctx
1055- ~dir
1056- ~loc
1057- ~theories_deps
1058- ~wrapper_name
1059- ~source_rule
1060- ~ml_flags
1061- ~mlpack_rule
1062- ~boot_flags
1063- ~stanza_coqdep_flags: s.coqdep_flags
1064- coq_modules
1178+ (if not (snd s.generate_project_file)
1179+ then Memo. return ()
1180+ else
1181+ setup_coqproject_for_theory_rule
1182+ ~scope
1183+ ~sctx
1184+ ~dir
1185+ ~loc
1186+ ~theories_deps
1187+ ~wrapper_name
1188+ ~use_stdlib
1189+ ~ml_flags
1190+ ~coq_lang_version
1191+ ~stanza_flags
1192+ ~theory_dirs
1193+ coq_modules)
1194+ >>> setup_coqdep_for_theory_rule
1195+ ~sctx
1196+ ~dir
1197+ ~loc
1198+ ~theories_deps
1199+ ~wrapper_name
1200+ ~source_rule
1201+ ~ml_flags
1202+ ~mlpack_rule
1203+ ~boot_flags
1204+ ~stanza_coqdep_flags: s.coqdep_flags
1205+ coq_modules
10651206 >>> Memo. parallel_iter
10661207 coq_modules
10671208 ~f:
0 commit comments