Skip to content

Commit

Permalink
Do not build and install shared libs when not supported (#1165)
Browse files Browse the repository at this point in the history
Read `ocamlc -where`/Makefile.config to determine whether this is
supported.

Signed-off-by: Jeremie Dimino <jeremie@dimino.org>
  • Loading branch information
jeremiedimino authored Aug 22, 2018
1 parent f59c547 commit c87d8e9
Show file tree
Hide file tree
Showing 14 changed files with 172 additions and 77 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,9 @@ next

- Highlight multi-line errors (#1131, @anuragsoni)

- Do no try to generate shared libraries when this is not supported by
the OS (#1165, fix #1051, @diml)

1.1.1 (08/08/2018)
------------------

Expand Down
23 changes: 17 additions & 6 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ type t =
; findlib_toolchain : string option
; arch_sixtyfour : bool
; opam_var_cache : (string, string) Hashtbl.t
; natdynlink_supported : bool
; natdynlink_supported : Dynlink_supported.By_the_os.t
; ocaml_config : Ocaml_config.t
; version_string : string
; version : Ocaml_version.t
Expand Down Expand Up @@ -81,6 +81,7 @@ type t =
; ast_intf_magic_number : string
; cmxs_magic_number : string
; cmt_magic_number : string
; supports_shared_libraries : Dynlink_supported.By_the_os.t
; which_cache : (string, Path.t option) Hashtbl.t
}

Expand All @@ -104,7 +105,10 @@ let sexp_of_t t =
; "env", Env.sexp_of_t (Env.diff t.env Env.initial)
; "findlib_path", list path (Findlib.path t.findlib)
; "arch_sixtyfour", bool t.arch_sixtyfour
; "natdynlink_supported", bool t.natdynlink_supported
; "natdynlink_supported",
bool (Dynlink_supported.By_the_os.get t.natdynlink_supported)
; "supports_shared_libraries",
bool (Dynlink_supported.By_the_os.get t.supports_shared_libraries)
; "opam_vars", string_hashtbl string t.opam_var_cache
; "ocaml_config", Ocaml_config.sexp_of_t t.ocaml_config
; "which", string_hashtbl (option path) t.which_cache
Expand Down Expand Up @@ -260,19 +264,22 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
in
let ocaml_config_ok_exn = function
| Ok x -> x
| Error msg ->
| Error (Ocaml_config.Origin.Ocamlc_config, msg) ->
die "Failed to parse the output of '%s -config':@\n\
%s"
(Path.to_string ocamlc) msg
| Error (Makefile_config file, msg) ->
Loc.fail (Loc.in_file (Path.to_string file)) "%s" msg
in
Fiber.fork_and_join
findlib_path
(fun () ->
Process.run_capture_lines ~env Strict ocamlc ["-config"]
>>| fun lines ->
let open Result.O in
ocaml_config_ok_exn
(Ocaml_config.Vars.of_lines lines >>= Ocaml_config.make))
(match Ocaml_config.Vars.of_lines lines with
| Ok vars -> Ocaml_config.make vars
| Error msg -> Error (Ocamlc_config, msg)))
>>= fun (findlib_path, ocfg) ->
let version = Ocaml_version.of_ocaml_config ocfg in
let env =
Expand Down Expand Up @@ -368,7 +375,8 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets

; opam_var_cache

; natdynlink_supported
; natdynlink_supported =
Dynlink_supported.By_the_os.of_bool natdynlink_supported

; stdlib_dir
; ocaml_config = ocfg
Expand Down Expand Up @@ -403,6 +411,9 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
; ast_intf_magic_number = Ocaml_config.ast_intf_magic_number ocfg
; cmxs_magic_number = Ocaml_config.cmxs_magic_number ocfg
; cmt_magic_number = Ocaml_config.cmt_magic_number ocfg
; supports_shared_libraries =
Dynlink_supported.By_the_os.of_bool
(Ocaml_config.supports_shared_libraries ocfg)

; which_cache
}
Expand Down
4 changes: 3 additions & 1 deletion src/context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ type t =
; opam_var_cache : (string, string) Hashtbl.t

; (** Native dynlink *)
natdynlink_supported : bool
natdynlink_supported : Dynlink_supported.By_the_os.t

; ocaml_config : Ocaml_config.t
; version_string : string
Expand Down Expand Up @@ -122,6 +122,8 @@ type t =
; cmxs_magic_number : string
; cmt_magic_number : string

; supports_shared_libraries : Dynlink_supported.By_the_os.t

; which_cache : (string, Path.t option) Hashtbl.t
}

