ocamltest: add the asmgen test

master
Sébastien Hinderer 2018-04-27 11:09:48 +02:00
parent 2d75541dfd
commit f1adcb8362
13 changed files with 215 additions and 0 deletions

View File

@ -223,6 +223,10 @@ ocamltest_config.ml: ocamltest_config.ml.in
-e 's|@@MKEXE@@|$(mkexe)|' \
-e 's|@@BYTECCLIBS@@|$(BYTECCLIBS)|' \
-e 's|@@NATIVECCLIBS@@|$(NATIVECCLIBS)|' \
-e 's|@@ASM@@|$(ASM)|' \
-e 's|@@CC@@|$(CC)|' \
-e 's|@@CFLAGS@@|$(CFLAGS)|' \
-e 's|@@CCOMPTYPE@@|$(CCOMPTYPE)|' \
$< > $@
.PHONY: clean

View File

@ -17,6 +17,13 @@
open Ocamltest_stdlib
let skip_with_reason reason =
let code _log env =
let result = Result.skip_with_reason reason in
(result, env)
in
Actions.make "skip" code
let pass_or_skip test pass_reason skip_reason _log env =
let open Result in
let result =

View File

@ -15,6 +15,8 @@
(* Helper functions when writing actions *)
val skip_with_reason : string -> Actions.t
val pass_or_skip
: bool -> string -> string -> out_channel -> Environments.t
-> Result.t * Environments.t

View File

@ -591,6 +591,134 @@ let mklib log env =
let ocamlmklib = Actions.make "ocamlmklib" mklib
let finalise_codegen_cc ocamlsrcdir test_basename _log env =
let test_module =
Filename.make_filename test_basename "s"
in
let archmod = Ocaml_files.asmgen_archmod ocamlsrcdir in
let modules = test_module ^ " " ^ archmod in
let program = Filename.make_filename test_basename "out" in
let env = Environments.add_bindings
[
Ocaml_variables.modules, modules;
Builtin_variables.program, program;
] env in
(Result.pass, env)
let finalise_codegen_msvc ocamlsrcdir test_basename log env =
let obj = Filename.make_filename test_basename Ocamltest_config.objext in
let src = Filename.make_filename test_basename "s" in
let what = "Running Microsoft assembler" in
Printf.fprintf log "%s\n%!" what;
let commandline = [Ocamltest_config.asm; obj; src] in
let expected_exit_status = 0 in
let exit_status =
Actions_helpers.run_cmd
~environment:dumb_term
~stdout_variable:Ocaml_variables.compiler_output
~stderr_variable:Ocaml_variables.compiler_output
~append:true
log env commandline in
if exit_status=expected_exit_status
then begin
let archmod = Ocaml_files.asmgen_archmod ocamlsrcdir in
let modules = obj ^ " " ^ archmod in
let program = Filename.make_filename test_basename "out" in
let env = Environments.add_bindings
[
Ocaml_variables.modules, modules;
Builtin_variables.program, program;
] env in
(Result.pass, env)
end else begin
let reason =
(Actions_helpers.mkreason
what (String.concat " " commandline) exit_status) in
(Result.fail_with_reason reason, env)
end
let run_codegen log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let testfile = Actions_helpers.testfile env in
let what = Printf.sprintf "Running codegen on %s" testfile in
Printf.fprintf log "%s\n%!" what;
let test_build_directory =
Actions_helpers.test_build_directory env in
let compiler_output =
Filename.make_path [test_build_directory; "compiler-output"]
in
let env =
Environments.add_if_undefined
Ocaml_variables.compiler_output
compiler_output
env
in
let commandline =
[
Ocaml_commands.ocamlrun_codegen ocamlsrcdir;
"-S " ^ testfile
] in
let expected_exit_status = 0 in
let exit_status =
Actions_helpers.run_cmd
~environment:dumb_term
~stdout_variable:Ocaml_variables.compiler_output
~stderr_variable:Ocaml_variables.compiler_output
~append:true
log env commandline in
if exit_status=expected_exit_status
then begin
let testfile_basename = Filename.chop_extension testfile in
let finalise =
if Ocamltest_config.ccomptype="msvc"
then finalise_codegen_msvc
else finalise_codegen_cc
in
finalise ocamlsrcdir testfile_basename log env
end else begin
let reason =
(Actions_helpers.mkreason
what (String.concat " " commandline) exit_status) in
(Result.fail_with_reason reason, env)
end
let codegen = Actions.make "codegen" run_codegen
let run_cc log env =
let ocamlsrcdir = Ocaml_directories.srcdir () in
let program = Environments.safe_lookup Builtin_variables.program env in
let what = Printf.sprintf "Running C compiler to build %s" program in
Printf.fprintf log "%s\n%!" what;
let output_exe =
if Ocamltest_config.ccomptype="msvc" then "/Fe" else "-o "
in
let commandline =
[
Ocamltest_config.cc;
Ocamltest_config.cflags;
"-I" ^ Ocaml_directories.runtime ocamlsrcdir;
output_exe ^ program;
Environments.safe_lookup Builtin_variables.arguments env;
] @ modules env in
let expected_exit_status = 0 in
let exit_status =
Actions_helpers.run_cmd
~environment:dumb_term
~stdout_variable:Ocaml_variables.compiler_output
~stderr_variable:Ocaml_variables.compiler_output
~append:true
log env commandline in
if exit_status=expected_exit_status
then (Result.pass, env)
else begin
let reason =
(Actions_helpers.mkreason
what (String.concat " " commandline) exit_status) in
(Result.fail_with_reason reason, env)
end
let cc = Actions.make "cc" run_cc
let run_expect_once ocamlsrcdir input_file principal log env =
let expect_flags = Sys.safe_getenv "EXPECT_FLAGS" in
let repo_root = "-repo-root " ^ ocamlsrcdir in
@ -1203,5 +1331,7 @@ let _ =
check_ocamldoc_output;
ocamldebug;
ocamlmklib;
codegen;
cc;
ocamlobjinfo
]

