diff --git a/src/dune/context.ml b/src/dune/context.ml index 17292adcf21a..dac7f165ae4f 100644 --- a/src/dune/context.ml +++ b/src/dune/context.ml @@ -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 @@ -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 @@ -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 @@ -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 @@ -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 diff --git a/src/dune/context.mli b/src/dune/context.mli index 7346e5df5cda..fca32523b713 100644 --- a/src/dune/context.mli +++ b/src/dune/context.mli @@ -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 @@ -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 diff --git a/src/dune/foreign_rules.ml b/src/dune/foreign_rules.ml index b085eb935b4f..b5801cfbbbaa 100644 --- a/src/dune/foreign_rules.ml +++ b/src/dune/foreign_rules.ml @@ -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 diff --git a/src/dune/lib_rules.ml b/src/dune/lib_rules.ml index b11f30f8d70f..8bfb88747808 100644 --- a/src/dune/lib_rules.ml +++ b/src/dune/lib_rules.ml @@ -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) @@ -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