Expand Down
4 changes: 2 additions & 2 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -913,7 +913,7 @@ module Library = struct
; wrapped : bool
; optional : bool
; buildable : Buildable.t
; dynlink : bool
; dynlink : Dynlink_supported.t
; project : Dune_project.t
; sub_systems : Sub_system_info.t Sub_system_name.Map.t
; no_keep_locs : bool
Expand Down Expand Up @@ -999,7 +999,7 @@ module Library = struct
; wrapped
; optional
; buildable
; dynlink = not no_dynlink
; dynlink = Dynlink_supported.of_bool (not no_dynlink)
; project
; sub_systems
; no_keep_locs
Expand Down
2 changes: 1 addition & 1 deletion src/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,7 @@ module Library : sig
; wrapped : bool
; optional : bool
; buildable : Buildable.t
; dynlink : bool
; dynlink : Dynlink_supported.t
; project : Dune_project.t
; sub_systems : Sub_system_info.t Sub_system_name.Map.t
; no_keep_locs : bool
Expand Down
9 changes: 9 additions & 0 deletions src/dynlink_supported.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
module By_the_os = struct
type t = bool
let of_bool t = t
let get t = t
end

type t = bool
let of_bool t = t
let get x y = x && y
11 changes: 11 additions & 0 deletions src/dynlink_supported.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
(** Track whether dynamic loading of code is supported *)

module By_the_os : sig
type t
val of_bool : bool -> t
val get : t -> bool
end

type t
val of_bool : bool -> t
val get : t -> By_the_os.t -> bool
5 changes: 3 additions & 2 deletions src/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ module Gen(P : Params) = struct
; Library.archive ~dir lib ~ext:ctx.ext_lib
]
in
if ctx.natdynlink_supported && lib.dynlink then
if Dynlink_supported.get lib.dynlink ctx.natdynlink_supported then
files @ [ Library.archive ~dir lib ~ext:".cmxs" ]
else
files)
Expand All @@ -178,7 +178,8 @@ module Gen(P : Params) = struct
]
in
let dlls =
if_ (byte && Library.has_stubs lib && lib.dynlink)
if_ (byte && Library.has_stubs lib &&
Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries)
[Library.dll ~dir lib ~ext_dll:ctx.ext_dll]
in
let execs =
Expand Down
8 changes: 5 additions & 3 deletions src/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ module Gen (P : Install_rules.Params) = struct
let ocamlmklib = ocamlmklib lib ~scope ~dir ~o_files in
if modes.native &&
modes.byte &&
lib.dynlink
Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries
then begin
(* If we build for both modes and support dynlink, use a
single invocation to build both the static and dynamic
Expand Down Expand Up @@ -340,7 +340,9 @@ module Gen (P : Install_rules.Params) = struct

let dep_graphs = Ocamldep.rules cctx in

let dynlink = lib.dynlink in
let dynlink =
Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries
in
let js_of_ocaml = lib.buildable.js_of_ocaml in
Module_compilation.build_modules cctx ~js_of_ocaml ~dynlink ~dep_graphs;

Expand Down Expand Up @@ -385,7 +387,7 @@ module Gen (P : Install_rules.Params) = struct
let target = Path.extend_basename src ~suffix:".js" in
Js_of_ocaml_rules.build_cm cctx ~js_of_ocaml ~src ~target);

if ctx.natdynlink_supported then
if Dynlink_supported.By_the_os.get ctx.natdynlink_supported then
build_shared lib ~dir ~flags ~ctx;

Odoc.setup_library_odoc_rules lib ~requires ~modules ~dep_graphs ~scope;
Expand Down
129 changes: 84 additions & 45 deletions src/ocaml-config/ocaml_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -82,6 +82,7 @@ type t =
; cmxs_magic_number : string
; cmt_magic_number : string
; natdynlink_supported : bool
; supports_shared_libraries : bool
}

let version t = t.version
Expand Down Expand Up @@ -131,6 +132,7 @@ let ast_intf_magic_number t = t.ast_intf_magic_number
let cmxs_magic_number t = t.cmxs_magic_number
let cmt_magic_number t = t.cmt_magic_number
let natdynlink_supported t = t.natdynlink_supported
let supports_shared_libraries t = t.supports_shared_libraries

let to_list t : (string * Value.t) list =
[ "version" , String t.version_string
Expand Down Expand Up @@ -179,6 +181,7 @@ let to_list t : (string * Value.t) list =
; "cmxs_magic_number" , String t.cmxs_magic_number
; "cmt_magic_number" , String t.cmt_magic_number
; "natdynlink_supported" , Bool t.natdynlink_supported
; "supports_shared_libraries", Bool t.supports_shared_libraries
]

let sexp_of_t t =
Expand All @@ -189,9 +192,11 @@ let sexp_of_t t =
; Value.sexp_of_t v
]))

exception E of string
let fail fmt =
Printf.ksprintf (fun msg -> raise (E msg)) fmt
module Origin = struct
type t =
| Ocamlc_config
| Makefile_config of Path.t
end

