diff --git a/bin/common.ml b/bin/common.ml index 1fe5c04ad012..4bf398e946cb 100644 --- a/bin/common.ml +++ b/bin/common.ml @@ -99,7 +99,9 @@ let set_common_other ?log_file c ~targets = Clflags.ignore_promoted_rules := c.ignore_promoted_rules; Option.iter ~f:Dune.Stats.enable c.stats_trace_file -let set_common ?log_file c ~targets = +let set_common ?log_file ?external_lib_deps_mode c ~targets = + Option.iter external_lib_deps_mode ~f:(fun x -> + Clflags.external_lib_deps_mode := x); set_dirs c; set_common_other ?log_file c ~targets diff --git a/bin/common.mli b/bin/common.mli index f143d6978650..7dc947802e3c 100644 --- a/bin/common.mli +++ b/bin/common.mli @@ -28,12 +28,17 @@ val default_target : t -> Arg.Dep.t val prefix_target : t -> string -> string -(** [set_common ?log common ~targets] is [set_dirs common] followed by - [set_common_other common ~targets]. In general, [set_common] executes - sequence of side-effecting actions to initialize Dune's working environment - based on the options determined in a [Common.t] record.contents. *) +(** [set_common ?log common ~targets ~external_lib_deps_mode] is + [set_dirs common] followed by [set_common_other common ~targets]. In + general, [set_common] executes sequence of side-effecting actions to + initialize Dune's working environment based on the options determined in a + [Common.t] record.contents. *) val set_common : - ?log_file:Dune_util.Log.File.t -> t -> targets:Arg.Dep.t list -> unit + ?log_file:Dune_util.Log.File.t + -> ?external_lib_deps_mode:bool + -> t + -> targets:Arg.Dep.t list + -> unit (** [set_common_other common ~targets] sets all stateful values dictated by [common], except those accounted for by [set_dirs]. [targets] are used to diff --git a/bin/compute.ml b/bin/compute.ml index ba38c15990e5..b0f8e64c5cac 100644 --- a/bin/compute.ml +++ b/bin/compute.ml @@ -29,13 +29,11 @@ let term = & info [] ~docv:"INPUT" ~doc:"Use $(docv) as the input to the function.") in - Common.set_common common ~targets:[]; + Common.set_common common ~targets:[] ~external_lib_deps_mode:true; let action = Scheduler.go ~common (fun () -> let open Fiber.O in - let* _setup = - Import.Main.setup common ~external_lib_deps_mode:true - in + let* _setup = Import.Main.setup common in match (fn, inp) with | "list", None -> Fiber.return `List | "list", Some _ -> diff --git a/bin/describe.ml b/bin/describe.ml index 0ff22fa4fa0a..3d21bbab8abd 100644 --- a/bin/describe.ml +++ b/bin/describe.ml @@ -188,11 +188,11 @@ let term = and+ context_name = Common.context_arg ~doc:"Build context to use." and+ format = Format.arg and+ lang = Lang.arg in - Common.set_common common ~targets:[]; + Common.set_common common ~targets:[] ~external_lib_deps_mode:false; let what = What.parse what ~lang in Scheduler.go ~common (fun () -> let open Fiber.O in - let* setup = Import.Main.setup common ~external_lib_deps_mode:false in + let* setup = Import.Main.setup common in let context = Import.Main.find_context_exn setup.workspace ~name:context_name in diff --git a/bin/external_lib_deps.ml b/bin/external_lib_deps.ml index 2a6ee7421d4f..8673faca7510 100644 --- a/bin/external_lib_deps.ml +++ b/bin/external_lib_deps.ml @@ -130,11 +130,11 @@ let term = and+ sexp = Arg.(value & flag & info [ "sexp" ] ~doc:{|Produce a s-expression output|}) in - Common.set_common common ~targets:[]; + Common.set_common common ~targets:[] ~external_lib_deps_mode:true; let setup, lib_deps = Scheduler.go ~common (fun () -> let open Fiber.O in - let+ setup = Import.Main.setup common ~external_lib_deps_mode:true in + let+ setup = Import.Main.setup common in let targets = Target.resolve_targets_exn common setup targets in let request = Target.request targets in let deps = Build_system.all_lib_deps ~request in diff --git a/bin/import.ml b/bin/import.ml index 477b66bc4d15..676f87d84048 100644 --- a/bin/import.ml +++ b/bin/import.ml @@ -79,7 +79,7 @@ module Main = struct let ancestor_vcs = (Common.root common).ancestor_vcs in scan_workspace ?workspace_file ?x ?profile ~capture_outputs ~ancestor_vcs () - let setup ?external_lib_deps_mode common = + let setup common = let open Fiber.O in let* caching = make_cache (Common.config common) in let* workspace = scan_workspace common in @@ -121,7 +121,7 @@ module Main = struct in init_build_system workspace ~sandboxing_preference:(Common.config common).sandboxing_preference - ?caching ?external_lib_deps_mode ?only_packages + ?caching ?only_packages end module Scheduler = struct diff --git a/bin/print_rules.ml b/bin/print_rules.ml index 2e322bfbd694..52d42edc90f3 100644 --- a/bin/print_rules.ml +++ b/bin/print_rules.ml @@ -109,10 +109,10 @@ let term = and+ targets = Arg.(value & pos_all string [] & Arg.info [] ~docv:"TARGET") in let out = Option.map ~f:Path.of_string out in let targets = List.map ~f:Arg.Dep.file targets in - Common.set_common common ~targets; + Common.set_common common ~targets ~external_lib_deps_mode:true; Scheduler.go ~common (fun () -> let open Fiber.O in - let* setup = Import.Main.setup common ~external_lib_deps_mode:true in + let* setup = Import.Main.setup common in let request = match targets with | [] -> diff --git a/src/dune/clflags.ml b/src/dune/clflags.ml index 342e167f72ed..243478563cc9 100644 --- a/src/dune/clflags.ml +++ b/src/dune/clflags.ml @@ -10,6 +10,8 @@ let debug_dep_path = ref false let external_lib_deps_hint = ref [] +let external_lib_deps_mode = ref false + let capture_outputs = ref true let debug_backtraces = Dune_util.Report_error.report_backtraces diff --git a/src/dune/clflags.mli b/src/dune/clflags.mli index 91bcb0a93f3d..84ff6d07a181 100644 --- a/src/dune/clflags.mli +++ b/src/dune/clflags.mli @@ -9,6 +9,8 @@ val debug_findlib : bool ref (** The command line for "Hint: try: dune external-lib-deps ..." *) val external_lib_deps_hint : string list ref +val external_lib_deps_mode : bool ref + (** Capture the output of sub-commands *) val capture_outputs : bool ref diff --git a/src/dune/gen_rules.ml b/src/dune/gen_rules.ml index 898fb7717ab3..7dcbba6777f3 100644 --- a/src/dune/gen_rules.ml +++ b/src/dune/gen_rules.ml @@ -402,7 +402,7 @@ let filter_out_stanzas_from_hidden_packages ~visible_pkgs = { implementation = name; virtual_lib; variant; project; loc }) | _ -> None )) -let gen ~contexts ?(external_lib_deps_mode = false) ?only_packages conf = +let gen ~contexts ?only_packages conf = let open Fiber.O in let { Dune_load.dune_files; packages; projects } = conf in let packages = Option.value only_packages ~default:packages in @@ -432,8 +432,7 @@ let gen ~contexts ?(external_lib_deps_mode = false) ?only_packages conf = in let* host, stanzas = Fiber.fork_and_join host stanzas in let sctx = - Super_context.create ?host ~context ~projects ~packages - ~external_lib_deps_mode ~stanzas + Super_context.create ?host ~context ~projects ~packages ~stanzas in let+ () = Fiber.Ivar.fill (Table.find_exn sctxs context.name) sctx in (context.name, sctx) diff --git a/src/dune/gen_rules.mli b/src/dune/gen_rules.mli index af026b9ee23f..ea05dcdb38d4 100644 --- a/src/dune/gen_rules.mli +++ b/src/dune/gen_rules.mli @@ -4,7 +4,6 @@ open! Import (* Generate rules. Returns evaluated Dune files per context names. *) val gen : contexts:Context.t list - -> ?external_lib_deps_mode:bool (* default: false *) -> ?only_packages:Package.t Package.Name.Map.t -> Dune_load.conf -> Super_context.t Context_name.Map.t Fiber.t diff --git a/src/dune/install_rules.ml b/src/dune/install_rules.ml index 5d5d59def488..99d3882e0e83 100644 --- a/src/dune/install_rules.ml +++ b/src/dune/install_rules.ml @@ -174,7 +174,7 @@ end = struct let stanzas_to_entries sctx = let ctx = Super_context.context sctx in let stanzas = Super_context.stanzas sctx in - let external_lib_deps_mode = Super_context.external_lib_deps_mode sctx in + let external_lib_deps_mode = !Clflags.external_lib_deps_mode in let keep_if = keep_if ~external_lib_deps_mode in let init = Super_context.packages sctx diff --git a/src/dune/lib.ml b/src/dune/lib.ml index 4852d71f3e52..0e04ac3a5436 100644 --- a/src/dune/lib.ml +++ b/src/dune/lib.ml @@ -1918,7 +1918,7 @@ module DB = struct | Some (Found lib) -> Found lib) ~all:(fun () -> Lib_name.Map.keys map) - let create_from_findlib ~external_lib_deps_mode ~stdlib_dir findlib = + let create_from_findlib ~stdlib_dir findlib = create () ~parent:None ~stdlib_dir ~resolve:(fun name -> match Findlib.find findlib name with @@ -1930,7 +1930,7 @@ module DB = struct match e with | Invalid_dune_package why -> Invalid why | Not_found -> - if external_lib_deps_mode then + if !Clflags.external_lib_deps_mode then let pkg = Findlib.dummy_lib findlib ~name in Found (Dune_package.Lib.info pkg) else diff --git a/src/dune/lib.mli b/src/dune/lib.mli index 7d71e1b8f032..af79098ffff9 100644 --- a/src/dune/lib.mli +++ b/src/dune/lib.mli @@ -194,8 +194,7 @@ module DB : sig -> Library_related_stanza.t list -> t - val create_from_findlib : - external_lib_deps_mode:bool -> stdlib_dir:Path.t -> Findlib.t -> t + val create_from_findlib : stdlib_dir:Path.t -> Findlib.t -> t val find : t -> Lib_name.t -> lib option diff --git a/src/dune/main.ml b/src/dune/main.ml index afe8e60b2624..f7ca96e4d401 100644 --- a/src/dune/main.ml +++ b/src/dune/main.ml @@ -68,14 +68,10 @@ let scan_workspace ?workspace_file ?x ?(capture_outputs = true) ?profile ]); { contexts; conf; env } -let init_build_system ?only_packages ?external_lib_deps_mode - ~sandboxing_preference ?caching w = +let init_build_system ?only_packages ~sandboxing_preference ?caching w = Build_system.reset (); Build_system.init ~sandboxing_preference ~contexts:w.contexts ?caching; - let+ scontexts = - Gen_rules.gen w.conf ~contexts:w.contexts ?only_packages - ?external_lib_deps_mode - in + let+ scontexts = Gen_rules.gen w.conf ~contexts:w.contexts ?only_packages in { workspace = w; scontexts } let auto_concurrency = diff --git a/src/dune/main.mli b/src/dune/main.mli index f558e6a41bf2..8cf3422f4b77 100644 --- a/src/dune/main.mli +++ b/src/dune/main.mli @@ -29,7 +29,6 @@ val scan_workspace : (** Load dune files and initializes the build system *) val init_build_system : ?only_packages:Package.t Package.Name.Map.t - -> ?external_lib_deps_mode:bool -> sandboxing_preference:Sandbox_mode.t list -> ?caching:Build_system.caching -> workspace diff --git a/src/dune/super_context.ml b/src/dune/super_context.ml index 1733790bac1a..040addd27a7b 100644 --- a/src/dune/super_context.ml +++ b/src/dune/super_context.ml @@ -186,7 +186,6 @@ type t = ; lib_entries_by_package : Lib_entry.t list Package.Name.Map.t ; env_tree : Env_tree.t ; dir_status_db : Dir_status.DB.t - ; external_lib_deps_mode : bool ; (* Env node that represents the environment configured for the workspace. It is used as default at the root of every project in the workspace. *) default_env : Env_node.t Memo.Lazy.t @@ -207,8 +206,6 @@ let build_dir t = t.context.build_dir let profile t = t.context.profile -let external_lib_deps_mode t = t.external_lib_deps_mode - let equal = (( == ) : t -> t -> bool) let hash t = Context.hash t.context @@ -415,13 +412,11 @@ let get_installed_binaries stanzas ~(context : Context.t) = acc | _ -> acc) -let create ~(context : Context.t) ?host ~projects ~packages ~stanzas - ~external_lib_deps_mode = +let create ~(context : Context.t) ?host ~projects ~packages ~stanzas = let lib_config = Context.lib_config context in let installed_libs = let stdlib_dir = context.stdlib_dir in Lib.DB.create_from_findlib context.findlib ~stdlib_dir - ~external_lib_deps_mode in let scopes, public_libs = Scope.DB.create_from_stanzas ~projects ~context ~installed_libs ~lib_config @@ -528,7 +523,6 @@ let create ~(context : Context.t) ?host ~projects ~packages ~stanzas Lib_name.compare (Lib_entry.name a) (Lib_entry.name b))) ; env_tree ; default_env - ; external_lib_deps_mode ; dir_status_db ; projects_by_key } diff --git a/src/dune/super_context.mli b/src/dune/super_context.mli index bc02452c0779..22ed28de8bf6 100644 --- a/src/dune/super_context.mli +++ b/src/dune/super_context.mli @@ -16,7 +16,6 @@ val create : -> projects:Dune_project.t list -> packages:Package.t Package.Name.Map.t -> stanzas:Dune_load.Dune_file.t list - -> external_lib_deps_mode:bool -> t val context : t -> Context.t @@ -36,8 +35,6 @@ val profile : t -> Profile.t val host : t -> t -val external_lib_deps_mode : t -> bool - module Lib_entry : sig type t = | Library of Lib.Local.t