Skip to content

Commit

Permalink
ocamltest: pass timeout as an ocamltest 'variable'
Browse files Browse the repository at this point in the history
  • Loading branch information
gasche committed Jan 2, 2021
1 parent 36f93fc commit 407132a
Show file tree
Hide file tree
Showing 9 changed files with 42 additions and 8 deletions.
19 changes: 15 additions & 4 deletions ocamltest/actions_helpers.ml
Original file line number Diff line number Diff line change
Expand Up @@ -101,15 +101,13 @@ let setup_simple_build_env add_testfile additional_files log env =
(test_build_directory_prefix env) env in
setup_build_env add_testfile additional_files log build_env

let default_timeout = ref 0

let run_cmd
?(environment=[||])
?(stdin_variable=Builtin_variables.stdin)
?(stdout_variable=Builtin_variables.stdout)
?(stderr_variable=Builtin_variables.stderr)
?(append=false)
?(timeout= !default_timeout)
?timeout
log env original_cmd
=
let log_redirection std filename =
Expand Down Expand Up @@ -153,6 +151,15 @@ let run_cmd
environment
(Environments.to_system_env env)
in
let timeout =
match timeout with
| Some timeout -> timeout
| None ->
begin match Environments.lookup_as_int Builtin_variables.timeout env with
| Some timeout -> timeout
| None -> 0
end
in
let n =
Run_command.run {
Run_command.progname = progname;
Expand Down Expand Up @@ -275,6 +282,10 @@ let run_hook hook_name log input_env =
Builtin_variables.ocamltest_response response_file input_env in
let systemenv =
Environments.to_system_env hookenv in
let timeout =
match Environments.lookup_as_int Builtin_variables.timeout input_env with
| None -> 0
| Some timeout -> timeout in
let open Run_command in
let settings = {
progname = "sh";
Expand All @@ -284,7 +295,7 @@ let run_hook hook_name log input_env =
stdout_filename = "";
stderr_filename = "";
append = false;
timeout = !default_timeout;
timeout = timeout;
log = log;
} in let exit_status = run settings in
let final_value = match exit_status with
Expand Down
2 changes: 0 additions & 2 deletions ocamltest/actions_helpers.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,6 @@ val setup_build_env : bool -> string list -> Actions.code

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

val default_timeout : int ref

val run_cmd :
?environment : string array ->
?stdin_variable : Variables.t ->
Expand Down
4 changes: 3 additions & 1 deletion ocamltest/builtin_variables.ml
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,8 @@ let test_skip = Variables.make ("TEST_SKIP",
let test_fail = Variables.make ("TEST_FAIL",
"Exit code to let a script report failure")


let timeout = Variables.make ("timeout",
"Maximal execution time for every command (in seconds)")

let _ = List.iter Variables.register_variable
[
Expand Down Expand Up @@ -129,4 +130,5 @@ let _ = List.iter Variables.register_variable
test_pass;
test_skip;
test_fail;
timeout;
]
2 changes: 2 additions & 0 deletions ocamltest/builtin_variables.mli
Original file line number Diff line number Diff line change
Expand Up @@ -65,3 +65,5 @@ val test_pass : Variables.t
val test_skip : Variables.t

val test_fail : Variables.t

val timeout : Variables.t
9 changes: 9 additions & 0 deletions ocamltest/environments.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,15 @@ let lookup_as_bool variable env =
| Some "true" -> Some true
| Some _ -> Some false

let lookup_as_int variable env =
match lookup variable env with
| None -> None
| Some value ->
begin match int_of_string value with
| exception _ -> None
| n -> Some n
end

let safe_lookup variable env = match lookup variable env with
| None -> ""
| Some value -> value
Expand Down
5 changes: 5 additions & 0 deletions ocamltest/environments.mli
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,11 @@ val lookup_as_bool : Variables.t -> t -> bool option
[Some false] if it is set to another string, and
[None] if not set. *)

val lookup_as_int : Variables.t -> t -> int option
(** returns [Some n] if the variable is set to a string
representation of the integer [n],
and [None] if it is not an integer or not set. *)

val add : Variables.t -> string -> t -> t
val add_if_undefined : Variables.t -> string -> t -> t
val add_bindings : (Variables.t * string) list -> t -> t
Expand Down
2 changes: 2 additions & 0 deletions ocamltest/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -167,6 +167,7 @@ let test_file test_filename =
let summary = Sys.with_chdir test_build_directory_prefix
(fun () ->
let promote = string_of_bool Options.promote in
let default_timeout = string_of_int Options.default_timeout in
let install_hook name =
let hook_name = Filename.make_filename hookname_prefix name in
if Sys.file_exists hook_name then begin
Expand All @@ -187,6 +188,7 @@ let test_file test_filename =
Builtin_variables.test_build_directory_prefix,
test_build_directory_prefix;
Builtin_variables.promote, promote;
Builtin_variables.timeout, default_timeout;
] in
let rootenv =
Environments.initialize Environments.Pre log initial_environment in
Expand Down
5 changes: 4 additions & 1 deletion ocamltest/options.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,8 @@ let log_to_stderr = ref false

let promote = ref false

let default_timeout = ref 0

let keep_test_dir_on_success = ref false

let find_test_dirs = ref []
Expand All @@ -68,7 +70,7 @@ let commandline_options =
("-show-variables", Arg.Unit show_variables, " Show available variables.");
("-timeout",
Arg.Int (fun t -> if t >= 0
then Actions_helpers.default_timeout := t
then default_timeout := t
else raise (Arg.Bad "negative timeout")),
"<seconds> Set maximal execution time for every command (in seconds)");
("-find-test-dirs", Arg.String (add_to_list find_test_dirs),
Expand All @@ -89,6 +91,7 @@ let () =
let log_to_stderr = !log_to_stderr
let files_to_test = !files_to_test
let promote = !promote
let default_timeout = !default_timeout
let find_test_dirs = !find_test_dirs
let list_tests = !list_tests
let keep_test_dir_on_success = !keep_test_dir_on_success
2 changes: 2 additions & 0 deletions ocamltest/options.mli
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,8 @@ val files_to_test : string list

val promote : bool

val default_timeout : int

val usage : string

val find_test_dirs : string list
Expand Down

0 comments on commit 407132a

Please sign in to comment.