Skip to content

Commit

Permalink
remove cxx_flags_orig from super_context
Browse files Browse the repository at this point in the history
Signed-off-by: Greta Yorsh <gyorsh@janestreet.com>
  • Loading branch information
gretay-js committed Dec 21, 2018
1 parent 55a4d22 commit 61045a5
Show file tree
Hide file tree
Showing 7 changed files with 6 additions and 15 deletions.
4 changes: 2 additions & 2 deletions src/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ let expand_var_exn t var syn =
(String_with_vars.Var.describe var))

let make ~scope ~(context : Context.t) ~artifacts
~artifacts_host ~cxx_flags =
~artifacts_host =
let expand_var ({ bindings; ocaml_config; env = _; scope
; hidden_env = _
; dir = _ ; artifacts = _; expand_var = _
Expand All @@ -111,7 +111,7 @@ let make ~scope ~(context : Context.t) ~artifacts
in
let ocaml_config = lazy (make_ocaml_config context.ocaml_config) in
let dir = context.build_dir in
let bindings = Pform.Map.create ~context ~cxx_flags in
let bindings = Pform.Map.create ~context in
let env = context.env in
{ dir
; hidden_env = Env.Var.Set.empty
Expand Down
1 change: 0 additions & 1 deletion src/expander.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ val make
-> context:Context.t
-> artifacts:Artifacts.t
-> artifacts_host:Artifacts.t
-> cxx_flags:string list
-> t

val set_env : t -> var:string -> value:string -> t
Expand Down
1 change: 0 additions & 1 deletion src/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,6 @@ module Gen (P : Install_rules.Params) = struct
~dir:(Path.parent_exn src)
(SC.resolve_program ~loc:None ~dir sctx ctx.c_compiler)
([ S [A "-I"; Path ctx.stdlib_dir]
; As (SC.cxx_flags_orig sctx)
; includes
; Dyn (fun cxx_flags -> As cxx_flags)
] @ output_param @
Expand Down
4 changes: 3 additions & 1 deletion src/pform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,7 @@ module Map = struct
; "env", since ~version:(1, 4) Macro.Env
]

let create ~(context : Context.t) ~cxx_flags =
let create ~(context : Context.t) =
let ocamlopt =
match context.ocamlopt with
| None -> Path.relative context.ocaml_bin "ocamlopt"
Expand All @@ -168,6 +168,8 @@ module Map = struct
| Some p -> path p
in
let cflags = context.ocamlc_cflags in
let cxx_flags = List.filter context.ocamlc_cflags
~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in
let strings s = values (Value.L.strings s) in
let lowercased =
[ "cpp" , strings (context.c_compiler :: cflags @ ["-E"])
Expand Down
2 changes: 1 addition & 1 deletion src/pform.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ end
module Map : sig
type t

val create : context:Context.t -> cxx_flags:string list -> t
val create : context:Context.t -> t

val superpose : t -> t -> t

Expand Down
8 changes: 0 additions & 8 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ type t =
; packages : Package.t Package.Name.Map.t
; file_tree : File_tree.t
; artifacts : Artifacts.t
; cxx_flags_orig : string list
; expander : Expander.t
; chdir : (Action.t, Action.t) Build.t
; host : t option
Expand All @@ -37,7 +36,6 @@ let packages t = t.packages
let libs_by_package t = t.libs_by_package
let artifacts t = t.artifacts
let file_tree t = t.file_tree
let cxx_flags_orig t = t.cxx_flags_orig
let build_dir t = t.context.build_dir
let profile t = t.context.profile
let build_system t = t.build_system
Expand Down Expand Up @@ -347,10 +345,6 @@ let create
let artifacts =
Artifacts.create context ~public_libs ~build_system
in
let cxx_flags_orig =
List.filter context.ocamlc_cflags
~f:(fun s -> not (String.is_prefix s ~prefix:"-std="))
in
let default_env = lazy (
let make ~inherit_from ~config =
Env_node.make
Expand Down Expand Up @@ -382,7 +376,6 @@ let create
~context
~artifacts
~artifacts_host
~cxx_flags:cxx_flags_orig
in
let dir_status_db = Dir_status.DB.make file_tree ~stanzas_per_dir in
{ context
Expand All @@ -397,7 +390,6 @@ let create
; packages
; file_tree
; artifacts
; cxx_flags_orig
; chdir = Build.arr (fun (action : Action.t) ->
match action with
| Chdir _ -> action
Expand Down
1 change: 0 additions & 1 deletion src/super_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,6 @@ val packages : t -> Package.t Package.Name.Map.t
val libs_by_package : t -> (Package.t * Lib.Set.t) Package.Name.Map.t
val file_tree : t -> File_tree.t
val artifacts : t -> Artifacts.t
val cxx_flags_orig : t -> string list
val build_dir : t -> Path.t
val profile : t -> string
val host : t -> t
Expand Down

0 comments on commit 61045a5

Please sign in to comment.