Skip to content

Commit

Permalink
Adds a new 'instrumentation' setting in env stanza
Browse files Browse the repository at this point in the history
Signed-off-by: Marc Lasson <[email protected]>
  • Loading branch information
mlasson committed Jun 25, 2019
1 parent 8c278d0 commit 2370365
Show file tree
Hide file tree
Showing 5 changed files with 43 additions and 2 deletions.
9 changes: 9 additions & 0 deletions src/dune_env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module Stanza = struct
; c_flags : Ordered_set_lang.Unexpanded.t C.Kind.Dict.t
; env_vars : Env.t
; binaries : File_binding.Unexpanded.t list
; instrumentation: String_with_vars.t option
}

type pattern =
Expand All @@ -30,6 +31,12 @@ module Stanza = struct
; rules : (pattern * config) list
}

let instrumentation_field =
field_o
"instrumentation"
(Syntax.since Stanza.syntax (1, 10) >>>
String_with_vars.decode)

let env_vars_field =
field
"env-vars"
Expand All @@ -48,11 +55,13 @@ module Stanza = struct
and+ binaries = field ~default:[] "binaries"
(Syntax.since Stanza.syntax (1, 6)
>>> File_binding.Unexpanded.L.decode)
and+ instrumentation = instrumentation_field
in
{ flags
; c_flags
; env_vars
; binaries
; instrumentation
}

let rule =
Expand Down
1 change: 1 addition & 0 deletions src/dune_env.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module Stanza : sig
; c_flags : Ordered_set_lang.Unexpanded.t C.Kind.Dict.t
; env_vars : Env.t
; binaries : File_binding.Unexpanded.t list
; instrumentation: String_with_vars.t option
}

type pattern =
Expand Down
21 changes: 20 additions & 1 deletion src/env_node.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@ type t =
; mutable ocaml_flags : Ocaml_flags.t option
; mutable c_flags : (unit, string list) Build.t C.Kind.Dict.t option
; mutable external_ : Env.t option
; mutable bin_artifacts : Artifacts.Bin.t option
; mutable bin_artifacts : Artifacts.Bin.t option
; mutable instrumentation : string option;
}

let scope t = t.scope
Expand All @@ -24,6 +25,7 @@ let make ~dir ~inherit_from ~scope ~config =
; external_ = None
; bin_artifacts = None
; local_binaries = None
; instrumentation = None
}

let find_config t ~profile =
Expand Down Expand Up @@ -121,6 +123,23 @@ let rec ocaml_flags t ~profile ~expander =
t.ocaml_flags <- Some flags;
flags

let instrumentation t ~profile ~expander =
match t.instrumentation with
| Some x -> x
| None ->
let flags =
match find_config t ~profile with
| None | Some {instrumentation = None; _} ->
if profile = "release" then
"disabled"
else
"enabled"
| Some {instrumentation = Some s; _} ->
Expander.expand_str expander s
in
t.instrumentation <- Some flags;
flags

let rec c_flags t ~profile ~expander ~default_context_flags =
match t.c_flags with
| Some x -> x
Expand Down
2 changes: 2 additions & 0 deletions src/env_node.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ val external_ : t -> profile:string -> default:Env.t -> Env.t

val ocaml_flags : t -> profile:string -> expander:Expander.t -> Ocaml_flags.t

val instrumentation : t -> profile:string -> expander:Expander.t -> string

val c_flags
: t
-> profile:string
Expand Down
12 changes: 11 additions & 1 deletion src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,10 @@ end = struct
in
Env_node.local_binaries node ~profile:t.profile ~expander

let instrumentation ({expander; profile; _} as t) ~dir =
let node = get t ~dir in
Env_node.instrumentation node ~expander ~profile

let bin_artifacts t ~dir =
let expander =
expander_for_artifacts t ~context_expander:t.expander ~dir
Expand All @@ -174,7 +178,13 @@ end = struct
expander_for_artifacts t ~context_expander:t.expander ~dir
in
let bin_artifacts_host = bin_artifacts_host t ~dir in
Expander.set_bin_artifacts expander ~bin_artifacts_host
let bindings =
Pform.Map.singleton "instrumentation"
(Values [String (instrumentation t ~dir)])
in
expander
|> Expander.add_bindings ~bindings
|> Expander.set_bin_artifacts ~bin_artifacts_host

let ocaml_flags t ~dir =
Env_node.ocaml_flags (get t ~dir)
Expand Down

0 comments on commit 2370365

Please sign in to comment.