@@ -49,7 +49,7 @@ end function process_system_kill
49
49
subroutine process_wait (seconds ) bind(C,name= ' process_wait' )
50
50
import c_float
51
51
implicit none
52
- real (c_float), intent (in ) :: seconds
52
+ real (c_float), intent (in ), value :: seconds
53
53
end subroutine process_wait
54
54
55
55
! Return path to the null device
@@ -76,8 +76,12 @@ end function process_has_win32
76
76
! Call system-dependent wait implementation
77
77
module subroutine sleep (millisec )
78
78
integer , intent (in ) :: millisec
79
+
80
+ real (c_float) :: seconds
81
+
82
+ seconds = 0.001_c_float * max (0 ,millisec)
79
83
80
- call process_wait(real ( 0.001 * real ( max ( 0 ,millisec),c_float),c_float) )
84
+ call process_wait(seconds )
81
85
82
86
end subroutine sleep
83
87
@@ -262,8 +266,16 @@ module subroutine wait_for_completion(process, max_wait_time)
262
266
! Optional max wait time in seconds
263
267
real , optional , intent (in ) :: max_wait_time
264
268
269
+ integer :: sleep_interval
265
270
real (RTICKS) :: wait_time, elapsed
266
271
integer (TICKS) :: start_time, current_time, count_rate
272
+
273
+ ! Sleep interval ms
274
+ integer , parameter :: MIN_WAIT_MS = 1
275
+ integer , parameter :: MAX_WAIT_MS = 100
276
+
277
+ ! Starting sleep interval: 1ms
278
+ sleep_interval = MIN_WAIT_MS
267
279
268
280
! Determine the wait time
269
281
if (present (max_wait_time)) then
@@ -279,9 +291,11 @@ module subroutine wait_for_completion(process, max_wait_time)
279
291
280
292
! Wait loop
281
293
wait_loop: do while (process_is_running(process) .and. elapsed <= wait_time)
282
-
283
- ! Small sleep to avoid CPU hogging (1 ms)
284
- call sleep(1 )
294
+
295
+ ! Small sleep to avoid CPU hogging, with exponential backoff (1 ms)
296
+ ! from 1ms up to 100ms
297
+ call sleep(millisec= sleep_interval)
298
+ sleep_interval = min (sleep_interval* 2 , MAX_WAIT_MS)
285
299
286
300
call system_clock (current_time)
287
301
elapsed = real (current_time - start_time, RTICKS) / count_rate
0 commit comments