summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2013-06-16 19:07:45 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2013-06-16 19:07:45 +0000
commit122caaf20b03e920a88677cf030901981c60781b (patch)
treedd935c8c01d60c1d8233c0a0a3f7729ea09d6ac4
parentf79d1a4e2dd68a268cdb12f809624ada19503d06 (diff)
ocamlbuild: when tag "native" is set, use ocamlopt instead of ocamlc for .mli->.cmi
This was requested (with a patch proposal) by "jessicah" in PR#4613. Given that the effect of such changes are hard to test, I commit this in trunk only, not version-4.01, to give more time to detect eventual problems. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13787 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--ocamlbuild/ocaml_compiler.ml12
-rw-r--r--ocamlbuild/ocaml_compiler.mli1
-rw-r--r--ocamlbuild/ocaml_specific.ml2
-rw-r--r--ocamlbuild/testsuite/level0.ml7
4 files changed, 21 insertions, 1 deletions
diff --git a/ocamlbuild/ocaml_compiler.ml b/ocamlbuild/ocaml_compiler.ml
index 218842feb..4b2a761bf 100644
--- a/ocamlbuild/ocaml_compiler.ml
+++ b/ocamlbuild/ocaml_compiler.ml
@@ -128,6 +128,18 @@ let byte_compile_ocaml_interf mli cmi env build =
prepare_compile build mli;
ocamlc_c (tags_of_pathname mli++"interf") mli cmi
+(* given that .cmi can be built from either ocamlc and ocamlopt, this
+ "agnostic" rule chooses either compilers depending on whether the
+ "native" tag is present. This was requested during PR#4613 as way
+ to enable using ocamlbuild in environments where only ocamlopt is
+ available, not ocamlc. *)
+let compile_ocaml_interf mli cmi env build =
+ let mli = env mli and cmi = env cmi in
+ prepare_compile build mli;
+ let tags = tags_of_pathname mli++"interf" in
+ let comp_c = if Tags.mem "native" tags then ocamlopt_c else ocamlc_c in
+ comp_c tags mli cmi
+
let byte_compile_ocaml_implem ?tag ml cmo env build =
let ml = env ml and cmo = env cmo in
prepare_compile build ml;
diff --git a/ocamlbuild/ocaml_compiler.mli b/ocamlbuild/ocaml_compiler.mli
index 667191af2..5e6796005 100644
--- a/ocamlbuild/ocaml_compiler.mli
+++ b/ocamlbuild/ocaml_compiler.mli
@@ -26,6 +26,7 @@ val ocamlopt_p : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
val ocamlmklib : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
val ocamlmktop : Tags.t -> Pathname.t list -> Pathname.t -> Command.t
val prepare_compile : Rule.builder -> Pathname.t -> unit
+val compile_ocaml_interf : string -> string -> Rule.action
val byte_compile_ocaml_interf : string -> string -> Rule.action
val byte_compile_ocaml_implem : ?tag:string -> string -> string -> Rule.action
val prepare_link :
diff --git a/ocamlbuild/ocaml_specific.ml b/ocamlbuild/ocaml_specific.ml
index c4330252e..a4c6e46e9 100644
--- a/ocamlbuild/ocaml_specific.ml
+++ b/ocamlbuild/ocaml_specific.ml
@@ -78,7 +78,7 @@ rule "ocaml: mli -> cmi"
~tags:["ocaml"]
~prod:"%.cmi"
~deps:["%.mli"; "%.mli.depends"]
- (Ocaml_compiler.byte_compile_ocaml_interf "%.mli" "%.cmi");;
+ (Ocaml_compiler.compile_ocaml_interf "%.mli" "%.cmi");;
rule "ocaml: mlpack & d.cmo* -> d.cmo & cmi"
~tags:["ocaml"; "debug"; "byte"]
diff --git a/ocamlbuild/testsuite/level0.ml b/ocamlbuild/testsuite/level0.ml
index a94b8d980..defa249bd 100644
--- a/ocamlbuild/testsuite/level0.ml
+++ b/ocamlbuild/testsuite/level0.ml
@@ -131,4 +131,11 @@ test "SyntaxFlag"
~matching:[M.f "dummy.native"]
~targets:("dummy.native",[]) ();;
+test "NativeMliCmi"
+ ~description:"check that ocamlopt is used for .mli->.cmi when tag 'native' is set"
+ ~tree:[T.f "foo.mli" ~content:"val bar : int"]
+ ~options:[`ocamlc "toto";(*using ocamlc would fail*) `tags["native"]]
+ ~matching:[M.f "_build/foo.cmi"]
+ ~targets:("foo.cmi",[]) ();;
+
run ~root:"_test";;