@@ -395,61 +395,52 @@ let rocqc_native_flags ~sctx ~dir ~theories_deps ~theory_dirs ~(mode : Rocq_mode
395395;;
396396
397397(* closure of all the ML libs a theory depends on *)
398- let libs_of_theory ~lib_db ~theories_deps plugins : ( Lib.t list * _) Resolve.Memo.t =
398+ let libs_of_theory ~lib_db ~theories_deps plugins : Lib.t list Resolve.Memo.t =
399399 let open Resolve.Memo.O in
400400 let * libs =
401401 Resolve.Memo.List. map plugins ~f: (fun (loc , name ) ->
402402 let + lib = Lib.DB. resolve lib_db (loc, name) in
403403 loc, lib)
404404 in
405405 let * theories = theories_deps in
406- (* Filter dune theories *)
407- let f (t : Rocq_lib.t ) =
408- match t with
409- | Dune t -> Left t
410- | Legacy t -> Right t
411- in
412- let dune_theories, legacy_theories = List. partition_map ~f theories in
413- let * dlibs =
414- Resolve.List. concat_map ~f: Rocq_lib.Dune. libraries dune_theories |> Resolve.Memo. lift
406+ let f = function
407+ | Rocq_lib. Dune d -> Rocq_lib.Dune. libraries d
408+ | Rocq_lib. Legacy _ -> Resolve. return []
415409 in
410+ let * dlibs = Resolve.List. concat_map ~f theories |> Resolve.Memo. lift in
416411 let libs = libs @ dlibs in
417412 let + findlib_libs = Lib. closure ~linking: false (List. map ~f: snd libs) in
418- findlib_libs, legacy_theories
413+ findlib_libs
419414;;
420415
421- (* compute include flags and mlpack rules *)
422- let ml_pack_and_meta_rule ~context ~all_libs (buildable : Rocq_stanza.Buildable.t )
416+ (* depend on the right META files so findlib works for loading Rocq plugins *)
417+ let ml_meta_rule ~context ~all_libs (buildable : Rocq_stanza.Buildable.t )
423418 : unit Action_builder. t
424419 =
425- (* rocqdep expects an mlpack file next to the sources otherwise it will
426- omit the cmxs deps *)
427420 let plugin_loc = List. hd_opt buildable.plugins |> Option. map ~f: fst in
428421 let meta_info = Util. meta_info ~loc: plugin_loc ~context in
429422 Action_builder. paths (List. filter_map ~f: meta_info all_libs)
430423;;
431424
432- let ml_flags_and_ml_pack_rule
425+ let ml_flags_and_ml_meta_rule
433426 ~context
434427 ~lib_db
435428 ~theories_deps
436429 (buildable : Rocq_stanza.Buildable.t )
437430 =
438431 let res =
439432 let open Resolve.Memo.O in
440- let + all_libs, _legacy_theories =
441- libs_of_theory ~lib_db ~theories_deps buildable.plugins
442- in
433+ let + all_libs = libs_of_theory ~lib_db ~theories_deps buildable.plugins in
443434 let findlib_plugin_flags = Util. include_flags all_libs in
444435 let ml_flags = Command.Args. S [ findlib_plugin_flags ] in
445- ml_flags, ml_pack_and_meta_rule ~context ~all_libs buildable
436+ ml_flags, ml_meta_rule ~context ~all_libs buildable
446437 in
447- let mlpack_rule =
438+ let ml_meta_rule =
448439 let open Action_builder.O in
449- let * _, mlpack_rule = Resolve.Memo. read res in
450- mlpack_rule
440+ let * _, ml_meta_rule = Resolve.Memo. read res in
441+ ml_meta_rule
451442 in
452- Resolve.Memo. map ~f: fst res, mlpack_rule
443+ Resolve.Memo. map ~f: fst res, ml_meta_rule
453444;;
454445
455446let dep_theory_file ~dir ~wrapper_name =
@@ -1020,7 +1011,7 @@ let theory_context ~context ~scope ~name buildable =
10201011 (* ML-level flags for depending libraries *)
10211012 let ml_flags, mlpack_rule =
10221013 let lib_db = Scope. libs scope in
1023- ml_flags_and_ml_pack_rule ~context ~theories_deps ~lib_db buildable
1014+ ml_flags_and_ml_meta_rule ~context ~theories_deps ~lib_db buildable
10241015 in
10251016 theory, theories_deps, ml_flags, mlpack_rule
10261017;;
@@ -1050,7 +1041,7 @@ let extraction_context ~context ~scope (buildable : Rocq_stanza.Buildable.t) =
10501041 in
10511042 let ml_flags, mlpack_rule =
10521043 let lib_db = Scope. libs scope in
1053- ml_flags_and_ml_pack_rule ~context ~theories_deps ~lib_db buildable
1044+ ml_flags_and_ml_meta_rule ~context ~theories_deps ~lib_db buildable
10541045 in
10551046 theories_deps, ml_flags, mlpack_rule
10561047;;
0 commit comments