Skip to content

Commit

Permalink
tune testsuite for msvc
Browse files Browse the repository at this point in the history
  • Loading branch information
hhugo committed Jun 26, 2024
1 parent e73a665 commit da492c9
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 25 deletions.
2 changes: 1 addition & 1 deletion testsuite/findlibonly_test_header.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
match Sys.command "ocamlfind ocamlc -version" with
match sys_command "ocamlfind ocamlc -version" with
| 0 -> ()
| _ ->
prerr_endline "Having ocamlfind installed is a prerequisite \
Expand Down
24 changes: 10 additions & 14 deletions testsuite/internal.ml
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,7 @@ let () = test "BasicNativeTree"
"dummy.ml";
"dummy.ml.depends";
"dummy.native";
"dummy.o";
"dummy" -.- o;
"_log"]))]
~targets:("dummy.native",[]) ();;

Expand Down Expand Up @@ -250,25 +250,23 @@ let () = test "OutputObj"
~description:"output_obj targets for native and bytecode (PR #6049)"
~requirements:ocamlopt_available
~tree:[T.f "hello.ml" ~content:{|print_endline "Hello, World!"|}]
~targets:("hello.byte.o",["hello.byte.c";"hello.native.o"]) ();;

let so = if Sys.win32 then "dll" else "so"
~targets:("hello.byte" -.- o,["hello.byte.c";"hello.native" -.- o]) ();;

