Skip to content

Commit

Permalink
Add a (env) dependency
Browse files Browse the repository at this point in the history
  • Loading branch information
emillon committed Aug 28, 2018
1 parent fc0d99c commit f8d37fe
Show file tree
Hide file tree
Showing 10 changed files with 68 additions and 0 deletions.
10 changes: 10 additions & 0 deletions src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1284,9 +1284,19 @@ let update_universe t =
make_local_dirs t (Path.Set.singleton Path.build_dir);
Io.write_file universe_file (Dsexp.to_string ~syntax:Dune (Dsexp.To_sexp.int n))

let env_file = Path.relative Path.build_dir ".env"

let update_env_file env =
Marshal.to_string env []
|> Digest.string
|> Digest.to_hex
|> Io.write_file env_file

let do_build t ~request =
entry_point t ~f:(fun () ->
update_universe t;
let env_context = Option.value_exn @@ String.Map.find t.contexts "default" in
update_env_file env_context.env;
eval_request t ~request ~process_target:(wait_for_file ~loc:None t))

module Ir_set = Set.Make(Internal_rule)
Expand Down
3 changes: 3 additions & 0 deletions src/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -195,6 +195,9 @@ val do_build
(** File for the [(universe)] dependency. *)
val universe_file : Path.t

(** File for the [(env)] dependency. *)
val env_file : Path.t

val is_target : t -> Path.t -> bool

(** Return all the library dependencies (as written by the user)
Expand Down
5 changes: 5 additions & 0 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -308,6 +308,7 @@ module Dep_conf = struct
| Source_tree of String_with_vars.t
| Package of String_with_vars.t
| Universe
| Env

let remove_locs = function
| File sw -> File (String_with_vars.remove_locs sw)
Expand All @@ -317,6 +318,7 @@ module Dep_conf = struct
| Source_tree sw -> Source_tree (String_with_vars.remove_locs sw)
| Package sw -> Package (String_with_vars.remove_locs sw)
| Universe -> Universe
| Env -> Env

let dparse =
let dparse =
Expand All @@ -337,6 +339,7 @@ module Dep_conf = struct
(let%map () = Syntax.since Stanza.syntax (1, 0)
and x = sw in
Source_tree x)
; "env", return Env
]
in
if_list
Expand Down Expand Up @@ -365,6 +368,8 @@ module Dep_conf = struct
; String_with_vars.dgen t]
| Universe ->
Dsexp.unsafe_atom_of_string "universe"
| Env ->
Dsexp.unsafe_atom_of_string "env"

let to_sexp t = Dsexp.to_sexp (dgen t)
end
Expand Down
1 change: 1 addition & 0 deletions src/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -119,6 +119,7 @@ module Dep_conf : sig
| Source_tree of String_with_vars.t
| Package of String_with_vars.t
| Universe
| Env

val remove_locs : t -> t

Expand Down
3 changes: 3 additions & 0 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -768,6 +768,9 @@ module Deps = struct
| Universe ->
Build.path Build_system.universe_file
>>^ fun () -> []
| Env ->
Build.path Build_system.env_file
>>^ fun () -> []

let interpret t ~scope ~dir l =
List.map l ~f:(dep t ~scope ~dir)
Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -159,6 +159,14 @@
test-cases/env
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name env-tracking)
(deps (package dune) (source_tree test-cases/env-tracking))
(action
(chdir
test-cases/env-tracking
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name envs-and-contexts)
(deps (package dune) (source_tree test-cases/envs-and-contexts))
Expand Down Expand Up @@ -843,6 +851,7 @@
(alias dune-project-edition)
(alias dup-fields)
(alias env)
(alias env-tracking)
(alias exclude-missing-module)
(alias exec-cmd)
(alias exec-missing)
Expand Down Expand Up @@ -945,6 +954,7 @@
(alias dune-project-edition)
(alias dup-fields)
(alias env)
(alias env-tracking)
(alias exclude-missing-module)
(alias exec-cmd)
(alias exec-missing)
Expand Down
6 changes: 6 additions & 0 deletions test/blackbox-tests/test-cases/env-tracking/a.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
let var k =
match Sys.getenv k with
| v -> Printf.sprintf "%s = %S" k v
| exception Not_found -> Printf.sprintf "%s is not set" k

let () = print_endline @@ var "X"
14 changes: 14 additions & 0 deletions test/blackbox-tests/test-cases/env-tracking/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
(executable
(name a)
)

(alias
(name without_dep)
(action (run ./a.exe))
)

(alias
(name with_dep)
(deps (env))
(action (run ./a.exe))
)
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/env-tracking/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.1)
15 changes: 15 additions & 0 deletions test/blackbox-tests/test-cases/env-tracking/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Aliases without a (env) dependency are not rebuilt when the environment changes:

$ dune build @without_dep
a alias without_dep
X is not set
$ X=x dune build @without_dep

But if there is a dependency, the alias gets rebuilt:

$ dune build @with_dep
a alias with_dep
X is not set
$ X=x dune build @with_dep
a alias with_dep
X = "x"

0 comments on commit f8d37fe

Please sign in to comment.