Skip to content

Commit

Permalink
Merge pull request #1519 from shindere/migrate-expect-tests
Browse files Browse the repository at this point in the history
Migrate expect tests to ocamltest
  • Loading branch information
gasche committed Dec 12, 2017
2 parents 015d158 + 2e46ae4 commit b0a59c3
Show file tree
Hide file tree
Showing 111 changed files with 528 additions and 195 deletions.
4 changes: 0 additions & 4 deletions .gitignore
Expand Up @@ -325,10 +325,6 @@ _ocamltest
/testsuite/tests/tool-lexyacc/grammar.mli
/testsuite/tests/tool-lexyacc/grammar.ml

/testsuite/tests/typing-misc/false.flat-float
/testsuite/tests/typing-misc/true.flat-float
/testsuite/tests/typing-misc/pr6939.ml

/testsuite/tests/typing-multifile/a.ml
/testsuite/tests/typing-multifile/b.ml
/testsuite/tests/typing-multifile/c.ml
Expand Down
1 change: 1 addition & 0 deletions ocamltest/Makefile
Expand Up @@ -177,6 +177,7 @@ ocamltest_config.ml: ocamltest_config.ml.in
-e 's|@@OCAMLSRCDIR@@|$(ocamlsrcdir)|' \
-e 's|@@FLAMBDA@@|$(FLAMBDA)|' \
-e 's|@@FORCE_SAFE_STRING@@|$(FORCE_SAFE_STRING)|' \
-e 's|@@FLAT_FLOAT_ARRAY@@|$(FLAT_FLOAT_ARRAY)|' \
$< > $@

.PHONY: clean
Expand Down
9 changes: 9 additions & 0 deletions ocamltest/actions_helpers.ml
Expand Up @@ -33,6 +33,9 @@ let test_source_directory env =
let test_build_directory env =
Environments.safe_lookup Builtin_variables.test_build_directory env

let test_build_directory_prefix env =
Environments.safe_lookup Builtin_variables.test_build_directory_prefix env

let words_of_variable env variable =
String.words (Environments.safe_lookup variable env)

Expand Down Expand Up @@ -62,6 +65,12 @@ let setup_build_env add_testfile additional_files (_log : out_channel) env =
Sys.chdir build_dir;
Pass env

let setup_simple_build_env add_testfile additional_files log env =
let build_env = Environments.add
Builtin_variables.test_build_directory
(test_build_directory_prefix env) env in
setup_build_env add_testfile additional_files log build_env

let run_cmd
?(environment=[||])
?(stdin_variable=Builtin_variables.stdin)
Expand Down
2 changes: 2 additions & 0 deletions ocamltest/actions_helpers.mli
Expand Up @@ -31,6 +31,8 @@ val setup_symlinks : string -> string -> string list -> unit

val setup_build_env : bool -> string list -> Actions.code

val setup_simple_build_env : bool -> string list -> Actions.code

val run_cmd :
?environment : string array ->
?stdin_variable : Variables.t ->
Expand Down
4 changes: 4 additions & 0 deletions ocamltest/builtin_actions.ml
Expand Up @@ -63,6 +63,10 @@ let setup_build_env = make
"setup-build-env"
(Actions_helpers.setup_build_env true [])

let setup_simple_build_env = make
"setup-simple-build-env"
(Actions_helpers.setup_simple_build_env true [])

let run = make
"run"
Actions_helpers.run_program
Expand Down
4 changes: 4 additions & 0 deletions ocamltest/builtin_actions.mli
Expand Up @@ -24,6 +24,10 @@ val dumpenv : Actions.t
val unix : Actions.t
val windows : Actions.t

val setup_build_env : Actions.t

val setup_simple_build_env : Actions.t

val run : Actions.t
val script : Actions.t

Expand Down
6 changes: 4 additions & 2 deletions ocamltest/main.ml
Expand Up @@ -140,10 +140,12 @@ let test_file test_filename =
Builtin_variables.test_file, test_basename;
Builtin_variables.reference, reference_filename;
Builtin_variables.test_source_directory, test_source_directory;
Builtin_variables.test_build_directory_prefix, test_build_directory_prefix;
Builtin_variables.test_build_directory_prefix,
test_build_directory_prefix;
] in
let root_environment =
interprete_environment_statements initial_environment rootenv_statements in
interprete_environment_statements
initial_environment rootenv_statements in
let rootenv = Environments.initialize log root_environment in
let common_prefix = " ... testing '" ^ test_basename ^ "' with" in
List.iteri
Expand Down
81 changes: 77 additions & 4 deletions ocamltest/ocaml_actions.ml
Expand Up @@ -79,6 +79,15 @@ let ocaml_dot_opt ocamlsrcdir =
let cmpbyt ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "tools"; "cmpbyt"]

let expect_program ocamlsrcdir =
Filename.make_path
[ocamlsrcdir; "testsuite"; "tools"; Filename.mkexe "expect_test"]

let expect_command ocamlsrcdir =
let ocamlrun = ocamlrun ocamlsrcdir in
let expect_test = expect_program ocamlsrcdir in
ocamlrun ^ " " ^ expect_test

