diff --git a/bin/top.ml b/bin/top.ml index 8684879f9b0..454f8749c90 100644 --- a/bin/top.ml +++ b/bin/top.ml @@ -17,9 +17,8 @@ let man = let info = Term.info "top" ~doc ~man -let link_deps link ~lib_config = - List.concat_map link ~f:(fun t -> - Dune.Lib.link_deps t Dune.Link_mode.Byte lib_config) +let link_deps link = + List.concat_map link ~f:(fun t -> Dune.Lib.link_deps t Dune.Link_mode.Byte) let term = let+ common = Common.term @@ -44,8 +43,7 @@ let term = let libs = Dune.Utop.libs_under_dir sctx ~db ~dir:(Path.build dir) in let requires = Dune.Lib.closure ~linking:true libs |> Result.ok_exn in let include_paths = Dune.Lib.L.include_paths requires in - let lib_config = sctx |> Super_context.context |> Context.lib_config in - let files = link_deps requires ~lib_config in + let files = link_deps requires in let* () = do_build (List.map files ~f:(fun f -> Target.File f)) in let files_to_load = List.filter files ~f:(fun p -> diff --git a/src/dune/jsoo_rules.ml b/src/dune/jsoo_rules.ml index 264243c4c06..2539bd59911 100644 --- a/src/dune/jsoo_rules.ml +++ b/src/dune/jsoo_rules.ml @@ -153,7 +153,10 @@ let setup_separate_compilation_rules sctx components = META *) match lib_name with | "stdlib" -> - let archive = Path.relative ctx.stdlib_dir in + let archive = + let stdlib_dir = (Lib.lib_config pkg).stdlib_dir in + Path.relative stdlib_dir + in archive "stdlib.cma" :: archive "std_exit.cmo" :: archives | _ -> archives in diff --git a/src/dune/lib.ml b/src/dune/lib.ml index 0f7739e8cca..b8d7777a1a4 100644 --- a/src/dune/lib.ml +++ b/src/dune/lib.ml @@ -244,7 +244,7 @@ module T = struct ; resolved_selects : Resolved_select.t list ; user_written_deps : Dune_file.Lib_deps.t ; implements : t Or_exn.t option - ; stdlib_dir : Path.t + ; lib_config : Lib_config.t ; (* these fields cannot be forced until the library is instantiated *) default_implementation : t Or_exn.t Lazy.t option ; (* This is mutable to avoid this error: @@ -317,7 +317,7 @@ type db = ; resolve : Lib_name.t -> resolve_result ; table : (Lib_name.t, Status.t) Table.t ; all : Lib_name.t list Lazy.t - ; stdlib_dir : Path.t + ; lib_config : Lib_config.t ; instrument_with : Lib_name.t list } @@ -328,6 +328,8 @@ and resolve_result = | Invalid of exn | Redirect of db option * (Loc.t * Lib_name.t) +let lib_config (t : lib) = t.lib_config + let name t = t.name let info t = t.info @@ -390,7 +392,7 @@ module Link_params = struct not appear on the command line *) } - let get t (mode : Link_mode.t) (lib_config : Lib_config.t) = + let get t (mode : Link_mode.t) = let lib_files = Lib_info.foreign_archives t.info and dll_files = Lib_info.foreign_dll_files t.info in (* OCaml library archives [*.cma] and [*.cmxa] are directly listed in the @@ -440,14 +442,14 @@ module Link_params = struct Path.extend_basename obj_name ~suffix:(Cm_kind.ext Cmo) :: hidden_deps | Native -> Path.extend_basename obj_name ~suffix:(Cm_kind.ext Cmx) - :: Path.extend_basename obj_name ~suffix:lib_config.ext_obj + :: Path.extend_basename obj_name ~suffix:t.lib_config.ext_obj :: hidden_deps ) in { deps; hidden_deps; include_dirs } end -let link_deps t mode lib_config = - let x = Link_params.get t mode lib_config in +let link_deps t mode = + let x = Link_params.get t mode in List.rev_append x.hidden_deps x.deps module L = struct @@ -470,7 +472,7 @@ module L = struct in match ts with | [] -> dirs - | x :: _ -> Path.Set.remove dirs x.stdlib_dir + | x :: _ -> Path.Set.remove dirs x.lib_config.stdlib_dir let include_flags ts = to_iflags (include_paths ts) @@ -482,14 +484,12 @@ module L = struct in match ts with | [] -> dirs - | x :: _ -> Path.Set.remove dirs x.stdlib_dir + | x :: _ -> Path.Set.remove dirs x.lib_config.stdlib_dir let c_include_flags ts = to_iflags (c_include_paths ts) - let compile_and_link_flags ~compile ~link ~mode ~lib_config = - let params = - List.map link ~f:(fun t -> Link_params.get t mode lib_config) - in + let compile_and_link_flags ~compile ~link ~mode = + let params = List.map link ~f:(fun t -> Link_params.get t mode) in let dirs = let dirs = Path.Set.union (include_paths compile) (c_include_paths link) @@ -534,7 +534,7 @@ module Lib_and_module = struct Command.Args.S (List.map ts ~f:(function | Lib t -> - let p = Link_params.get t mode lib_config in + let p = Link_params.get t mode in Command.Args.S ( Deps p.deps :: Hidden_deps (Dep.Set.of_files p.hidden_deps) @@ -1088,7 +1088,7 @@ end = struct ; sub_systems = Sub_system_name.Map.empty ; implements ; default_implementation - ; stdlib_dir = db.stdlib_dir + ; lib_config = db.lib_config ; re_exports } in @@ -1650,7 +1650,7 @@ module DB = struct ; resolve ; table = Table.create (module Lib_name) 1024 ; all = Lazy.from_fun all - ; stdlib_dir = lib_config.Lib_config.stdlib_dir + ; lib_config ; instrument_with = lib_config.Lib_config.instrument_with } diff --git a/src/dune/lib.mli b/src/dune/lib.mli index f15a51ede5e..5d3783f9fa3 100644 --- a/src/dune/lib.mli +++ b/src/dune/lib.mli @@ -12,6 +12,8 @@ val to_dyn : t -> Dyn.t or the [name] if not. *) val name : t -> Lib_name.t +val lib_config : t -> Lib_config.t + val implements : t -> t Or_exn.t option (** Directory where the object files for the library are located. *) @@ -53,7 +55,7 @@ val hash : t -> int (** The list of files that will be read by the compiler when linking an executable against this library *) -val link_deps : t -> Link_mode.t -> Lib_config.t -> Path.t list +val link_deps : t -> Link_mode.t -> Path.t list (** Operations on list of libraries *) module L : sig @@ -70,11 +72,7 @@ module L : sig val c_include_flags : t -> _ Command.Args.t val compile_and_link_flags : - compile:t - -> link:t - -> mode:Link_mode.t - -> lib_config:Lib_config.t - -> _ Command.Args.t + compile:t -> link:t -> mode:Link_mode.t -> _ Command.Args.t val jsoo_runtime_files : t -> Path.t list diff --git a/src/dune/preprocessing.ml b/src/dune/preprocessing.ml index 8263e793561..87c765256c3 100644 --- a/src/dune/preprocessing.ml +++ b/src/dune/preprocessing.ml @@ -347,7 +347,7 @@ let build_ppx_driver sctx ~dep_kind ~target ~pps ~pp_names = (Result.map driver_and_libs ~f:(fun (_driver, libs) -> Command.Args.S [ Lib.L.compile_and_link_flags ~mode:link_mode - ~compile:libs ~link:libs ~lib_config:ctx.lib_config + ~compile:libs ~link:libs ; Hidden_deps (Lib_file_deps.deps libs ~groups:[ Cmi; Cmx ]) ]))