Skip to content

Commit

Permalink
Add link_deps field
Browse files Browse the repository at this point in the history
In some cases, the linking step requires some dependencies. For example,
passing a version script to the linker. The new `(link_deps)` field
uses the dependency DSL already used in other places.

Closes #852

Signed-off-by: Etienne Millon <etienne@cryptosense.com>
  • Loading branch information
emillon committed Jun 13, 2018
1 parent 5d6e919 commit 96b01c5
Show file tree
Hide file tree
Showing 10 changed files with 52 additions and 4 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,9 @@ next
* Allow setting environment variables in `findlib.conf` for cross compilation
contexts. (#733, @rgrinberg)

- Add a `link_deps` field to executables, to specify link-time dependencies
like version scripts. (#879, fix #852, @emillon)

1.0+beta20 (10/04/2018)
-----------------------

Expand Down
4 changes: 4 additions & 0 deletions doc/jbuild.rst
Original file line number Diff line number Diff line change
Expand Up @@ -248,6 +248,10 @@ Executables can also be linked as object or shared object files. See
- ``(link_flags <flags>)`` specifies additional flags to pass to the linker.
This field supports ``(:include ...)`` forms

- ``(link_deps (<deps-conf list>))`` specifies the dependencies used only by the
linker, for example when using a version script. See the `Dependency
specification`_ section for more details.

- ``(modules <modules>)`` specifies which modules in the current directory
Jbuilder should consider when building this executable. Modules not listed
here will be ignored and cannot be used inside the executable described by
Expand Down
4 changes: 4 additions & 0 deletions src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -857,7 +857,11 @@ module Gen(P : Install_rules.Params) = struct
in

let flags = SC.ocaml_flags sctx ~scope ~dir exes.buildable in
let link_deps =
SC.Deps.interpret sctx ~scope ~dir exes.link_deps
in
let link_flags =
link_deps >>^ ignore >>>
SC.expand_and_eval_set sctx exes.link_flags
~scope
~dir
Expand Down
3 changes: 3 additions & 0 deletions src/jbuild.ml
Original file line number Diff line number Diff line change
Expand Up @@ -874,6 +874,7 @@ module Executables = struct
type t =
{ names : (Loc.t * string) list
; link_flags : Ordered_set_lang.Unexpanded.t
; link_deps : Dep_conf.t list
; modes : Link_mode.Set.t
; buildable : Buildable.t
}
Expand All @@ -887,6 +888,7 @@ module Executables = struct
field "link_executables" bool ~default:true >>= fun _ ->
return ())
>>= fun () ->
field "link_deps" (list Dep_conf.t) ~default:[] >>= fun link_deps ->
field_oslu "link_flags" >>= fun link_flags ->
field "modes" Link_mode.Set.t ~default:Link_mode.Set.default
>>= fun modes ->
Expand All @@ -902,6 +904,7 @@ module Executables = struct
let t =
{ names
; link_flags
; link_deps
; modes
; buildable
}
Expand Down
9 changes: 5 additions & 4 deletions src/jbuild.mli
Original file line number Diff line number Diff line change
Expand Up @@ -256,10 +256,11 @@ module Executables : sig
end

type t =
{ names : (Loc.t * string) list
; link_flags : Ordered_set_lang.Unexpanded.t
; modes : Link_mode.Set.t
; buildable : Buildable.t
{ names : (Loc.t * string) list
; link_flags : Ordered_set_lang.Unexpanded.t
; link_deps : Dep_conf.t list
; modes : Link_mode.Set.t
; buildable : Buildable.t
}
end

Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -330,6 +330,14 @@
test-cases/lib-available
(progn (run ${exe:cram.exe} -test run.t) (diff? run.t run.t.corrected))))))

(alias
((name link-deps)
(deps ((package dune) (files_recursively_in test-cases/link-deps)))
(action
(chdir
test-cases/link-deps
(progn (run ${exe:cram.exe} -test run.t) (diff? run.t run.t.corrected))))))

(alias
((name loop)
(deps ((package dune) (files_recursively_in test-cases/loop)))
Expand Down Expand Up @@ -592,6 +600,7 @@
(alias installable-dup-private-libs)
(alias intf-only)
(alias lib-available)
(alias link-deps)
(alias loop)
(alias menhir)
(alias merlin-tests)
Expand Down Expand Up @@ -656,6 +665,7 @@
(alias installable-dup-private-libs)
(alias intf-only)
(alias lib-available)
(alias link-deps)
(alias loop)
(alias merlin-tests)
(alias meta-gen)
Expand Down
11 changes: 11 additions & 0 deletions test/blackbox-tests/test-cases/link-deps/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
(alias
((name message)
(deps (.link_deps.eobjs/link_deps.cmo))
(action (echo "link\n"))
))

(executable
((name link_deps)
(link_deps ((alias message)))
)
)
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/link-deps/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.0)
Empty file.
11 changes: 11 additions & 0 deletions test/blackbox-tests/test-cases/link-deps/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
It is possible to add link-time dependencies.

In particular, these can depend on the result of the compilation (like a .cmo
file) and be created just before linking.

$ dune build --display short link_deps.exe
ocamldep link_deps.ml.d
ocamlc .link_deps.eobjs/link_deps.{cmi,cmo,cmt}
link
ocamlopt .link_deps.eobjs/link_deps.{cmx,o}
ocamlopt link_deps.exe

0 comments on commit 96b01c5

Please sign in to comment.