Skip to content

Commit

Permalink
Port win-unicode test to ocamltest
Browse files Browse the repository at this point in the history
  • Loading branch information
nojb committed Apr 19, 2018
1 parent c436833 commit 8b20939
Show file tree
Hide file tree
Showing 10 changed files with 57 additions and 96 deletions.
2 changes: 0 additions & 2 deletions .gitignore
Expand Up @@ -307,8 +307,6 @@ _ocamltestd

/testsuite/tests/unwind/unwind_test

/testsuite/tests/win-unicode/symlink_tests.precheck

/testsuite/tools/expect_test

/tools/ocamldep
Expand Down
28 changes: 0 additions & 28 deletions testsuite/tests/win-unicode/Makefile

This file was deleted.

8 changes: 8 additions & 0 deletions testsuite/tests/win-unicode/exec_tests.ml 100755 → 100644
@@ -1,3 +1,11 @@
(* TEST
flags += "-strict-sequence -safe-string -w A -warn-error A"
include unix
* windows-unicode
** bytecode
** native
*)

let values =
[
"\xD0\xB2\xD0\xB5\xD1\x80\xD0\xB1\xD0\xBB\xD1\x8E\xD0\xB4\xD1\x8B"; (* "верблюды" *)
Expand Down
3 changes: 0 additions & 3 deletions testsuite/tests/win-unicode/exec_tests.precheck

This file was deleted.

34 changes: 32 additions & 2 deletions testsuite/tests/win-unicode/mltest.ml
@@ -1,3 +1,33 @@
(* TEST
include unix
flags += "-strict-sequence -safe-string -w A -warn-error A"
files = "print.ml mkfiles.c"
* windows-unicode
** setup-ocamlc.byte-build-env
program = "${test_build_directory}/mltest.byte"
*** ocamlc.byte
program = "${test_build_directory}/print.exe"
all_modules = "print.ml"
**** ocamlc.byte
program = "${test_build_directory}/mltest.byte"
all_modules= "mkfiles.c mltest.ml"
***** check-ocamlc.byte-output
****** run
******* check-program-output
** setup-ocamlopt.byte-build-env
program = "${test_build_directory}/mltest.opt"
*** ocamlc.byte
program = "${test_build_directory}/print.exe"
all_modules = "print.ml"
**** ocamlopt.byte
program = "${test_build_directory}/mltest.opt"
all_modules= "mkfiles.c mltest.ml"
***** check-ocamlopt.byte-output
****** run
******* check-program-output
*)

let total = ref 0
let failed = ref 0
let num = ref 0
Expand Down Expand Up @@ -354,15 +384,15 @@ let test_remove remove =

let test_open_process_in () =
let cmdline =
String.concat " " (Filename.concat Filename.current_dir_name "printargv.exe" :: List.map Filename.quote to_create_and_delete_files)
String.concat " " ("print.exe" :: List.map Filename.quote to_create_and_delete_files)
in
let l = open_process_in cmdline in
List.iter2 expect_string l to_create_and_delete_files

let test_open_process_full () =
let vars = List.map (fun s -> fst (split '=' s)) env0 in
let filter s = List.mem (fst (split '=' s)) vars in
let l = open_process_full filter (Filename.concat Filename.current_dir_name "printenv.exe") env0 in
let l = open_process_full filter "print.exe env" env0 in
expect_int (List.length env0) (List.length l);
List.iter2 expect_string env0 l

Expand Down
3 changes: 3 additions & 0 deletions testsuite/tests/win-unicode/ocamltests
@@ -0,0 +1,3 @@
mltest.ml
exec_tests.ml
symlink_tests.ml
5 changes: 5 additions & 0 deletions testsuite/tests/win-unicode/print.ml
@@ -0,0 +1,5 @@
let () =
if Array.length Sys.argv > 1 && Sys.argv.(1) = "env" then
Array.iter print_endline (Unix.environment ())
else
Array.iter print_endline Sys.argv
25 changes: 0 additions & 25 deletions testsuite/tests/win-unicode/printargv.c

This file was deleted.

36 changes: 0 additions & 36 deletions testsuite/tests/win-unicode/printenv.c

This file was deleted.

9 changes: 9 additions & 0 deletions testsuite/tests/win-unicode/symlink_tests.ml 100755 → 100644
@@ -1,3 +1,12 @@
(* TEST
flags += "-strict-sequence -safe-string -w A -warn-error A"
files = "mkfiles.c"
include unix
* windows-unicode
** has_symlink
*** bytecode
*** native
*)
external to_utf16 : string -> string = "caml_to_utf16"
external create_file : string -> string -> unit = "caml_create_file"

Expand Down

0 comments on commit 8b20939

Please sign in to comment.