Skip to content

Commit

Permalink
Never pass -nodynlink option
Browse files Browse the repository at this point in the history
This is an optimization when PIC executables are not used, but this
optimization is disabled becauses it causes errors on arm32. Most
distributions are going in the direction of requiring PIC, and
`-nodynlink` might go away (see ocaml/ocaml#8867), so the supporting
code in dune (which is bypassed in most cases) can be removed.

Closes #4069
Closes #2527

Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Jan 11, 2021
1 parent caef668 commit 8b2b0af
Show file tree
Hide file tree
Showing 11 changed files with 13 additions and 35 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,10 @@ Unreleased
- Fix `libexec` and `libexec-private` variables. In cross-compilation settings,
they now point to the file in the host context. (#4058, fixes #4057, @TheLortex)

- Remove support for passing `-nodynlink` for executables. It was bypassed in
most cases and not correct in other cases in particular on arm32.
(#4085, fixes #4069, fixes #2527, @emillon)

2.7.1 (2/09/2020)
-----------------

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ let gen_rules sctx t ~dir ~scope =
~requires_compile:(Lib.Compile.direct_requires compile_info)
~requires_link:(Lib.Compile.requires_link compile_info)
~flags:(Ocaml_flags.of_list [ "-w"; "-24" ])
~js_of_ocaml:None ~dynlink:false ~package:None
~js_of_ocaml:None ~package:None
in
Exe.build_and_link cctx
~program:{ name; main_module_name; loc }
Expand Down
7 changes: 1 addition & 6 deletions src/dune_rules/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,6 @@ type t =
; opaque : bool
; stdlib : Ocaml_stdlib.t option
; js_of_ocaml : Dune_file.Js_of_ocaml.t option
; dynlink : bool
; sandbox : Sandbox_config.t
; package : Package.t option
; vimpl : Vimpl.t option
Expand Down Expand Up @@ -102,8 +101,6 @@ let stdlib t = t.stdlib

let js_of_ocaml t = t.js_of_ocaml

let dynlink t = t.dynlink

let sandbox t = t.sandbox

let package t = t.package
Expand All @@ -118,8 +115,7 @@ let context t = Super_context.context t.super_context

let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
~requires_compile ~requires_link ?(preprocessing = Pp_spec.dummy) ~opaque
?stdlib ~js_of_ocaml ~dynlink ~package ?vimpl ?modes ?(bin_annot = true) ()
=
?stdlib ~js_of_ocaml ~package ?vimpl ?modes ?(bin_annot = true) () =
let project = Scope.project scope in
let requires_compile =
if Dune_project.implicit_transitive_deps project then
Expand Down Expand Up @@ -154,7 +150,6 @@ let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
; opaque
; stdlib
; js_of_ocaml
; dynlink
; sandbox
; package
; vimpl
Expand Down
3 changes: 0 additions & 3 deletions src/dune_rules/compilation_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@ val create :
-> opaque:opaque
-> ?stdlib:Ocaml_stdlib.t
-> js_of_ocaml:Dune_file.Js_of_ocaml.t option
-> dynlink:bool
-> package:Package.t option
-> ?vimpl:Vimpl.t
-> ?modes:Dune_file.Mode_conf.Set.Details.t Mode.Dict.t
Expand Down Expand Up @@ -82,8 +81,6 @@ val stdlib : t -> Ocaml_stdlib.t option

val js_of_ocaml : t -> Dune_file.Js_of_ocaml.t option

val dynlink : t -> bool

val sandbox : t -> Sandbox_config.t

val package : t -> Package.t option
Expand Down
11 changes: 1 addition & 10 deletions src/dune_rules/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -129,18 +129,9 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
else
Some js_of_ocaml
in
let dynlink =
(* See https://github.com/ocaml/dune/issues/2527 *)
true
|| Dune_file.Executables.Link_mode.Map.existsi exes.modes
~f:(fun mode _loc ->
match mode with
| Other { kind = Shared_object; _ } -> true
| _ -> false)
in
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~flags ~requires_link ~requires_compile ~preprocessing:pp
~js_of_ocaml ~opaque:Inherit_from_settings ~dynlink ~package:exes.package
~js_of_ocaml ~opaque:Inherit_from_settings ~package:exes.package
in
let requires_compile = Compilation_context.requires_compile cctx in
let preprocess =
Expand Down
3 changes: 1 addition & 2 deletions src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -292,8 +292,7 @@ include Sub_system.Register_end_point (struct
Compilation_context.create () ~super_context:sctx ~expander ~scope
~obj_dir ~modules ~opaque:(Explicit false) ~requires_compile:runner_libs
~requires_link:(lazy runner_libs)
~flags ~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~dynlink:false
~package
~flags ~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~package
in
let linkages =
let modes =
Expand Down
5 changes: 1 addition & 4 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -364,9 +364,6 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
let modules = Vimpl.impl_modules vimpl modules in
let requires_compile = Lib.Compile.direct_requires compile_info in
let requires_link = Lib.Compile.requires_link compile_info in
let dynlink =
Dynlink_supported.get lib.dynlink ctx.supports_shared_libraries
in
let modes =
let { Lib_config.has_native; _ } = ctx.lib_config in
Dune_file.Mode_conf.Set.eval_detailed lib.modes ~has_native
Expand All @@ -375,7 +372,7 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~flags ~requires_compile ~requires_link ~preprocessing:pp
~opaque:Inherit_from_settings ~js_of_ocaml:(Some lib.buildable.js_of_ocaml)
~dynlink ?stdlib:lib.stdlib ~package ?vimpl ~modes
?stdlib:lib.stdlib ~package ?vimpl ~modes

let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents
~compile_info =
Expand Down
5 changes: 0 additions & 5 deletions src/dune_rules/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,6 @@ let build_cm cctx ~dep_graphs ~precompiled_cmi ~cm_kind (m : Module.t) ~phase =
let ctx = SC.context sctx in
let stdlib = CC.stdlib cctx in
let mode = Mode.of_cm_kind cm_kind in
let dynlink = CC.dynlink cctx in
let sandbox =
let default = CC.sandbox cctx in
match Module.kind m with
Expand Down Expand Up @@ -187,10 +186,6 @@ let build_cm cctx ~dep_graphs ~precompiled_cmi ~cm_kind (m : Module.t) ~phase =
; Command.Args.S obj_dirs
; Cm_kind.Dict.get (CC.includes cctx) cm_kind
; As extra_args
; ( if dynlink || cm_kind <> Cmx then
Command.Args.empty
else
A "-nodynlink" )
; A "-no-alias-deps"
; opaque_arg
; As (Fdo.phase_flags phase)
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/preprocessing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -345,7 +345,7 @@ let build_ppx_driver sctx ~scope ~target ~pps ~pp_names =
let modules = Modules.singleton_exe module_ in
Compilation_context.create ~super_context:sctx ~scope ~expander ~obj_dir
~modules ~flags ~requires_compile ~requires_link ~opaque ~js_of_ocaml:None
~dynlink:false ~package:None ~bin_annot:false ()
~package:None ~bin_annot:false ()
in
Exe.build_and_link ~program ~linkages cctx ~promote:None

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/toplevel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,7 @@ module Stanza = struct
~expander
~modules:(Source.modules source preprocessing)
~opaque:(Explicit false) ~requires_compile ~requires_link ~flags
~js_of_ocaml:None ~dynlink:false ~package:None ~preprocessing
~js_of_ocaml:None ~package:None ~preprocessing
in
let resolved = make ~cctx ~source ~preprocess:toplevel.pps in
setup_rules resolved
Expand Down
4 changes: 2 additions & 2 deletions src/dune_rules/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -109,8 +109,8 @@ let setup sctx ~dir =
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~opaque:(Explicit false)
~requires_link:(lazy requires)
~requires_compile:requires ~flags ~js_of_ocaml:None ~dynlink:false
~package:None ~preprocessing
~requires_compile:requires ~flags ~js_of_ocaml:None ~package:None
~preprocessing
in
let toplevel = Toplevel.make ~cctx ~source ~preprocess:pps in
Toplevel.setup_rules toplevel

0 comments on commit 8b2b0af

Please sign in to comment.