View File

@ -50,3 +50,7 @@ val native_compiler : Actions.t
val afl_instrument : Actions.t
val no_afl_instrument : Actions.t
val codegen : Actions.t
val cc : Actions.t

View File

@ -40,3 +40,6 @@ let ocamlrun_ocamlobjinfo ocamlsrcdir =
let ocamlrun_ocamlmklib ocamlsrcdir =
ocamlrun ocamlsrcdir Ocaml_files.ocamlmklib
let ocamlrun_codegen ocamlsrcdir =
ocamlrun ocamlsrcdir Ocaml_files.codegen

View File

@ -32,3 +32,4 @@ val ocamlrun_ocamldebug : string -> string
val ocamlrun_ocamlobjinfo : string -> string
val ocamlrun_ocamlmklib : string -> string
val ocamlrun_codegen : string -> string

View File

@ -78,3 +78,12 @@ let ocamlobjinfo ocamlsrcdir =
let ocamlmklib ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "tools"; "ocamlmklib"]
let codegen ocamlsrcdir =
Filename.make_path [ocamlsrcdir; "testsuite"; "tools"; "codegen"]
let asmgen_archmod ocamlsrcdir =
let objname =
"asmgen_" ^ Ocamltest_config.arch ^ "." ^ Ocamltest_config.objext
in
Filename.make_path [ocamlsrcdir; "testsuite"; "tools"; objname]

View File

@ -48,3 +48,6 @@ val ocamldoc : string -> string
val ocamldebug : string -> string
val ocamlobjinfo : string -> string
val ocamlmklib : string -> string
val codegen : string -> string
val asmgen_archmod : string -> string

View File

@ -105,6 +105,35 @@ let ocamldoc =
[ skip ]
}
let asmgen_skip_on_bytecode_only =
Actions_helpers.skip_with_reason "native compiler disabled"
let asmgen_skip_on_spacetime =
Actions_helpers.skip_with_reason "not ported to Spacetime yet"
let msvc64 =
Ocamltest_config.ccomptype = "msvc" && Ocamltest_config.arch="amd64"
let asmgen_skip_on_msvc64 =
Actions_helpers.skip_with_reason "not ported to MSVC64 yet"
let asmgen_actions =
if Ocamltest_config.arch="none" then [asmgen_skip_on_bytecode_only]
else if Ocamltest_config.spacetime then [asmgen_skip_on_spacetime]
else if msvc64 then [asmgen_skip_on_msvc64]
else [
setup_simple_build_env;
codegen;
cc;
]
let asmgen =
{
test_name = "asmgen";
test_run_by_default = false;
test_actions = asmgen_actions
}
let _ =
List.iter register
[
@ -113,4 +142,5 @@ let _ =
toplevel;
expect;
ocamldoc;
asmgen;
]

View File

@ -24,3 +24,5 @@ val toplevel : Tests.t
val expect : Tests.t
val ocamldoc : Tests.t
val asmgen : Tests.t

View File

@ -19,6 +19,14 @@ let arch = "@@ARCH@@"
let afl_instrument = @@AFL_INSTRUMENT@@
let asm = "@@ASM@@"
let cc = "@@CC@@"
let cflags = "@@CFLAGS@@"
let ccomptype = "@@CCOMPTYPE@@"
let shared_libraries = @@SHARED_LIBRARIES@@
let libunix = @@UNIX@@

View File

@ -21,6 +21,18 @@ val arch : string
val afl_instrument : bool
(** Whether AFL support has been enabled in the compiler *)
val asm : string
(** Path to the assembler*)
val cc : string
(** Path to the C compiler*)
val cflags : string
(** Flags to pass to the C compiler *)
val ccomptype : string
(** Type of C compiler (msvc, cc, etc.) *)
val shared_libraries : bool
(** [true] if shared libraries are supported, [false] otherwise *)