-
Notifications
You must be signed in to change notification settings - Fork 415
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
which allows to easily dynlink packages and their dependencies. Dune is needed for putting in the binary the list of package statically linked. Signed-off-by: François Bobot <francois.bobot@cea.fr>
- Loading branch information
Showing
23 changed files
with
343 additions
and
5 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,100 @@ | ||
open Import | ||
|
||
module CC = Compilation_context | ||
module SC = Super_context | ||
|
||
type libs_or_module = | ||
| Libs of Lib.L.t | ||
| Module of Module.t | ||
|
||
type t = { | ||
libs_or_module: libs_or_module list; | ||
flags: Ocaml_flags.t; | ||
} | ||
|
||
let create ?(flags=Ocaml_flags.empty) libs = | ||
{ libs_or_module = [Libs libs]; flags } | ||
|
||
let only_libs libs = | ||
libs | ||
|> List.filter_map ~f:(function Libs libs -> Some libs | Module _ -> None) | ||
|> List.concat | ||
|
||
let rec cut_after_libs ~pkg_name before = function | ||
| [] -> None | ||
| a::l when String.equal (Lib.name a) pkg_name -> Some (List.rev (a::before),l) | ||
| a::l -> cut_after_libs (a::before) ~pkg_name l | ||
|
||
let rec cut_after ~pkg_name before = function | ||
| [] -> None | ||
| ((Module _ ) as a)::l -> cut_after (a::before) ~pkg_name l | ||
| ((Libs libs) as a)::l -> | ||
begin | ||
match cut_after_libs [] ~pkg_name libs with | ||
| None -> cut_after (a::before) ~pkg_name l | ||
| Some (a,b) -> Some (List.rev ((Libs a)::before), (Libs b)::l) | ||
end | ||
|
||
let findlib_dynload ~name ~mode cctx t = | ||
let sctx = CC.super_context cctx in | ||
let obj_dir = CC.obj_dir cctx in | ||
match cut_after [] ~pkg_name:"findlib.dynload" t.libs_or_module with | ||
| Some (before, after) -> | ||
(* If findlib.dynload is linked, we stores in the binary the packages linked by linking just | ||
after findlib.dynload a module containing the info *) | ||
let libs = | ||
List.filter | ||
~f:(fun lib -> match Lib.status lib with | Lib.Status.Private _ -> false | _ -> true) | ||
(only_libs t.libs_or_module) | ||
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 | ||
let s = | ||
Format.asprintf "%a@\nFindlib.record_package_predicates %a;;@." | ||
(Fmt.list ~pp_sep:Fmt.nl (fun fmt lib -> | ||
Format.fprintf fmt "Findlib.record_package Findlib.Record_core %S;;" | ||
(Lib.name lib))) | ||
libs | ||
(Fmt.ocaml_list Variant.pp) (Variant.Set.to_list preds) | ||
in | ||
let basename = Format.asprintf "%s_findlib_initl_%a" name Mode.pp mode in | ||
let ml = Path.relative obj_dir (basename ^ ".ml") in | ||
SC.add_rule sctx (Build.write_file ml s); | ||
let impl = Module.File.make OCaml ml in | ||
let name = Module.Name.of_string basename in | ||
let module_ = Module.make ~impl name in | ||
let cctx = Compilation_context.( | ||
create | ||
~super_context:sctx | ||
~scope:(scope cctx) | ||
~dir:(dir cctx) | ||
~dir_kind:(dir_kind cctx) | ||
~obj_dir:(obj_dir cctx) | ||
~modules:(Module.Name.Map.singleton name module_) | ||
~requires:(Lib.DB.find_many (SC.public_libs sctx) ["findlib"]) | ||
~flags:Ocaml_flags.empty | ||
~opaque:true | ||
()) | ||
in | ||
Module_compilation.build_module ~dynlink:false | ||
~dep_graphs:(Ocamldep.Dep_graphs.dummy module_) | ||
cctx | ||
module_; | ||
{ | ||
libs_or_module = before@[Module module_]@after; | ||
flags = Ocaml_flags.append_common t.flags ["-linkall"]; | ||
} | ||
| None -> | ||
t |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,23 @@ | ||
(** {1 Handle link time code generation} *) | ||
|
||
type libs_or_module = | ||
| Libs of Lib.L.t | ||
| Module of Module.t | ||
(** List of library and modules in link order *) | ||
|
||
type t = { | ||
libs_or_module: libs_or_module list; | ||
flags: Ocaml_flags.t; | ||
} | ||
|
||
|
||
val create: ?flags:Ocaml_flags.t -> Lib.L.t -> t | ||
(** Should be the complete list of library linked in dependency order *) | ||
|
||
val findlib_dynload: | ||
name:string -> | ||
mode:Mode.t -> | ||
Compilation_context.t -> | ||
t -> | ||
t | ||
(** Insert link time generated code for findlib_dynload in the list *) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,2 @@ | ||
let () = print_endline "a: init" | ||
let called () = print_endline "a: called" |
Empty file.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,46 @@ | ||
(library | ||
(name a) | ||
(public_name a) | ||
(modules a) | ||
) | ||
|
||
(library | ||
(name mytool_plugin_b) | ||
(public_name mytool-plugin-b) | ||
(modules mytool_plugin_b) | ||
(libraries a mytool) | ||
) | ||
|
||
(library | ||
(name mytool) | ||
(public_name mytool) | ||
(modules register) | ||
) | ||
|
||
(executable | ||
(name main) | ||
(modules main) | ||
(public_name mytool) | ||
(package mytool) | ||
(libraries mytool findlib.dynload) | ||
) | ||
|
||
|
||
(rule (copy main.ml main_with_a.ml)) | ||
|
||
(executable | ||
(name main_with_a) | ||
(modules main_with_a) | ||
(public_name mytool_with_a) | ||
(package mytool) | ||
(libraries mytool findlib.dynload a) | ||
) | ||
|
||
|
||
(executable | ||
(name main_auto) | ||
(modules main_auto) | ||
(public_name mytool_auto) | ||
(package mytool) | ||
(libraries mytool findlib.dynload findlib) | ||
) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
(lang dune 1.0) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,9 @@ | ||
let () = print_endline "m: init" | ||
|
||
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, _) -> | ||
Printf.printf "The package %S can't be found.\n%!" pkg | ||
done |
11 changes: 11 additions & 0 deletions
11
test/blackbox-tests/test-cases/findlib-dynload/main_auto.ml
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,11 @@ | ||
let () = print_endline "m: init" | ||
|
||
let () = Findlib.init () | ||
let () = | ||
let pkgs = Fl_package_base.list_packages () in | ||
let pkgs = | ||
List.filter | ||
(fun pkg -> 14 <= String.length pkg && String.sub pkg 0 14 = "mytool-plugin-") | ||
pkgs | ||
in | ||
Fl_dynload.load_packages pkgs |
Empty file.
Empty file.
4 changes: 4 additions & 0 deletions
4
test/blackbox-tests/test-cases/findlib-dynload/mytool_plugin_b.ml
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,4 @@ | ||
let () = print_endline "b: init" | ||
let called () = print_endline "b: called"; A.called () | ||
|
||
let () = Mytool.Register.register "b" called |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
let register s f = print_endline (s^": registering"); f () |
Oops, something went wrong.