ocamlbuild: Add support for native dynlink
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10264 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
49a83dd965
commit
4e6cb15c4f
|
@ -71,6 +71,7 @@ let ocamlopt_link flag tags deps out =
|
|||
atomize_paths deps; A"-o"; Px out])
|
||||
|
||||
let ocamlopt_link_lib = ocamlopt_link (A"-a")
|
||||
let ocamlopt_link_shared_lib = ocamlopt_link (A"-shared")
|
||||
let ocamlopt_link_prog = ocamlopt_link N
|
||||
|
||||
let ocamlopt_p tags deps out =
|
||||
|
@ -93,8 +94,17 @@ let native_lib_linker tags =
|
|||
else
|
||||
ocamlopt_link_lib tags
|
||||
|
||||
let native_shared_lib_linker tags =
|
||||
(* ocamlmklib seems to not support -shared, is this OK?
|
||||
if Tags.mem "ocamlmklib" tags then
|
||||
ocamlmklib tags
|
||||
else
|
||||
*)
|
||||
ocamlopt_link_shared_lib tags
|
||||
|
||||
let native_lib_linker_tags tags = tags++"ocaml"++"link"++"native"++"library"
|
||||
|
||||
|
||||
let prepare_compile build ml =
|
||||
let dir = Pathname.dirname ml in
|
||||
let include_dirs = Pathname.include_dirs_of dir in
|
||||
|
@ -181,6 +191,11 @@ module Ocaml_dependencies = Ocaml_dependencies.Make(Ocaml_dependencies_input)
|
|||
|
||||
let caml_transitive_closure = Ocaml_dependencies.caml_transitive_closure
|
||||
|
||||
let link_one_gen linker tagger cmX out env _build =
|
||||
let cmX = env cmX and out = env out in
|
||||
let tags = tagger (tags_of_pathname out) in
|
||||
linker tags [cmX] out
|
||||
|
||||
let link_gen cmX_ext cma_ext a_ext extensions linker tagger cmX out env build =
|
||||
let cmX = env cmX and out = env out in
|
||||
let tags = tagger (tags_of_pathname out) in
|
||||
|
@ -335,11 +350,32 @@ let native_library_link_modules x =
|
|||
link_modules [("cmx",[!Options.ext_obj])] "cmx" "cmxa"
|
||||
!Options.ext_lib native_lib_linker native_lib_linker_tags x
|
||||
|
||||
let native_shared_library_link_modules x =
|
||||
link_modules [("cmx",[!Options.ext_obj])] "cmx" "cmxa"
|
||||
!Options.ext_lib native_shared_lib_linker
|
||||
(fun tags -> native_lib_linker_tags tags++"shared") x
|
||||
|
||||
let native_library_link_mllib = link_from_file native_library_link_modules
|
||||
|
||||
let native_shared_library_link_mldylib = link_from_file native_shared_library_link_modules
|
||||
|
||||
let native_shared_library_tags tags basetags =
|
||||
List.fold_left (++) (basetags++"ocaml"++"link"++"native"++"shared"++"library") tags
|
||||
|
||||
let native_shared_library_link ?(tags = []) x =
|
||||
link_one_gen native_shared_lib_linker
|
||||
(native_shared_library_tags tags) x
|
||||
|
||||
let native_profile_library_link_modules x =
|
||||
link_modules [("p.cmx",["p" -.- !Options.ext_obj])] "p.cmx" "p.cmxa"
|
||||
("p" -.- !Options.ext_lib) native_lib_linker
|
||||
(fun tags -> native_lib_linker_tags tags++"profile") x
|
||||
|
||||
let native_profile_shared_library_link_modules x =
|
||||
link_modules [("p.cmx",["p" -.- !Options.ext_obj])] "p.cmx" "p.cmxa"
|
||||
("p" -.- !Options.ext_lib) native_shared_lib_linker
|
||||
(fun tags -> native_lib_linker_tags tags++"shared"++"profile") x
|
||||
|
||||
let native_profile_library_link_mllib = link_from_file native_profile_library_link_modules
|
||||
|
||||
let native_profile_shared_library_link_mldylib = link_from_file native_profile_shared_library_link_modules
|
||||
|
|
|
@ -19,6 +19,7 @@ val ocamlc_link_prog : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
|||
val ocamlc_p : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
val ocamlopt_c : Tags.t -> Pathname.t -> Pathname.t -> Command.t
|
||||
val ocamlopt_link_lib : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
val ocamlopt_link_shared_lib : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
val ocamlopt_link_prog : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
val ocamlopt_p : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
val ocamlmklib : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
|
||||
|
@ -44,6 +45,7 @@ val byte_debug_link : string -> string -> Rule.action
|
|||
val byte_debug_library_link : string -> string -> Rule.action
|
||||
val native_link : string -> string -> Rule.action
|
||||
val native_library_link : string -> string -> Rule.action
|
||||
val native_shared_library_link : ?tags:(string list) -> string -> string -> Rule.action
|
||||
val native_profile_link : string -> string -> Rule.action
|
||||
val native_profile_library_link : string -> string -> Rule.action
|
||||
val link_modules :
|
||||
|
@ -72,10 +74,14 @@ val native_pack_modules : string list -> string -> Rule.action
|
|||
val native_pack_mlpack : string -> string -> Rule.action
|
||||
val native_library_link_modules : string list -> string -> Rule.action
|
||||
val native_library_link_mllib : string -> string -> Rule.action
|
||||
val native_shared_library_link_modules : string list -> string -> Rule.action
|
||||
val native_shared_library_link_mldylib : string -> string -> Rule.action
|
||||
val native_profile_pack_modules : string list -> string -> Rule.action
|
||||
val native_profile_pack_mlpack : string -> string -> Rule.action
|
||||
val native_profile_library_link_modules : string list -> string -> Rule.action
|
||||
val native_profile_library_link_mllib : string -> string -> Rule.action
|
||||
val native_profile_shared_library_link_modules : string list -> string -> Rule.action
|
||||
val native_profile_shared_library_link_mldylib : string -> string -> Rule.action
|
||||
|
||||
(** [hide_package_contents pack_name]
|
||||
Don't treat the given package as an open package.
|
||||
|
|
|
@ -55,6 +55,7 @@ let x_a = "%"-.-ext_lib;;
|
|||
let x_dll = "%"-.-ext_dll;;
|
||||
let x_p_o = "%.p"-.-ext_obj;;
|
||||
let x_p_a = "%.p"-.-ext_lib;;
|
||||
let x_p_dll = "%.p"-.-ext_dll;;
|
||||
|
||||
rule "target files"
|
||||
~dep:"%.itarget"
|
||||
|
@ -207,18 +208,54 @@ rule "ocaml: mllib & cmx* & o* -> cmxa & a"
|
|||
~dep:"%.mllib"
|
||||
(Ocaml_compiler.native_library_link_mllib "%.mllib" "%.cmxa");;
|
||||
|
||||
rule "ocaml: p.cmx* & p.o* -> p.cmxa & p.a"
|
||||
rule "ocaml: p.cmx & p.o -> p.cmxa & p.a"
|
||||
~tags:["ocaml"; "native"; "profile"; "library"]
|
||||
~prods:["%.p.cmxa"; x_p_a]
|
||||
~deps:["%.p.cmx"; x_p_o]
|
||||
(Ocaml_compiler.native_profile_library_link "%.p.cmx" "%.p.cmxa");;
|
||||
|
||||
rule "ocaml: cmx* & o* -> cmxa & a"
|
||||
rule "ocaml: cmx & o -> cmxa & a"
|
||||
~tags:["ocaml"; "native"; "library"]
|
||||
~prods:["%.cmxa"; x_a]
|
||||
~deps:["%.cmx"; x_o]
|
||||
(Ocaml_compiler.native_library_link "%.cmx" "%.cmxa");;
|
||||
|
||||
rule "ocaml: mldylib & p.cmx* & p.o* -> p.cmxs & p.so"
|
||||
~tags:["ocaml"; "native"; "profile"; "shared"; "library"]
|
||||
~prods:["%.p.cmxs"; x_p_dll]
|
||||
~dep:"%.mldylib"
|
||||
(Ocaml_compiler.native_profile_shared_library_link_mldylib "%.mldylib" "%.p.cmxs");;
|
||||
|
||||
rule "ocaml: mldylib & cmx* & o* -> cmxs & so"
|
||||
~tags:["ocaml"; "native"; "shared"; "library"]
|
||||
~prods:["%.cmxs"; x_dll]
|
||||
~dep:"%.mldylib"
|
||||
(Ocaml_compiler.native_shared_library_link_mldylib "%.mldylib" "%.cmxs");;
|
||||
|
||||
rule "ocaml: p.cmx & p.o -> p.cmxs & p.so"
|
||||
~tags:["ocaml"; "native"; "profile"; "shared"; "library"]
|
||||
~prods:["%.p.cmxs"; x_p_dll]
|
||||
~deps:["%.p.cmx"; x_p_o]
|
||||
(Ocaml_compiler.native_shared_library_link ~tags:["profile"] "%.p.cmx" "%.p.cmxs");;
|
||||
|
||||
rule "ocaml: p.cmxa & p.a -> p.cmxs & p.so"
|
||||
~tags:["ocaml"; "native"; "profile"; "shared"; "library"]
|
||||
~prods:["%.p.cmxs"; x_p_dll]
|
||||
~deps:["%.p.cmxa"; x_p_a]
|
||||
(Ocaml_compiler.native_shared_library_link ~tags:["profile";"linkall"] "%.p.cmxa" "%.p.cmxs");;
|
||||
|
||||
rule "ocaml: cmx & o -> cmxs & so"
|
||||
~tags:["ocaml"; "native"; "shared"; "library"]
|
||||
~prods:["%.cmxs"; x_dll]
|
||||
~deps:["%.cmx"; x_o]
|
||||
(Ocaml_compiler.native_shared_library_link "%.cmx" "%.cmxs");;
|
||||
|
||||
rule "ocaml: cmxa & a -> cmxs & so"
|
||||
~tags:["ocaml"; "native"; "shared"; "library"]
|
||||
~prods:["%.cmxs"; x_dll]
|
||||
~deps:["%.cmxa"; x_a]
|
||||
(Ocaml_compiler.native_shared_library_link ~tags:["linkall"] "%.cmxa" "%.cmxs");;
|
||||
|
||||
rule "ocaml dependencies ml"
|
||||
~prod:"%.ml.depends"
|
||||
~dep:"%.ml"
|
||||
|
|
Loading…
Reference in New Issue