Skip to content

Commit 9b58d84

Browse files
committedJan 13, 2021
Add build_context field to context
Now we create the build context only once per context Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
1 parent 4d53aad commit 9b58d84

File tree

6 files changed

+22
-20
lines changed

6 files changed

+22
-20
lines changed
 

‎src/dune_rules/context.ml

+12-8
Original file line numberDiff line numberDiff line change
@@ -97,16 +97,14 @@ module T = struct
9797
; supports_shared_libraries : Dynlink_supported.By_the_os.t
9898
; which : string -> Path.t option
9999
; lib_config : Lib_config.t
100+
; build_context : Build_context.t
100101
}
101102

102103
let equal x y = Context_name.equal x.name y.name
103104

104105
let hash t = Context_name.hash t.name
105106

106-
let rec to_build_context
107-
{ name; build_dir; env; for_host; stdlib_dir; default_ocamlpath; _ } =
108-
Build_context.create ~name ~build_dir ~env ~stdlib_dir ~default_ocamlpath
109-
~host:(Option.map ~f:to_build_context for_host)
107+
let build_context t = t.build_context
110108

111109
let to_dyn t : Dyn.t =
112110
let open Dyn.Encoder in
@@ -419,7 +417,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
419417
| Error (Makefile_config file, msg) ->
420418
User_error.raise ~loc:(Loc.in_file file) [ Pp.text msg ]
421419
in
422-
let* default_findlib_paths, (ocaml_config_vars, ocfg) =
420+
let* default_ocamlpath, (ocaml_config_vars, ocfg) =
423421
Fiber.fork_and_join default_findlib_paths (fun () ->
424422
let+ lines =
425423
Process.run_capture_lines ~env Strict ocamlc [ "-config" ]
@@ -432,7 +430,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
432430
(vars, ocfg)
433431
| Error msg -> Error (Ocamlc_config, msg) ))
434432
in
435-
let findlib_paths = ocamlpath @ default_findlib_paths in
433+
let findlib_paths = ocamlpath @ default_ocamlpath in
436434
let version = Ocaml_version.of_ocaml_config ocfg in
437435
let env =
438436
(* See comment in ansi_color.ml for setup_env_for_colors. For versions
@@ -473,7 +471,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
473471
; ( "DUNE_OCAML_HARDCODED"
474472
, String.concat
475473
~sep:(Char.escaped ocamlpath_sep)
476-
(List.map ~f:Path.to_string default_findlib_paths) )
474+
(List.map ~f:Path.to_string default_ocamlpath) )
477475
; extend_var "OCAMLTOP_INCLUDE_PATH"
478476
(Path.Build.relative local_lib_root "toplevel")
479477
; extend_var "OCAMLFIND_IGNORE_DUPS_IN" ~path_sep:ocamlpath_sep
@@ -545,6 +543,11 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
545543
supports_shared_libraries && dynamically_linked_foreign_archives
546544
in
547545
let t =
546+
let build_context =
547+
Build_context.create ~name ~build_dir ~env ~stdlib_dir
548+
~default_ocamlpath
549+
~host:(Option.map host ~f:(fun c -> c.build_context))
550+
in
548551
{ name
549552
; implicit
550553
; kind
@@ -570,7 +573,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
570573
; env
571574
; findlib = Findlib.create ~paths:findlib_paths ~lib_config
572575
; findlib_toolchain
573-
; default_ocamlpath = default_findlib_paths
576+
; default_ocamlpath
574577
; arch_sixtyfour
575578
; install_prefix
576579
; stdlib_dir
@@ -581,6 +584,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
581584
Dynlink_supported.By_the_os.of_bool supports_shared_libraries
582585
; which
583586
; lib_config
587+
; build_context
584588
}
585589
in
586590
if Ocaml_version.supports_response_file version then (

‎src/dune_rules/context.mli

+2-1
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ type t = private
9494
(** Given a program name, e.g. ["ocaml"], find the path to a preferred
9595
executable in PATH, e.g. [Some "/path/to/ocaml.opt.exe"]. *)
9696
; lib_config : Lib_config.t
97+
; build_context : Build_context.t
9798
}
9899

