Skip to content

Commit

Permalink
Add type for ctx.ccomp_type
Browse files Browse the repository at this point in the history
This avoid the string check for msvc everywhere

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Oct 31, 2019
1 parent bfa2b76 commit e5188b7
Show file tree
Hide file tree
Showing 4 changed files with 40 additions and 17 deletions.
28 changes: 22 additions & 6 deletions src/dune/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,22 @@ module Env_nodes = struct
(Dune_env.Stanza.find env_nodes.workspace ~profile).env_vars
end

module Ccomp_type = struct
type t =
| Msvc
| Other of string

let to_dyn =
let open Dyn.Encoder in
function
| Msvc -> constr "Msvc" []
| Other s -> constr "Other" [string s]

let of_string = function
| "msvc" -> Msvc
| s -> Other s
end

type t =
{ name : Context_name.t
; kind : Kind.t
Expand Down Expand Up @@ -63,7 +79,7 @@ type t =
; version_string : string
; version : Ocaml_version.t
; stdlib_dir : Path.t
; ccomp_type : string
; ccomp_type : Ccomp_type.t
; c_compiler : string
; ocamlc_cflags : string list
; ocamlopt_cflags : string list
Expand Down Expand Up @@ -474,6 +490,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
in
if Option.is_some fdo_target_exe then
check_fdo_support lib_config.has_native ocfg ~name;
let ccomp_type = Ccomp_type.of_string (Ocaml_config.ccomp_type ocfg) in
let t =
{ name
; implicit
Expand Down Expand Up @@ -508,7 +525,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
; ocaml_config = ocfg
; version_string
; version
; ccomp_type = Ocaml_config.ccomp_type ocfg
; ccomp_type
; c_compiler = Ocaml_config.c_compiler ocfg
; ocamlc_cflags = Ocaml_config.ocamlc_cflags ocfg
; ocamlopt_cflags = Ocaml_config.ocamlopt_cflags ocfg
Expand Down Expand Up @@ -788,10 +805,9 @@ let best_mode t : Mode.t =
| None -> Byte

let cc_g (ctx : t) =
if ctx.ccomp_type <> "msvc" then
[ "-g" ]
else
[]
match ctx.ccomp_type with
| Msvc -> []
| Other _ -> ["-g"]

let name t = t.name

Expand Down
10 changes: 9 additions & 1 deletion src/dune/context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,14 @@ module Env_nodes : sig
}
end

module Ccomp_type : sig
type t =
| Msvc
| Other of string

val to_dyn : t -> Dyn.t
end

type t =
{ name : Context_name.t
; kind : Kind.t
Expand Down Expand Up @@ -81,7 +89,7 @@ type t =
; version_string : string
; version : Ocaml_version.t
; stdlib_dir : Path.t
; ccomp_type : string
; ccomp_type : Ccomp_type.t
; c_compiler : string
; ocamlc_cflags : string list
; ocamlopt_cflags : string list
Expand Down
6 changes: 3 additions & 3 deletions src/dune/foreign_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -90,10 +90,10 @@ let build_cxx_file ~sctx ~dir ~expander ~include_flags (loc, src, dst) =
let flags = Foreign.Source.flags src in
let ctx = Super_context.context sctx in
let output_param =
if ctx.ccomp_type = "msvc" then
match ctx.ccomp_type with
| Msvc ->
[ Command.Args.Concat ("", [ A "/Fo"; Target dst ]) ]
else
[ A "-o"; Target dst ]
| Other _ -> [ A "-o"; Target dst ]
in
let cxx_flags =
Super_context.foreign_flags sctx ~dir ~expander ~flags
Expand Down
13 changes: 6 additions & 7 deletions src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,10 +34,9 @@ let build_lib (lib : Library.t) ~sctx ~expander ~flags ~dir ~mode ~cm_files =
in
let map_cclibs =
(* https://github.com/ocaml/dune/issues/119 *)
if ctx.ccomp_type = "msvc" then
msvc_hack_cclibs
else
Fn.id
match ctx.ccomp_type with
| Msvc -> msvc_hack_cclibs
| Other _ -> Fn.id
in
let obj_deps =
Build.paths (Cm_files.unsorted_objects_and_cms cm_files ~mode)
Expand Down Expand Up @@ -135,11 +134,11 @@ let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files
case, but we pass them unconditionally for simplicity. *)
(Build.map cclibs_args ~f:(fun cclibs ->
(* https://github.com/ocaml/dune/issues/119 *)
if ctx.ccomp_type = "msvc" then
match ctx.ccomp_type with
| Msvc ->
let cclibs = msvc_hack_cclibs cclibs in
Command.quote_args "-ldopt" cclibs
else
As cclibs))
| Other _ -> As cclibs))
; Hidden_targets targets
])
in
Expand Down

0 comments on commit e5188b7

Please sign in to comment.