let split_prog s =
match String.extract_blank_separated_words s with
Expand All @@ -209,7 +214,11 @@ module Vars = struct
| Some i ->
let x =
(String.sub line ~pos:0 ~len:i,
String.sub line ~pos:(i + 2) ~len:(String.length line - i - 2))
let len = String.length line - i - 2 in
if len < 0 then
""
else
String.sub line ~pos:(i + 2) ~len)
in
loop (x :: acc) lines
| None ->
Expand All @@ -219,51 +228,71 @@ module Vars = struct
Result.map_error (String.Map.of_list vars) ~f:(fun (var, _, _) ->
Printf.sprintf "Variable %S present twice." var)

let get_opt t var = String.Map.find t var
let load_makefile_config file =
let lines = Io.lines_of_file file in
List.filter_map lines ~f:(fun line ->
let line = String.trim line in
if line = "" || line.[0] = '#' then
None
else
String.lsplit2 line ~on:'=')
|> String.Map.of_list_reduce ~f:(fun _ x -> x)

exception E of Origin.t * string

let get t var =
match get_opt t var with
| Some s -> s
| None -> fail "Variable %S not found." var
module Getters(Origin : sig val origin : Origin.t end) = struct
let fail fmt =
Printf.ksprintf (fun msg -> raise (E (Origin.origin, msg))) fmt

let get_bool t var =
match get_opt t var with
| None -> false
| Some s ->
match s with
| "true" -> true
| "false" -> false
| s ->
fail "Value of %S is neither 'true' neither 'false': %s." var s
let get_opt t var = String.Map.find t var

let get_int_opt t var =
match get_opt t var with
| None -> None
| Some s ->
match int_of_string s with
| x -> Some x
| exception _ ->
fail "Value of %S is not an integer: %s." var s
let get t var =
match get_opt t var with
| Some s -> s
| None -> fail "Variable %S not found." var

let get_words t var =
match get_opt t var with
| None -> []
| Some s -> String.extract_blank_separated_words s
let get_bool t ?(default=false) var =
match get_opt t var with
| None -> default
| Some s ->
match s with
| "true" -> true
| "false" -> false
| s ->
fail "Value of %S is neither 'true' neither 'false': %s." var s

let get_prog_or_dummy t var =
Option.map (get_opt t var) ~f:(fun v ->
match split_prog v with
| None ->
{ prog = Printf.sprintf "%s-not-found-in-ocaml-config" var
; args = []
}
let get_int_opt t var =
match get_opt t var with
| None -> None
| Some s ->
match int_of_string s with
| x -> Some x
| exception _ ->
fail "Value of %S is not an integer: %s." var s

let get_words t var =
match get_opt t var with
| None -> []
| Some s -> String.extract_blank_separated_words s

let get_prog_or_dummy t var =
Option.map (get_opt t var) ~f:(fun v ->
match split_prog v with
| None ->
{ prog = Printf.sprintf "%s-not-found-in-ocaml-config" var
; args = []
}
| Some s -> s
)

let get_prog_or_dummy_exn t var =
match get_prog_or_dummy t var with
| None -> fail "Variable %S not found." var
| Some s -> s
)
end

let get_prog_or_dummy_exn t var =
match get_prog_or_dummy t var with
| None -> fail "Variable %S not found." var
| Some s -> s
module Ocamlc_config_getters =
Getters(struct let origin = Origin.Ocamlc_config end)
end

let get_arch_sixtyfour stdlib_dir =
Expand All @@ -287,7 +316,7 @@ let get_arch_sixtyfour stdlib_dir =

let make vars =
match
let open Vars in
let open Vars.Ocamlc_config_getters in
let bytecomp_c_compiler =
get_prog_or_dummy_exn vars "bytecomp_c_compiler" in
let native_c_compiler =
Expand Down Expand Up @@ -369,6 +398,15 @@ let make vars =
let natdynlink_supported =
Sys.file_exists (Filename.concat standard_library "dynlink.cmxa")
in

let file =
Path.relative (Path.of_string standard_library) "Makefile.config"
in
let vars = Vars.load_makefile_config file in
let module Getters =
Vars.Getters(struct let origin = Origin.Makefile_config file end)
in
let supports_shared_libraries = get_bool vars "SUPPORTS_SHARED_LIBRARIES" in
{ version
; version_string
; standard_library_default
Expand Down Expand Up @@ -416,7 +454,8 @@ let make vars =
; cmxs_magic_number
; cmt_magic_number
; natdynlink_supported
; supports_shared_libraries
}
with
| t -> Ok t
| exception (E msg) -> Error msg
| t -> Ok t
| exception (Vars.E (origin, msg)) -> Error (origin, msg)
Loading

0 comments on commit c87d8e9

Please sign in to comment.