99100
val equal : t -> t -> bool
@@ -130,7 +131,7 @@ val lib_config : t -> Lib_config.t
130131
the host build context. Otherwise, it just returns [exe]. *)
131132
val map_exe : t -> Path.t -> Path.t
132133

133-
val to_build_context : t -> Build_context.t
134+
val build_context : t -> Build_context.t
134135

135136
val init_configurator : t -> unit
136137

‎src/dune_rules/dep_conf_eval.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ let dep expander = function
5050
| Some pkg ->
5151
Build.alias
5252
(Build_system.Alias.package_install
53-
~context:(Context.to_build_context context)
53+
~context:(Context.build_context context)
5454
~pkg)
5555
| None ->
5656
Build.fail

‎src/dune_rules/install_rules.ml

+4-7
Original file line numberDiff line numberDiff line change
@@ -741,23 +741,20 @@ let install_rules sctx (package : Package.t) =
741741
]
742742
in
743743
let () =
744+
let context = Context.build_context ctx in
744745
let target_alias =
745-
Build_system.Alias.package_install
746-
~context:(Context.to_build_context ctx)
747-
~pkg:package
746+
Build_system.Alias.package_install ~context ~pkg:package
748747
in
749748
Rules.Produce.Alias.add_deps target_alias files
750749
~dyn_deps:
751750
(let+ packages = packages in
752751
Package.Id.Set.to_list packages
753752
|> Path.Set.of_list_map ~f:(fun (pkg : Package.Id.t) ->
754-
let name = Package.Id.name pkg in
755753
let pkg =
754+
let name = Package.Id.name pkg in
756755
Package.Name.Map.find_exn (Super_context.packages sctx) name
757756
in
758-
Build_system.Alias.package_install
759-
~context:(Context.to_build_context ctx)
760-
~pkg
757+
Build_system.Alias.package_install ~context ~pkg
761758
|> Alias.stamp_file |> Path.build))
762759
in
763760
let action =

‎src/dune_rules/main.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ let init_build_system ?only_packages ~sandboxing_preference ?caching w =
8080
Artifact_substitution.copy_file ?chmod ~src ~dst ~conf ()
8181
in
8282
Build_system.init ~sandboxing_preference ~promote_source
83-
~contexts:(List.map ~f:Context.to_build_context w.contexts)
83+
~contexts:(List.map ~f:Context.build_context w.contexts)
8484
?caching ();
8585
List.iter w.contexts ~f:Context.init_configurator;
8686
let+ scontexts = Gen_rules.gen w.conf ~contexts:w.contexts ?only_packages in

‎src/dune_rules/super_context.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -292,7 +292,7 @@ let make_rule t ?sandbox ?mode ?locks ?loc ~dir build =
292292
let build = chdir_to_build_context_root t build in
293293
let env = get_node t.env_tree ~dir |> Env_node.external_env in
294294
Rule.make ?sandbox ?mode ?locks ~info:(Rule.Info.of_loc_opt loc)
295-
~context:(Some (Context.to_build_context t.context))
295+
~context:(Some (Context.build_context t.context))
296296
~env:(Some env) build
297297

298298
let add_rule t ?sandbox ?mode ?locks ?loc ~dir build =
@@ -310,7 +310,7 @@ let add_rules t ?sandbox ~dir builds =
310310
let add_alias_action t alias ~dir ~loc ?locks ~stamp action =
311311
let env = Some (get_node t.env_tree ~dir |> Env_node.external_env) in
312312
Rules.Produce.Alias.add_action
313-
~context:(Context.to_build_context t.context)
313+
~context:(Context.build_context t.context)
314314
~env alias ~loc ?locks ~stamp action
315315

316316
let build_dir_is_vendored build_dir =

0 commit comments

Comments
 (0)
Please sign in to comment.