Skip to content

Commit

Permalink
Support new locations of unix, str and dynlink
Browse files Browse the repository at this point in the history
Signed-off-by: David Allsopp <david.allsopp@metastack.com>
  • Loading branch information
dra27 committed May 24, 2022
1 parent dea0387 commit 3f5f4cf
Show file tree
Hide file tree
Showing 7 changed files with 47 additions and 6 deletions.
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
2.9.4 (unreleased)
------------------

- Support new locations of unix, str, dynlink in OCaml >= 5.0 (#5582, @dra27)

2.9.3 (26/01/2022)
------------------

Expand Down
10 changes: 9 additions & 1 deletion boot/duneboot.ml
Original file line number Diff line number Diff line change
Expand Up @@ -572,6 +572,8 @@ module Config : sig
val ocaml_config : unit -> string StringMap.t Fiber.t

val output_complete_obj_arg : string

val unix_library_flags : string list
end = struct
let ocaml_version = Scanf.sscanf Sys.ocaml_version "%d.%d" (fun a b -> (a, b))

Expand Down Expand Up @@ -650,6 +652,12 @@ end = struct
"-custom"
else
"-output-complete-exe"

let unix_library_flags =
if ocaml_version >= (5, 0) then
[ "-I"; "+unix" ]
else
[]
end

let insert_header fn ~header =
Expand Down Expand Up @@ -1031,7 +1039,7 @@ let resolve_externals external_libraries =
let convert = function
| "threads.posix" ->
("threads" ^ Config.ocaml_archive_ext, [ "-I"; "+threads" ])
| "unix" -> ("unix" ^ Config.ocaml_archive_ext, [])
| "unix" -> ("unix" ^ Config.ocaml_archive_ext, Config.unix_library_flags)
| s -> fatal "unhandled external library %s" s
in
let externals = List.map ~f:convert external_libraries in
Expand Down
6 changes: 5 additions & 1 deletion bootstrap.ml
Original file line number Diff line number Diff line change
Expand Up @@ -91,14 +91,18 @@ let () =
(compiler, Some "--secondary")
in
exit_if_non_zero
(runf "%s %s -w -24 -g -o %s -I boot unix.cma %s" compiler
(runf "%s %s -w -24 -g -o %s -I boot %sunix.cma %s" compiler
(* Make sure to produce a self-contained binary as dlls tend to cause
issues *)
(if v < (4, 10, 1) then
"-custom"
else
"-output-complete-exe")
prog
(if v >= (5, 0, 0) then
"-I +unix "
else
"")
(List.map modules ~f:(fun m -> m ^ ".ml") |> String.concat ~sep:" "));
let args = Array.to_list (Array.sub Sys.argv 1 (Array.length Sys.argv - 1)) in
let args =
Expand Down
12 changes: 9 additions & 3 deletions src/dune_rules/findlib/meta.ml
Original file line number Diff line number Diff line change
Expand Up @@ -198,6 +198,12 @@ let builtins ~stdlib_dir ~version:ocaml_version =
; entries = [ version; main_modules [ name ] ]
}
in
let sandbox_if_necessary dir =
if Ocaml_version.has_sandboxed_otherlibs ocaml_version then
"+" ^ dir
else
"+"
in
let compiler_libs =
let sub name ?kind ?exists_if_ext deps =
Package
Expand All @@ -220,8 +226,8 @@ let builtins ~stdlib_dir ~version:ocaml_version =
}
in
let stdlib = dummy "stdlib" in
let str = simple "str" [] ~dir:"+" in
let unix = simple ~labels:true "unix" [] ~dir:"+" in
let str = simple "str" [] ~dir:(sandbox_if_necessary "str") in
let unix = simple ~labels:true "unix" [] ~dir:(sandbox_if_necessary "unix") in
let bigarray =
if
Ocaml_version.stdlib_includes_bigarray ocaml_version
Expand All @@ -231,7 +237,7 @@ let builtins ~stdlib_dir ~version:ocaml_version =
else
simple "bigarray" [ "unix" ] ~dir:"+"
in
let dynlink = simple "dynlink" [] ~dir:"+" in
let dynlink = simple "dynlink" [] ~dir:(sandbox_if_necessary "dynlink") in
let bytes = dummy "bytes" in
let result = dummy "result" in
let uchar = dummy "uchar" in
Expand Down
4 changes: 4 additions & 0 deletions src/dune_rules/ocaml_version.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,3 +49,7 @@ let custom_or_output_complete_exe version =
let ocamlopt_always_calls_library_linker version = version < (4, 12, 0)

let has_sys_opaque_identity version = version >= (4, 3, 0)

let has_bigarray_library version = version < (5, 0, 0)

let has_sandboxed_otherlibs version = version >= (5, 0, 0)
7 changes: 7 additions & 0 deletions src/dune_rules/ocaml_version.mli
Original file line number Diff line number Diff line change
Expand Up @@ -68,3 +68,10 @@ val ocamlopt_always_calls_library_linker : t -> bool

(** Whether [Sys.opaque_identity] is in the standard library *)
val has_sys_opaque_identity : t -> bool

(** Whether [bigarray] {e library} exists *)
val has_bigarray_library : t -> bool

(** Whether [dynlink], [str] and [unix] are in subdirectories of the standard
library *)
val has_sandboxed_otherlibs : t -> bool
9 changes: 8 additions & 1 deletion src/ocaml-config/ocaml_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -513,7 +513,14 @@ let make vars =
let cmt_magic_number = get vars "cmt_magic_number" in
let windows_unicode = get_bool vars "windows_unicode" in
let natdynlink_supported =
Sys.file_exists (Filename.concat standard_library "dynlink.cmxa")
let lib = "dynlink.cmxa" in
let lib =
if version >= (5, 0, 0) then
Filename.concat "dynlink" lib
else
lib
in
Sys.file_exists (Filename.concat standard_library lib)
in
let file =
let stdlib = Path.external_ (Path.External.of_string standard_library) in
Expand Down

0 comments on commit 3f5f4cf

Please sign in to comment.