let stdlib ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "stdlib"]

Expand Down Expand Up @@ -450,11 +459,51 @@ let ocamlopt_opt = Actions.make
"ocamlopt.opt"
(compile_test_program Builtin_variables.program2 ocamlopt_opt_compiler)

let run_expect_once ocamlsrcdir input_file principal log env =
let expect_flags = try Sys.getenv "EXPECT_FLAGS" with Not_found -> "" in
let repo_root = "-repo-root " ^ ocamlsrcdir in
let principal_flag = if principal then "-principal" else "" in
let commandline =
[
expect_command ocamlsrcdir;
expect_flags;
flags env;
repo_root;
principal_flag;
input_file
] in
let exit_status = Actions_helpers.run_cmd log env commandline in
if exit_status=0 then Pass env
else Fail (Actions_helpers.mkreason
"expect" (String.concat " " commandline) exit_status)

let run_expect_twice ocamlsrcdir input_file log env =
let corrected filename = Filename.make_filename filename "corrected" in
let first_run = run_expect_once ocamlsrcdir input_file false log env in
match first_run with
| Skip _ | Fail _ -> first_run
| Pass env1 ->
let intermediate_file = corrected input_file in
let second_run =
run_expect_once ocamlsrcdir intermediate_file true log env1 in
(match second_run with
| Skip _ | Fail _ -> second_run
| Pass env2 ->
let output_file = corrected intermediate_file in
let output_env = Environments.add_bindings
[
Builtin_variables.reference, input_file;
Builtin_variables.output, output_file
] env2 in
Pass output_env
)

let run_expect log env =
let newenv = Environments.apply_modifiers env Ocaml_modifiers.expect in
Actions_helpers.run_script log newenv
let ocamlsrcdir = ocamlsrcdir () in
let input_file = Actions_helpers.testfile env in
run_expect_twice ocamlsrcdir input_file log env

let expect = Actions.make "expect" run_expect
let run_expect = Actions.make "run-expect" run_expect

let make_check_compiler_output name compiler = Actions.make
name
Expand Down Expand Up @@ -623,6 +672,28 @@ let config_variables _log env = Environments.add_bindings
Ocaml_variables.os_type, Sys.os_type;
] env

let flat_float_array = Actions.make
"flat-float-array"
(fun log env ->
if Ocamltest_config.flat_float_array then
begin
Printf.fprintf log
"The flat-float-array action succeeds.\n%!";
Pass env
end else
Skip "Compiler configured with -no-flat-float-array.")

let no_flat_float_array = make
"no-flat-float-array"
(fun log env ->
if not Ocamltest_config.flat_float_array then
begin
Printf.fprintf log
"The no-flat-float-array action succeeds.\n%!";
Pass env
end else
Skip "The compiler has been configured with -flat-float-array.")

let _ =
Environments.register_initializer "find_source_modules" find_source_modules;
Environments.register_initializer "config_variables" config_variables;
Expand All @@ -640,7 +711,7 @@ let _ =
setup_ocamlopt_opt_build_env;
ocamlopt_opt;
check_ocamlopt_opt_output;
expect;
run_expect;
compare_bytecode_programs;
compare_native_programs;
setup_ocaml_build_env;
Expand All @@ -649,4 +720,6 @@ let _ =
setup_ocamlnat_build_env;
ocamlnat;
check_ocamlnat_output;
flat_float_array;
no_flat_float_array;
]
5 changes: 4 additions & 1 deletion ocamltest/ocaml_actions.mli
Expand Up @@ -27,7 +27,7 @@ val check_ocamlopt_byte_output : Actions.t
val setup_ocamlopt_opt_build_env : Actions.t
val ocamlopt_opt : Actions.t
val check_ocamlopt_opt_output : Actions.t
val expect : Actions.t
val run_expect : Actions.t
val compare_bytecode_programs : Actions.t
val compare_native_programs : Actions.t
val setup_ocaml_build_env : Actions.t
Expand All @@ -36,3 +36,6 @@ val check_ocaml_output : Actions.t
val setup_ocamlnat_build_env : Actions.t
val ocamlnat : Actions.t
val check_ocamlnat_output : Actions.t

val flat_float_array : Actions.t
val no_flat_float_array : Actions.t
25 changes: 10 additions & 15 deletions ocamltest/ocaml_modifiers.ml
Expand Up @@ -18,12 +18,6 @@
open Ocamltest_stdlib
open Environments

let expect =
[
Add (Builtin_variables.script,
"bash ${OCAMLSRCDIR}/testsuite/tools/expect");
]

