2013-09-15 04:36:12 -07:00
|
|
|
#use "internal_test_header.ml";;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
|
|
|
test "BasicNativeTree"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2012-12-28 20:34:30 -08:00
|
|
|
~description:"Output tree for native compilation"
|
2012-12-29 19:25:35 -08:00
|
|
|
~tree:[T.f "dummy.ml"]
|
|
|
|
~matching:[M.Exact
|
2013-09-15 04:36:12 -07:00
|
|
|
(_build
|
|
|
|
(M.lf
|
2012-12-28 20:34:30 -08:00
|
|
|
["_digests";
|
|
|
|
"dummy.cmi";
|
|
|
|
"dummy.cmo";
|
|
|
|
"dummy.cmx";
|
|
|
|
"dummy.ml";
|
|
|
|
"dummy.ml.depends";
|
|
|
|
"dummy.native";
|
|
|
|
"dummy.o";
|
2012-12-29 19:25:35 -08:00
|
|
|
"_log"]))]
|
2012-12-31 17:37:26 -08:00
|
|
|
~targets:("dummy.native",[]) ();;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
|
|
|
test "BasicByteTree"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2012-12-28 20:34:30 -08:00
|
|
|
~description:"Output tree for byte compilation"
|
2012-12-29 19:25:35 -08:00
|
|
|
~tree:[T.f "dummy.ml"]
|
|
|
|
~matching:[M.Exact
|
2013-09-15 04:36:12 -07:00
|
|
|
(_build
|
|
|
|
(M.lf
|
2012-12-28 20:34:30 -08:00
|
|
|
["_digests";
|
|
|
|
"dummy.cmi";
|
|
|
|
"dummy.cmo";
|
|
|
|
"dummy.ml";
|
|
|
|
"dummy.ml.depends";
|
|
|
|
"dummy.byte";
|
2012-12-29 19:25:35 -08:00
|
|
|
"_log"]))]
|
2012-12-31 17:37:26 -08:00
|
|
|
~targets:("dummy.byte",[]) ();;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
|
|
|
test "SeveralTargets"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2012-12-28 20:34:30 -08:00
|
|
|
~description:"Several targets"
|
2012-12-29 19:25:35 -08:00
|
|
|
~tree:[T.f "dummy.ml"]
|
|
|
|
~matching:[_build (M.lf ["dummy.byte"; "dummy.native"])]
|
2012-12-31 17:37:26 -08:00
|
|
|
~targets:("dummy.byte",["dummy.native"]) ();;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
|
|
|
let alt_build_dir = "BuIlD2";;
|
|
|
|
|
|
|
|
test "BuildDir"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind; `build_dir alt_build_dir]
|
2012-12-28 20:34:30 -08:00
|
|
|
~description:"Different build directory"
|
2012-12-29 19:25:35 -08:00
|
|
|
~tree:[T.f "dummy.ml"]
|
|
|
|
~matching:[M.d alt_build_dir (M.lf ["dummy.byte"])]
|
2012-12-31 17:37:26 -08:00
|
|
|
~targets:("dummy.byte",[]) ();;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
2013-09-15 04:36:12 -07:00
|
|
|
let tag_pat_msgs =
|
|
|
|
["*:a", "File \"_tags\", line 1, column 0: \
|
|
|
|
Lexing error: Invalid globbing pattern \"*\".";
|
2012-12-31 17:37:26 -08:00
|
|
|
|
2013-09-15 04:36:12 -07:00
|
|
|
"\n<*{>:a", "File \"_tags\", line 2, column 0: \
|
|
|
|
Lexing error: Invalid globbing pattern \"<*{>\".";
|
2013-07-26 12:40:12 -07:00
|
|
|
|
2013-09-15 04:36:12 -07:00
|
|
|
"<*>: ~@a,# ~a", "File \"_tags\", line 1, column 10: \
|
|
|
|
Lexing error: Only ',' separated tags are alllowed."];;
|
2012-12-31 20:53:51 -08:00
|
|
|
|
|
|
|
List.iteri (fun i (content,failing_msg) ->
|
|
|
|
test (Printf.sprintf "TagsErrorMessage_%d" (i+1))
|
2013-08-20 09:02:37 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2012-12-31 20:53:51 -08:00
|
|
|
~description:"Confirm relevance of an error message due to erronous _tags"
|
|
|
|
~failing_msg
|
|
|
|
~tree:[T.f "_tags" ~content; T.f "dummy.ml"]
|
|
|
|
~targets:("dummy.native",[]) ()) tag_pat_msgs;;
|
2012-12-28 20:34:30 -08:00
|
|
|
|
2013-01-16 23:06:41 -08:00
|
|
|
test "Itarget"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-01-16 23:34:58 -08:00
|
|
|
~description:".itarget building with dependencies between the modules (PR#5686)"
|
2013-01-16 23:06:41 -08:00
|
|
|
~tree:[T.f "foo.itarget" ~content:"a.cma\nb.byte\n"; T.f "a.ml"; T.f "b.ml" ~content:"open A\n"]
|
|
|
|
~matching:[M.f "a.cma"; M.f "b.byte"]
|
|
|
|
~targets:("foo.otarget",[]) ();;
|
|
|
|
|
2013-01-16 23:34:58 -08:00
|
|
|
test "PackAcross"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-01-16 23:34:58 -08:00
|
|
|
~description:"Pack using a module from the other tree (PR#4592)"
|
|
|
|
~tree:[T.f "main.ml" ~content:"let _ = Pack.Packed.g ()\n";
|
|
|
|
T.f "Pack.mlpack" ~content:"pack/Packed";
|
|
|
|
T.f "_tags" ~content:"<lib>: include\n<pack/*.cmx>: for-pack(Pack)\n";
|
|
|
|
T.d "lib" [T.f "Lib.ml" ~content:"let f()=()";
|
|
|
|
T.f "Lib.mli" ~content:"val f : unit -> unit"];
|
|
|
|
T.d "pack" [T.f "Packed.ml" ~content:"let g() = Lib.f ()"]]
|
|
|
|
~matching:[M.f "main.byte"; M.f "main.native"]
|
|
|
|
~targets:("main.byte", ["main.native"])
|
|
|
|
();;
|
|
|
|
|
2013-01-23 15:40:19 -08:00
|
|
|
test "PackAcross2"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-01-23 15:40:19 -08:00
|
|
|
~description:"Pack using a module from the other tree (PR#4592)"
|
|
|
|
~tree:[T.f "a2.mli" ~content:"val f : unit -> unit";
|
|
|
|
T.f "a2.ml" ~content:"let f _ = ()";
|
|
|
|
T.f "lib.ml" ~content:"module A = A2";
|
|
|
|
T.f "b.ml" ~content:"let g = Lib.A.f";
|
|
|
|
T.f "sup.mlpack" ~content:"B";
|
|
|
|
T.f "prog.ml" ~content:"Sup.B.g"]
|
|
|
|
~matching:[M.f "prog.byte"]
|
|
|
|
~targets:("prog.byte",[]) ();;
|
|
|
|
|
|
|
|
test "PackAcross3"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-01-23 15:40:19 -08:00
|
|
|
~description:"Pack using a module from the other tree (PR#4592)"
|
|
|
|
~tree:[T.d "foo" [ T.f "bar.ml" ~content:"let baz = Quux.xyzzy"];
|
|
|
|
T.f "foo.mlpack" ~content:"foo/Bar";
|
|
|
|
T.f "main.ml" ~content:"prerr_endline Foo.Bar.baz";
|
|
|
|
T.f "myocamlbuild.ml";
|
|
|
|
T.f "quux.ml" ~content:"let xyzzy = \"xyzzy\"";
|
|
|
|
T.f "quux.mli" ~content:"val xyzzy : string"]
|
|
|
|
~matching:[M.f "main.byte"]
|
|
|
|
~targets:("main.byte",[]) ();;
|
|
|
|
|
2013-06-16 12:07:45 -07:00
|
|
|
test "NativeMliCmi"
|
2013-09-15 04:36:12 -07:00
|
|
|
~options:[`no_ocamlfind; `ocamlc "toto" (*using ocamlc would fail*);
|
|
|
|
`tags["native"]]
|
|
|
|
~description:"check that ocamlopt is used for .mli->.cmi \
|
|
|
|
when tag 'native' is set (part of PR#4613)"
|
2013-06-16 12:07:45 -07:00
|
|
|
~tree:[T.f "foo.mli" ~content:"val bar : int"]
|
2013-07-26 12:40:12 -07:00
|
|
|
~matching:[_build [M.f "foo.cmi"]]
|
2013-06-16 12:07:45 -07:00
|
|
|
~targets:("foo.cmi",[]) ();;
|
|
|
|
|
2013-06-17 06:12:40 -07:00
|
|
|
test "NoIncludeNoHygiene1"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-06-17 06:12:40 -07:00
|
|
|
~description:"check that hygiene checks are only done in traversed directories\
|
|
|
|
(PR#4502)"
|
|
|
|
~tree:[T.d "must_ignore" [ T.f "dirty.mli" ~content:"val bug : int"];
|
|
|
|
T.f "hello.ml" ~content:"print_endline \"Hello, World!\"";
|
|
|
|
T.f "_tags" ~content:"<must_ignore>: -traverse"]
|
|
|
|
~pre_cmd:"ocamlc -c must_ignore/dirty.mli"
|
|
|
|
(* will make hygiene fail if must_ignore/ is checked *)
|
|
|
|
~targets:("hello.byte",[]) ();;
|
|
|
|
|
|
|
|
test "NoIncludeNoHygiene2"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind; `build_dir "must_ignore"]
|
2013-06-17 06:12:40 -07:00
|
|
|
~description:"check that hygiene checks are not done on the -build-dir \
|
|
|
|
(PR#4502)"
|
|
|
|
~tree:[T.d "must_ignore" [ T.f "dirty.mli" ~content:"val bug : int"];
|
|
|
|
T.f "hello.ml" ~content:"print_endline \"Hello, World!\"";
|
|
|
|
T.f "_tags" ~content:""]
|
|
|
|
~pre_cmd:"ocamlc -c must_ignore/dirty.mli"
|
|
|
|
(* will make hygiene fail if must_ignore/ is checked *)
|
|
|
|
~targets:("hello.byte",[]) ();;
|
|
|
|
|
|
|
|
test "NoIncludeNoHygiene3"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind; `X "must_ignore"]
|
2013-06-17 06:12:40 -07:00
|
|
|
~description:"check that hygiene checks are not done on excluded dirs (PR#4502)"
|
|
|
|
~tree:[T.d "must_ignore" [ T.f "dirty.mli" ~content:"val bug : int"];
|
|
|
|
T.f "hello.ml" ~content:"print_endline \"Hello, World!\"";
|
|
|
|
T.f "_tags" ~content:""]
|
|
|
|
~pre_cmd:"ocamlc -c must_ignore/dirty.mli"
|
|
|
|
(* will make hygiene fail if must_ignore/ is checked *)
|
|
|
|
~targets:("hello.byte",[]) ();;
|
|
|
|
|
2013-06-30 01:34:42 -07:00
|
|
|
test "OutputObj"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind]
|
2013-06-30 01:34:42 -07:00
|
|
|
~description:"output_obj targets for native and bytecode (PR #6049)"
|
|
|
|
~tree:[T.f "hello.ml" ~content:"print_endline \"Hello, World!\""]
|
|
|
|
~targets:("hello.byte.o",["hello.byte.c";"hello.native.o"]) ();;
|
|
|
|
|
2013-06-30 16:28:18 -07:00
|
|
|
test "StrictSequenceFlag"
|
2013-07-26 17:02:13 -07:00
|
|
|
~options:[`no_ocamlfind; `quiet]
|
2013-06-30 16:28:18 -07:00
|
|
|
~description:"-strict_sequence tag"
|
|
|
|
~tree:[T.f "hello.ml" ~content:"let () = 1; ()";
|
|
|
|
T.f "_tags" ~content:"true: strict_sequence\n"]
|
|
|
|
~failing_msg:"File \"hello.ml\", line 1, characters 9-10:
|
|
|
|
Error: This expression has type int but an expression was expected of type
|
|
|
|
unit\nCommand exited with code 2."
|
|
|
|
~targets:("hello.byte",[]) ();;
|
|
|
|
|
2013-07-26 17:02:13 -07:00
|
|
|
test "PrincipalFlag"
|
|
|
|
~options:[`no_ocamlfind; `quiet]
|
2013-06-30 16:28:18 -07:00
|
|
|
~description:"-principal tag"
|
2013-09-15 04:36:12 -07:00
|
|
|
~tree:[T.f "hello.ml"
|
|
|
|
~content:"type s={foo:int;bar:unit} type t={foo:int}
|
|
|
|
let f x = (x.bar; x.foo)";
|
2013-06-30 16:28:18 -07:00
|
|
|
T.f "_tags" ~content:"true: principal\n"]
|
2013-09-15 04:36:14 -07:00
|
|
|
~failing_msg:"File \"hello.ml\", line 2, characters 42-45:
|
2013-06-30 16:28:18 -07:00
|
|
|
Warning 18: this type-based field disambiguation is not principal."
|
2013-08-20 09:02:37 -07:00
|
|
|
~targets:("hello.byte",[]) ();;
|
2013-06-30 16:28:18 -07:00
|
|
|
|
2013-08-19 00:42:39 -07:00
|
|
|
test "ModularPlugin1"
|
2013-08-24 13:46:05 -07:00
|
|
|
~options:[`no_ocamlfind; `quiet; `plugin_tag "use_str"]
|
2013-08-19 00:42:39 -07:00
|
|
|
~description:"test a plugin with dependency on external libraries"
|
|
|
|
~tree:[T.f "main.ml" ~content:"let x = 1";
|
|
|
|
T.f "myocamlbuild.ml" ~content:"ignore (Str.quote \"\");;"]
|
|
|
|
~matching:[M.f "main.byte"]
|
|
|
|
~targets:("main.byte",[]) ();;
|
|
|
|
|
|
|
|
test "ModularPlugin2"
|
|
|
|
~description:"check that parametrized tags defined by the plugin
|
|
|
|
do not warn at plugin-compilation time"
|
2013-08-20 09:02:37 -07:00
|
|
|
~options:[`no_ocamlfind; `quiet]
|
2013-08-19 00:42:39 -07:00
|
|
|
~tree:[T.f "main.ml" ~content:"let x = 1";
|
|
|
|
T.f "_tags" ~content:"<main.*>: toto(-g)";
|
|
|
|
T.f "myocamlbuild.ml"
|
|
|
|
~content:"open Ocamlbuild_plugin;;
|
|
|
|
pflag [\"link\"] \"toto\" (fun arg -> A arg);;"]
|
|
|
|
~failing_msg:""
|
|
|
|
~matching:[M.f "main.byte"]
|
|
|
|
~targets:("main.byte",[]) ();;
|
|
|
|
|
|
|
|
test "ModularPlugin3"
|
|
|
|
~description:"check that unknown parametrized tags encountered
|
|
|
|
during plugin compilation still warn"
|
2013-08-24 13:46:05 -07:00
|
|
|
~options:[`no_ocamlfind; `quiet; `plugin_tag "'toto(-g)'"]
|
2013-08-19 00:42:39 -07:00
|
|
|
~tree:[T.f "main.ml" ~content:"let x = 1";
|
|
|
|
T.f "myocamlbuild.ml"
|
|
|
|
~content:"open Ocamlbuild_plugin;;
|
|
|
|
pflag [\"link\"] \"toto\" (fun arg -> A arg);;"]
|
|
|
|
~failing_msg:"Warning: tag \"toto\" does not expect a parameter, \
|
|
|
|
but is used with parameter \"-g\""
|
|
|
|
~matching:[M.f "main.byte"]
|
|
|
|
~targets:("main.byte",[]) ();;
|
|
|
|
|
2013-09-15 04:36:12 -07:00
|
|
|
run ~root:"_test_internal";;
|