Skip to content

Commit dbfa4d5

Browse files
committed
feat(cram): timeout for cram tests
We add a (timeout) field for cram stanzas allowing users to set up a time budget for cram tests to run in. If the budget is exceeded then the cram test will be cancelled. Signed-off-by: Ali Caglayan <alizter@gmail.com>
1 parent 6059d7c commit dbfa4d5

File tree

11 files changed

+325
-84
lines changed

11 files changed

+325
-84
lines changed

src/dune_engine/process.ml

Lines changed: 38 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -13,22 +13,44 @@ module Failure_mode = struct
1313
| Strict : ('a, 'a) t
1414
| Accept : int Predicate.t -> ('a, ('a, int) result) t
1515
| Return : ('a, 'a * int) t
16+
| Timeout :
17+
{ timeout_seconds : float option
18+
; failure_mode : ('a, 'b) t
19+
}
20+
-> ('a, ('b, [ `Timed_out ]) result) t
1621

17-
let accepted_codes : type a b. (a, b) t -> int -> bool = function
22+
let rec accepted_codes : type a b. (a, b) t -> int -> bool = function
1823
| Strict -> Int.equal 0
1924
| Accept exit_codes -> fun i -> Predicate.test exit_codes i
2025
| Return -> fun _ -> true
26+
| Timeout { failure_mode; _ } -> accepted_codes failure_mode
27+
;;
28+
29+
let exit_code_of_result = function
30+
| `Finished n -> n
31+
| `Timeout -> Code_error.raise "should not return `Timeout" []
32+
;;
33+
34+
let timeout_seconds : type a b. (a, b) t -> float option = function
35+
| Timeout { timeout_seconds; _ } -> timeout_seconds
36+
| Strict | Accept _ | Return -> None
2137
;;
2238

23-
let map_result : type a b. (a, b) t -> int -> f:(unit -> a) -> b =
24-
fun mode t ~f ->
39+
let rec map_result
40+
: type a b. (a, b) t -> [ `Timeout | `Finished of int ] -> f:(unit -> a) -> b
41+
=
42+
fun mode result ~f ->
2543
match mode with
2644
| Strict -> f ()
2745
| Accept _ ->
28-
(match t with
46+
(match exit_code_of_result result with
2947
| 0 -> Ok (f ())
3048
| n -> Error n)
31-
| Return -> f (), t
49+
| Return -> f (), exit_code_of_result result
50+
| Timeout { failure_mode; _ } ->
51+
(match result with
52+
| `Timeout -> Error `Timed_out
53+
| `Finished _ -> Ok (map_result failure_mode result ~f))
3254
;;
3355
end
3456

@@ -857,9 +879,9 @@ let report_process_finished
857879

858880
let set_temp_dir_when_running_actions = ref true
859881

860-
let await { response_file; pid; _ } =
882+
let await ~timeout_seconds { response_file; pid; _ } =
861883
let+ process_info, termination_reason =
862-
Scheduler.wait_for_build_process pid ~is_process_group_leader:true
884+
Scheduler.wait_for_build_process ?timeout_seconds pid ~is_process_group_leader:true
863885
in
864886
Option.iter response_file ~f:Path.unlink_exn;
865887
process_info, termination_reason
@@ -1019,7 +1041,7 @@ let run_internal
10191041
cmdline
10201042
| _ -> Pp.nop
10211043
in
1022-
let t =
1044+
let (t : t) =
10231045
spawn
10241046
?dir
10251047
?env
@@ -1045,7 +1067,9 @@ let run_internal
10451067
in
10461068
Running_jobs.start id t.pid ~description ~started_at:t.started_at
10471069
in
1048-
let* process_info, termination_reason = await t in
1070+
let* process_info, termination_reason =
1071+
await ~timeout_seconds:(Failure_mode.timeout_seconds fail_mode) t
1072+
in
10491073
let+ () = Running_jobs.stop id in
10501074
let result = Result.make t process_info fail_mode in
10511075
let times =
@@ -1076,6 +1100,7 @@ let run_internal
10761100
we're about to return. *)
10771101
Result.close result;
10781102
raise (Memo.Non_reproducible Scheduler.Run.Build_cancelled)
1103+
| Timeout -> `Timeout, times
10791104
| Normal ->
10801105
let output = Result.Out.get result.stdout ^ Result.Out.get result.stderr in
10811106
Log.command ~command_line ~output ~exit_status:process_info.status;
@@ -1103,12 +1128,12 @@ let run_internal
11031128
~has_unexpected_stderr:result.stderr.unexpected_output
11041129
in
11051130
Result.close result;
1106-
res, times)
1131+
`Finished res, times)
11071132
;;
11081133

11091134
let run ?dir ~display ?stdout_to ?stderr_to ?stdin_from ?env ?metadata fail_mode prog args
11101135
=
1111-
let+ run =
1136+
let+ run, _ =
11121137
run_internal
11131138
?dir
11141139
~display
@@ -1120,7 +1145,6 @@ let run ?dir ~display ?stdout_to ?stderr_to ?stdin_from ?env ?metadata fail_mode
11201145
fail_mode
11211146
prog
11221147
args
1123-
>>| fst
11241148
in
11251149
Failure_mode.map_result fail_mode run ~f:ignore
11261150
;;
@@ -1166,7 +1190,7 @@ let run_capture_gen
11661190
~f
11671191
=
11681192
let fn = Temp.create File ~prefix:"dune" ~suffix:"output" in
1169-
let+ run =
1193+
let+ run, _ =
11701194
run_internal
11711195
?dir
11721196
~display
@@ -1178,7 +1202,6 @@ let run_capture_gen
11781202
fail_mode
11791203
prog
11801204
args
1181-
>>| fst
11821205
in
11831206
Failure_mode.map_result fail_mode run ~f:(fun () ->
11841207
let x = f fn in
@@ -1258,4 +1281,5 @@ let run_inherit_std_in_out =
12581281
prog
12591282
args
12601283
>>| fst
1284+
>>| Failure_mode.exit_code_of_result
12611285
;;

src/dune_engine/process.mli

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,13 +5,19 @@ module Action_output_on_success := Execution_parameters.Action_output_on_success
55
module Action_output_limit := Execution_parameters.Action_output_limit
66

77
module Failure_mode : sig
8-
(** How to handle sub-process failures *)
8+
(** How to handle sub-process failures. This type controls the way in which the process we are running can fail. *)
99
type ('a, 'b) t =
1010
| Strict : ('a, 'a) t (** Fail if the process exits with anything else than [0] *)
1111
| Accept : int Predicate.t -> ('a, ('a, int) result) t
1212
(** Accept the following non-zero exit codes, and return [Error code] if
1313
the process exits with one of these codes. *)
1414
| Return : ('a, 'a * int) t (** Accept any error code and return it. *)
15+
| Timeout :
16+
{ timeout_seconds : float option
17+
; failure_mode : ('a, 'b) t
18+
}
19+
-> ('a, ('b, [ `Timed_out ]) result) t
20+
(** In addition to the [failure_mode], finish early if [timeout_seconds] was reached. *)
1521
end
1622