let () = test "OutputShared"
~options:[`no_ocamlfind]
~description:"output_shared targets for native and bytecode (PR #6733)"
~requirements:ocamlopt_available
~tree:[T.f "hello.ml" ~content:{|print_endline "Hello, World!"|};
T.f "_tags" ~content:"<*.so>: runtime_variant(_pic)"]
~targets:("hello.byte."^so,["hello.native."^so]) ();;
~targets:("hello.byte" -.- so,["hello.native" -.- so]) ();;

let () = test "CmxsStubLink"
~options:[`no_ocamlfind]
~description:".cmxs link rules pass correct -I flags"
~requirements:ocamlopt_available
~tree:[T.d "src" [
T.f "foo_stubs.c" ~content:"";
T.f "libfoo_stubs.clib" ~content:"foo_stubs.o";
T.f "libfoo_stubs.clib" ~content:("foo_stubs" -.- o) ;
T.f "foo.ml" ~content:"";
];
T.f "_tags" ~content:{|
Expand All @@ -280,9 +278,9 @@ open Ocamlbuild_plugin
let () =
dispatch begin function
| After_rules ->
dep ["record_foo_stubs"] ["src/libfoo_stubs.a"];
dep ["record_foo_stubs"] ["src/libfoo_stubs" -.- !Options.ext_lib];
flag_and_dep
["link"; "ocaml"; "link_foo_stubs"] (P "src/libfoo_stubs.a");
["link"; "ocaml"; "link_foo_stubs"] (P ("src/libfoo_stubs" -.- !Options.ext_lib));
flag ["library"; "ocaml"; "record_foo_stubs"]
(S ([A "-cclib"; A "-lfoo_stubs"]));
| _ -> ()
Expand Down Expand Up @@ -414,22 +412,20 @@ pflag ["link"] "toto" (fun arg -> A arg);;
~matching:[M.f "main.byte"]
~targets:("main.byte",[]) ();;

let exe_suf = if Sys.win32 then ".exe" else ""

let () = test "PluginCompilation1"
~description:"check that the plugin is not compiled when -no-plugin is passed"
~options:[`no_ocamlfind; `no_plugin]
~tree:[T.f "main.ml" ~content:"let x = 1";
T.f "myocamlbuild.ml" ~content:{|prerr_endline "foo";;|}]
~matching:[_build [M.Not (M.f ("myocamlbuild" ^ exe_suf))]]
~matching:[_build [M.Not (M.f ("myocamlbuild" ^ Ocamlbuild_config.exe))]]
~targets:("main.byte",[]) ();;

let () = test "PluginCompilation2"
~description:"check that the plugin is compiled when -just-plugin is passed"
~options:[`no_ocamlfind; `just_plugin]
~tree:[T.f "main.ml" ~content:"let x = 1";
T.f "myocamlbuild.ml" ~content:{|print_endline "foo";;|}]
~matching:[_build [M.f ("myocamlbuild" ^ exe_suf)]]
~matching:[_build [M.f ("myocamlbuild" ^ Ocamlbuild_config.exe)]]
~targets:("", []) ();;

let () = test "PluginCompilation3"
Expand Down Expand Up @@ -516,7 +512,7 @@ let () = test "TargetsStartingWithUnderscore"
*)
~options:[`no_ocamlfind]
~tree:[ T.f "_a.c" ~content:"" ]
~targets:("_a.o", []) ();;
~targets:("_a" -.- o, []) ();;

let () = test "OpaqueEverything"
~description:"Check that tagging everything opaque does not break build"
Expand Down Expand Up @@ -563,7 +559,7 @@ CAMLprim value hello_world(value unit)
}
|};
]
~targets:("libtest.a", []) ();;
~targets:("libtest" -.- a, []) ();;

let () = test "JustNoPlugin"
~description:"(ocamlbuild -just-plugin) should do nothing when no plugin is there"
Expand Down
30 changes: 20 additions & 10 deletions testsuite/ocamlbuild_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,17 @@
(* *)
(***********************************************************************)

#directory "../plugin-lib/";;
#directory "../src/";;

#load "../src/ocamlbuild_config.cmo"
#load "../plugin-lib/ocamlbuildlib.cma";;

open Format

module My_std = Ocamlbuild_pack.My_std
open Ocamlbuild_pack.Pathname.Operators

external (|>) : 'a -> ('a -> 'b) -> 'b = "%revapply"

let print_list ~sep f ppf = function
Expand All @@ -30,7 +39,7 @@ let print_string_list = print_list_com pp_print_string
let print_string_list_com = print_list_com pp_print_string
let print_string_list_blank = print_list_blank pp_print_string

let exists filename = Sys.file_exists filename
let exists filename = My_std.sys_file_exists filename

let execute cmd =
let ic = Unix.open_process_in cmd and lst = ref [] in
Expand All @@ -40,11 +49,7 @@ let execute cmd =
let ret_code = Unix.close_process_in ic
in ret_code, List.rev !lst

(* Simplified implementation of My_std.sys_command to avoid duplicating code. *)
let sys_command cmd =
if Sys.win32
then Sys.command (Printf.sprintf "bash --norc --noprofile -c %S" cmd)
else Sys.command cmd
let sys_command cmd = My_std.sys_command cmd

let rm f =
if exists f then
Expand Down Expand Up @@ -113,6 +118,7 @@ module Match = struct
let x ?(atts=()) name ~output = X ((atts,name), (0,output))

let match_with_fs ~root m =
My_std.reset_readdir_cache ();
let rec visit ~exact ~successes ~errors path m =
let string_of_path path = "./" ^ String.concat "/" (List.rev path) in
let file name = string_of_path (name :: path) in
Expand Down Expand Up @@ -386,6 +392,10 @@ module Tree = struct

end

let a = Ocamlbuild_config.a
let o = Ocamlbuild_config.o
let so = Ocamlbuild_config.so

type content = string
type filename = string
type run = filename * content
Expand Down Expand Up @@ -468,16 +478,16 @@ let run ~root =
copy
[ "plugin-lib/ocamlbuildlib.cma";
"plugin-lib/ocamlbuildlib.cmxa";
"plugin-lib/ocamlbuildlib.a";
"plugin-lib/ocamlbuildlib" -.- a;
"bin/ocamlbuild.cmo";
"bin/ocamlbuild.cmx";
"bin/ocamlbuild.o";
"bin/ocamlbuild" -.- o;
"src/ocamlbuild_pack.cmi";
"src/ocamlbuild_pack.cmx";
"src/ocamlbuild_pack.o";
"src/ocamlbuild_pack" -.- o;
"plugin-lib/ocamlbuild_plugin.cmi";
"plugin-lib/ocamlbuild_plugin.cmx";
"plugin-lib/ocamlbuild_plugin.o" ]
"plugin-lib/ocamlbuild_plugin" -.- o ]
install_lib_dir;
copy
[ "ocamlbuild.byte";
Expand Down

0 comments on commit da492c9

Please sign in to comment.