Skip to content

Commit

Permalink
Merge pull request #3404 from rgrinberg/external-lib-deps-mode
Browse files Browse the repository at this point in the history
Stop passing external lib deps mode
  • Loading branch information
rgrinberg authored Apr 22, 2020
2 parents bbf190f + efe8821 commit ff834f3
Show file tree
Hide file tree
Showing 18 changed files with 36 additions and 44 deletions.
4 changes: 3 additions & 1 deletion bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
15 changes: 10 additions & 5 deletions bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
6 changes: 2 additions & 4 deletions bin/compute.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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 _ ->
Expand Down
4 changes: 2 additions & 2 deletions bin/describe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions bin/external_lib_deps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions bin/print_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
| [] ->
Expand Down
2 changes: 2 additions & 0 deletions src/dune/clflags.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 2 additions & 0 deletions src/dune/clflags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
5 changes: 2 additions & 3 deletions src/dune/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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)
Expand Down
1 change: 0 additions & 1 deletion src/dune/gen_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
2 changes: 1 addition & 1 deletion src/dune/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions src/dune/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand Down
3 changes: 1 addition & 2 deletions src/dune/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
8 changes: 2 additions & 6 deletions src/dune/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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 =
Expand Down
1 change: 0 additions & 1 deletion src/dune/main.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
8 changes: 1 addition & 7 deletions src/dune/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
}
Expand Down
3 changes: 0 additions & 3 deletions src/dune/super_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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
Expand Down

0 comments on commit ff834f3

Please sign in to comment.