let principal =
[
Append (Ocaml_variables.flags, " -principal ");
Expand Down Expand Up @@ -57,18 +51,19 @@ let bigarray =
let str = make_library_modifier
"str" (compiler_subdir ["otherlibs"; "str"])

let compilerlibs_subdirs =
[
"utils"; "parsing"; "typing"; "bytecomp"; "compilerlibs";
]

let add_compiler_subdir subdir =
Append (Ocaml_variables.directories, (wrap (compiler_subdir [subdir])))

let ocamlcommon =
[
Append (Ocaml_variables.directories, wrap (compiler_subdir ["utils"]));
Append (Ocaml_variables.directories, wrap (compiler_subdir ["parsing"]));
Append (Ocaml_variables.directories, wrap (compiler_subdir ["typing"]));
Append (Ocaml_variables.directories, wrap (compiler_subdir ["bytecomp"]));
Append (Ocaml_variables.directories, wrap (compiler_subdir ["compilerlibs"]));
Append (Ocaml_variables.libraries, wrap "ocamlcommon");
]
(Append (Ocaml_variables.libraries, wrap "ocamlcommon")) ::
(List.map add_compiler_subdir compilerlibs_subdirs)

let _ =
register_modifiers "expect" expect;
register_modifiers "principal" principal;
register_modifiers "testing" testing;
register_modifiers "unix" unix;
Expand Down
2 changes: 0 additions & 2 deletions ocamltest/ocaml_modifiers.mli
Expand Up @@ -15,8 +15,6 @@

(* Definition of a few OCaml-specific environment modifiers *)

val expect : Environments.modifiers

val principal : Environments.modifiers

val testing : Environments.modifiers
Expand Down
13 changes: 13 additions & 0 deletions ocamltest/ocaml_tests.ml
Expand Up @@ -73,10 +73,23 @@ let toplevel = {
]
}

let expect =
{
test_name = "expect";
test_run_by_default = false;
test_actions =
[
setup_simple_build_env;
run_expect;
check_program_output
]
}

let _ =
List.iter register
[
bytecode;
toplevel;
expect;
];
if (Ocamltest_config.arch <> "none") then register native
2 changes: 2 additions & 0 deletions ocamltest/ocaml_tests.mli
Expand Up @@ -20,3 +20,5 @@ val bytecode : Tests.t
val native : Tests.t

val toplevel : Tests.t

val expect : Tests.t
2 changes: 2 additions & 0 deletions ocamltest/ocamltest_config.ml.in
Expand Up @@ -29,3 +29,5 @@ let ocamlc_default_flags = "@@OCAMLCDEFAULTFLAGS@@"
let ocamlopt_default_flags = "@@OCAMLOPTDEFAULTFLAGS@@"

let safe_string = @@FORCE_SAFE_STRING@@

let flat_float_array = @@FLAT_FLOAT_ARRAY@@
4 changes: 3 additions & 1 deletion ocamltest/ocamltest_config.mli
Expand Up @@ -24,7 +24,6 @@ val unix : bool
val c_preprocessor : string
(** Command to use to invoke the C preprocessor *)


val ocamlc_default_flags : string
(** Flags passed by default to ocamlc.byte and ocamlc.opt *)

Expand All @@ -39,3 +38,6 @@ val flambda : bool

val safe_string : bool
(** Whether the compiler was configured with -safe-string *)

val flat_float_array : bool
(* Whether the compiler was configured with -flat-float-array *)
3 changes: 0 additions & 3 deletions testsuite/tests/messages/Makefile

This file was deleted.

1 change: 1 addition & 0 deletions testsuite/tests/messages/ocamltests
@@ -0,0 +1 @@
precise_locations.ml
4 changes: 4 additions & 0 deletions testsuite/tests/messages/precise_locations.ml
@@ -1,3 +1,7 @@
(* TEST
* expect
*)

type t = (unit, unit, unit, unit) bar
;;
(* PR#7315: we expect the error location on "bar" instead of "(...) bar" *)
Expand Down
19 changes: 0 additions & 19 deletions testsuite/tests/typing-core-bugs/Makefile

This file was deleted.

4 changes: 4 additions & 0 deletions testsuite/tests/typing-core-bugs/example_let_missing_rec.ml
@@ -1,3 +1,7 @@
(* TEST
* expect
*)

let facto n = (* missing [rec] *)
if n = 0 then 1 else n * facto (n-1)

Expand Down
@@ -1,3 +1,7 @@
(* TEST
* expect
*)

let x = 3 in
let f x = f x in
();;
Expand Down
@@ -1,3 +1,7 @@
(* TEST
* expect
*)

let f x = if x < 0 then x else h (x-1)
and g x = if x < 0 then x else f (x-1)
and h x = if x < 0 then x else g (x-1)
Expand Down
4 changes: 4 additions & 0 deletions testsuite/tests/typing-core-bugs/ocamltests
@@ -0,0 +1,4 @@
example_let_missing_rec_loc.ml
example_let_missing_rec.ml
example_let_missing_rec_mutual.ml
unit_fun_hints.ml
5 changes: 5 additions & 0 deletions testsuite/tests/typing-core-bugs/unit_fun_hints.ml
@@ -1,3 +1,8 @@
(* TEST
flags = "-strict-sequence"
* expect
*)

let g f = f ()
let _ = g 3;; (* missing `fun () ->' *)

Expand Down

0 comments on commit b0a59c3

Please sign in to comment.