Skip to content

Commit

Permalink
Add tests for c_flags in env
Browse files Browse the repository at this point in the history
Signed-off-by: Greta Yorsh <[email protected]>
  • Loading branch information
gretay-js committed Dec 21, 2018
1 parent e5b7441 commit c9acd0b
Show file tree
Hide file tree
Showing 9 changed files with 80 additions and 1 deletion.
15 changes: 14 additions & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -279,7 +279,20 @@ let cxx_flags_gather t ~dir ~(lib : Library.t) ccg =
let local_binaries t ~dir = Env.local_binaries t ~dir

let dump_env t ~dir =
Ocaml_flags.dump (Env.ocaml_flags t ~dir)
let open Build.O in
let o_dump = Ocaml_flags.dump (Env.ocaml_flags t ~dir) in
let c_flags = Env.c_flags t ~dir in
let cxx_flags = Env.cxx_flags t ~dir in
let c_dump =
Build.fanout c_flags cxx_flags
>>^ fun (c_flags, cxx_flags) ->
List.map ~f:Dune_lang.Encoder.(pair string (list string))
[ "c_flags", c_flags
; "cxx_flags", cxx_flags
]
in (* combine o_dump and c_dump *)
(o_dump &&& c_dump) >>^ (fun (x, y) -> x @ y)


let resolve_program t ~dir ?hint ~loc bin =
let artifacts = Env.artifacts_host t ~dir in
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 @@ -255,6 +255,14 @@
test-cases/env-bins
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

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

(alias
(name env-dune-file)
(deps (package dune) (source_tree test-cases/env-dune-file))
Expand Down Expand Up @@ -1243,6 +1251,7 @@
(alias env)
(alias env-and-flags-include)
(alias env-bins)
(alias env-cflags)
(alias env-dune-file)
(alias env-tracking)
(alias env-var-expansion)
Expand Down Expand Up @@ -1393,6 +1402,7 @@
(alias env)
(alias env-and-flags-include)
(alias env-bins)
(alias env-cflags)
(alias env-dune-file)
(alias env-tracking)
(alias env-var-expansion)
Expand Down
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/env-cflags/bin/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(env
(default
(c_flags "in bin")
(cxx_flags "in bin")))
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/env-cflags/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(env
(default
(c_flags :standard ":standard + in .")
(cxx_flags :standard ":standard + in .")))
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/env-cflags/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.0)
26 changes: 26 additions & 0 deletions test/blackbox-tests/test-cases/env-cflags/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
$ dune printenv --profile default .
(
(flags (-w -40))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags (":standard + in ."))
(cxx_flags (":standard + in ."))
)

$ dune printenv --profile default src
(
(flags (-w -40))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags (":standard + in ." ":standard + in src"))
(cxx_flags (":standard + in ." ":standard + in src"))
)

$ dune printenv --profile default bin
(
(flags (-w -40))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ("in bin"))
(cxx_flags ("in bin"))
)
5 changes: 5 additions & 0 deletions test/blackbox-tests/test-cases/env-cflags/src/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(env
(default
(c_flags :standard ":standard + in src")
(cxx_flags :standard ":standard + in src")
))
14 changes: 14 additions & 0 deletions test/blackbox-tests/test-cases/env/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -3,24 +3,32 @@
(flags (-w -40 ":standard + in ."))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)
$ dune printenv --profile default src
(
(flags (-w -40 ":standard + in ." ":standard + in src"))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)
$ dune printenv --profile default bin
(
(flags ("in bin"))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)
$ dune printenv --profile default vendor
(
(flags (-w -40 ":standard + in ."))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)

Vendored project without env customization, the global default should
Expand All @@ -31,6 +39,8 @@ apply:
(flags (-w -40))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)

Vendored project with env customization, the global default +
Expand All @@ -41,11 +51,15 @@ customization of vendored project should apply:
(flags (-w -40 ":standard + in vendor/with-env-customization"))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)
$ dune printenv --profile default vendor/with-env-customization/src
(
(flags ("in vendor/with-env-customization/src"))
(ocamlc_flags (-g))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)

2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/workspaces/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -61,4 +61,6 @@ Workspaces also allow you to set the env for a context:
(flags (-w -40 -machin))
(ocamlc_flags (-g -verbose))
(ocamlopt_flags (-g))
(c_flags ())
(cxx_flags ())
)

0 comments on commit c9acd0b

Please sign in to comment.