1723
module Io : sig

src/dune_engine/scheduler.ml

Lines changed: 20 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -877,6 +877,7 @@ let wait_for_process t pid =
877877
type termination_reason =
878878
| Normal
879879
| Cancel
880+
| Timeout
880881

881882
(* We use this version privately in this module whenever we can pass the
882883
scheduler explicitly *)
@@ -1325,18 +1326,24 @@ let inject_memo_invalidation invalidation =
13251326
let wait_for_process_with_timeout t pid waiter ~timeout_seconds ~is_process_group_leader =
13261327
Fiber.of_thunk (fun () ->
13271328
let sleep = Alarm_clock.sleep (Lazy.force t.alarm_clock) ~seconds:timeout_seconds in
1328-
Fiber.fork_and_join_unit
1329-
(fun () ->
1330-
let+ res = Alarm_clock.await sleep in
1331-
if res = `Finished && Process_watcher.is_running t.process_watcher pid
1332-
then
1333-
if is_process_group_leader
1334-
then kill_process_group pid Sys.sigkill
1335-
else Unix.kill (Pid.to_int pid) Sys.sigkill)
1336-
(fun () ->
1337-
let+ res = waiter t pid in
1338-
Alarm_clock.cancel (Lazy.force t.alarm_clock) sleep;
1339-
res))
1329+
let+ clock_result =
1330+
Alarm_clock.await sleep
1331+
>>| function
1332+
| `Finished when Process_watcher.is_running t.process_watcher pid ->
1333+
if is_process_group_leader
1334+
then kill_process_group pid Sys.sigkill
1335+
else Unix.kill (Pid.to_int pid) Sys.sigkill;
1336+
`Timed_out
1337+
| _ -> `Finished
1338+
and+ res, termination_reason =
1339+
let+ res = waiter t pid in
1340+
Alarm_clock.cancel (Lazy.force t.alarm_clock) sleep;
1341+
res
1342+
in
1343+
( res
1344+
, match clock_result with
1345+
| `Timed_out -> Timeout
1346+
| `Finished -> termination_reason ))
13401347
;;
13411348

13421349
let wait_for_build_process ?timeout_seconds ?(is_process_group_leader = false) pid =
@@ -1353,16 +1360,7 @@ let wait_for_build_process ?timeout_seconds ?(is_process_group_leader = false) p
13531360
;;
13541361

13551362
let wait_for_process ?timeout_seconds ?(is_process_group_leader = false) pid =
1356-
let* t = t () in
1357-
match timeout_seconds with
1358-
| None -> wait_for_process t pid
1359-
| Some timeout_seconds ->
1360-
wait_for_process_with_timeout
1361-
t
1362-
pid
1363-
wait_for_process
1364-
~timeout_seconds
1365-
~is_process_group_leader
1363+
wait_for_build_process ?timeout_seconds ~is_process_group_leader pid >>| fst
13661364
;;
13671365

13681366
let sleep ~seconds =

src/dune_engine/scheduler.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,7 @@ val wait_for_process
104104
type termination_reason =
105105
| Normal
106106
| Cancel
107+
| Timeout
107108

108109
val wait_for_build_process
109110
: ?timeout_seconds:float

0 commit comments

Comments
 (0)