Skip to content

Commit

Permalink
Force installation of the threads module with findlib.dynload
Browse files Browse the repository at this point in the history
Signed-off-by: François Bobot <francois.bobot@cea.fr>
  • Loading branch information
bobot committed Aug 27, 2018
1 parent 457ee46 commit 9fd5d6e
Show file tree
Hide file tree
Showing 7 changed files with 52 additions and 21 deletions.
10 changes: 6 additions & 4 deletions doc/advanced-topics.rst
Original file line number Diff line number Diff line change
Expand Up @@ -76,14 +76,16 @@ to add ``findlib.dynload`` to the set of library dependencies:
(executable
(name main)
(public_name mytool)
(libraries mytool findlib.dynload)
(libraries mytool findlib.dynload threads)
(modules ...)
)
Then you could use in your application ``Fl_dynload.load_packages l`` that
will load the list ``l`` of packages. The packages are loaded only
once. So trying to load a package statically linked does nothing.
Then you could use in your application ``Fl_dynload.load_packages l``
that will load the list ``l`` of packages. The packages are loaded
only once. So trying to load a package statically linked does nothing.
The builtin nature of the library ``threads`` forces to link it even
if an application don't need it in case a plugin would use it.

A plugin creator just need to link to your library:

Expand Down
21 changes: 7 additions & 14 deletions src/link_time_code_gen.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,20 +24,13 @@ let libraries_link ~name ~mode cctx libs =
~f:(fun lib -> match Lib.status lib with | Lib.Status.Private _ -> false | _ -> true)
libs
in
(* We can't use directly Findlib.Package.preds because there
are fixups in ocamlfind that adds the package "thread" as
dependency of all the packages when the predicate "mt" is
used. Also independently of ocamlfind it could be strange
if a library can be used without or with `thread` but
"thread" is forced during dynlink because we always add "mt". *)
let preds =
if List.exists libs ~f:(fun lib -> Lib.name lib = "threads")
then Findlib.Package.preds
else
Variant.Set.diff Findlib.Package.preds
(Variant.Set.of_list [Variant.mt;Variant.mt_posix])
in
let preds = Variant.Set.add preds (Mode.variant mode) in
(* If thread is not present we error out otherwise if a plugin need
it there is a linking error. *)
if not (List.exists libs ~f:(fun lib -> Lib.name lib = "threads"))
then
Arg_spec.Dyn (fun _ -> die "The threads package should always be present with package findlib.dynload")
else
let preds = Variant.Set.add Findlib.Package.preds (Mode.variant mode) in
let s =
Format.asprintf "%a@\nFindlib.record_package_predicates %a;;@."
(Fmt.list ~pp_sep:Fmt.nl (fun fmt lib ->
Expand Down
7 changes: 7 additions & 0 deletions test/blackbox-tests/test-cases/findlib-dynload/c_thread.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
let t =
Thread.create
(fun () -> print_endline "thread started"; Thread.delay 0.001; print_endline "thread stopping") ()

let () = Thread.delay 0.001

let () = Mytool.Register.register "c_thread" (fun () -> Thread.join t)
Empty file.
22 changes: 20 additions & 2 deletions test/blackbox-tests/test-cases/findlib-dynload/dune
Original file line number Diff line number Diff line change
Expand Up @@ -22,18 +22,19 @@
(modules main)
(public_name mytool)
(package mytool)
(libraries mytool findlib.dynload)
(libraries mytool findlib.dynload threads)
)


(rule (copy main.ml main_with_a.ml))
(rule (copy main.ml main_without_threads.ml))

(executable
(name main_with_a)
(modules main_with_a)
(public_name mytool_with_a)
(package mytool)
(libraries mytool findlib.dynload a)
(libraries mytool findlib.dynload a threads)
)


Expand All @@ -42,5 +43,22 @@
(modules main_auto)
(public_name mytool_auto)
(package mytool)
(libraries mytool findlib.dynload findlib threads)
)


(executable
(name main_without_threads)
(modules main_without_threads)
(public_name mytool_without_threads)
(package mytool)
(libraries mytool findlib.dynload findlib)
)


(library
(name c_thread)
(public_name c_thread)
(modules c_thread)
(libraries threads mytool)
)
5 changes: 4 additions & 1 deletion test/blackbox-tests/test-cases/findlib-dynload/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,9 @@ let () =
for i = 1 to (Array.length Sys.argv - 1); do
try
Fl_dynload.load_packages [Sys.argv.(i)]
with Fl_package_base.No_such_package(pkg, _) ->
with
| Fl_package_base.No_such_package(pkg, _) ->
Printf.printf "The package %S can't be found.\n%!" pkg
| Dynlink.Error error ->
Printf.printf "Error during dynlink: %s\n%!" (Dynlink.error_message error)
done
8 changes: 8 additions & 0 deletions test/blackbox-tests/test-cases/findlib-dynload/run.t
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
$ dune build
The threads package should always be present with package findlib.dynload
[1]

$ dune exec mytool
m: init
Expand Down Expand Up @@ -54,3 +56,9 @@
b: registering
b: called
a: called
$ dune exe mytool c_thread
m: init
thread started
c_thread: registering
thread stopping

0 comments on commit 9fd5d6e

Please sign in to comment.