Skip to content

Commit

Permalink
Revert "Follow c_compiler links for a better ccomp_type detection"
Browse files Browse the repository at this point in the history
This reverts commit 5df51fd.
  • Loading branch information
voodoos committed Dec 3, 2020
1 parent 7974132 commit 3598cf5
Show file tree
Hide file tree
Showing 7 changed files with 10 additions and 49 deletions.
2 changes: 1 addition & 1 deletion src/dune_rules/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -901,7 +901,7 @@ let best_mode t : Mode.t =
let cc_g (ctx : t) =
match ctx.lib_config.ccomp_type with
| Msvc -> []
| _ -> [ "-g" ]
| Other _ -> [ "-g" ]

let name t = t.name

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/foreign_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) =
let output_param =
match ctx.lib_config.ccomp_type with
| Msvc -> [ Command.Args.Concat ("", [ A "/Fo"; Target dst ]) ]
| _ -> [ A "-o"; Target dst ]
| Other _ -> [ A "-o"; Target dst ]
in
Super_context.add_rule sctx ~loc
~dir
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/lib_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -53,4 +53,4 @@ let get_for_enabled_if t ~var =
let linker_can_create_empty_archives t =
match t.ccomp_type with
| Msvc -> false
| _ -> true
| Other _ -> true
4 changes: 2 additions & 2 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ let build_lib (lib : Library.t) ~sctx ~modules ~expander ~flags ~dir ~mode
(* https://github.com/ocaml/dune/issues/119 *)
match ctx.lib_config.ccomp_type with
| Msvc -> msvc_hack_cclibs
| _ -> Fun.id
| Other _ -> Fun.id
in
let obj_deps =
Build.paths (Cm_files.unsorted_objects_and_cms cm_files ~mode)
Expand Down Expand Up @@ -145,7 +145,7 @@ let ocamlmklib ~loc ~c_library_flags ~sctx ~dir ~expander ~o_files ~archive_name
| Msvc ->
let cclibs = msvc_hack_cclibs cclibs in
Command.quote_args "-ldopt" cclibs
| _ -> As cclibs))
| Other _ -> As cclibs))
; Hidden_targets targets
])
in
Expand Down
2 changes: 1 addition & 1 deletion src/ocaml-config/dune
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
(library
(name ocaml_config)
(public_name dune-private-libs.ocaml-config)
(libraries stdune dune_re dune_lang)
(libraries stdune dune_lang)
(synopsis "[Internal] Interpret the output of 'ocamlc -config'"))
45 changes: 4 additions & 41 deletions src/ocaml-config/ocaml_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -55,57 +55,20 @@ end
module Ccomp_type = struct
type t =
| Msvc
| Gcc
| Clang
| Other of string

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

let readlinks bin =
let path = Env.(path initial) in
let rec aux i start =
(* Enfore same depth limit as (old) linux [path_resolution] *)
if i >= 8 then
start
else
let path =
Bin.which ~path start
|> Option.map ~f:Path.to_absolute_filename
|> Option.value ~default:bin
in
try
let end_ = Unix.readlink path in
if end_ = start then
start
else
aux (i + 1) end_
with Unix.Unix_error _ -> start
in
aux 0 bin

let of_string ~c_compiler ccomp_type =
let re name =
Dune_re.(seq [ rep any; char '-'; str name; rep any ]) |> Dune_re.compile
in
let c_compiler = readlinks c_compiler in
match (ccomp_type, c_compiler) with
| "msvc", _ -> Msvc
| _, "gcc" -> Gcc
| _, "clang" -> Clang
| _, s when Dune_re.execp (re "gcc") s -> Gcc
| _, s when Dune_re.execp (re "clang") s -> Clang
| s, _ -> Other s
let of_string = function
| "msvc" -> Msvc
| s -> Other s

let to_string = function
| Msvc -> "msvc"
| Gcc -> "gcc"
| Clang -> "clang"
| Other s -> s
end

Expand Down Expand Up @@ -493,7 +456,7 @@ let make vars =
(get_opt vars "standard_runtime")
~default:"the_standard_runtime_variable_was_deleted"
in
let ccomp_type = Ccomp_type.of_string ~c_compiler (get vars "ccomp_type") in
let ccomp_type = Ccomp_type.of_string (get vars "ccomp_type") in
let bytecomp_c_libraries = get_words vars "bytecomp_c_libraries" in
let native_c_libraries = get_words vars "native_c_libraries" in
let cc_profile = get_words vars "cc_profile" in
Expand Down
2 changes: 0 additions & 2 deletions src/ocaml-config/ocaml_config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,6 @@ end
module Ccomp_type : sig
type t =
| Msvc
| Gcc
| Clang
| Other of string

val to_dyn : t -> Stdune.Dyn.t
Expand Down

0 comments on commit 3598cf5

Please sign in to comment.