@@ -32,23 +32,25 @@ end subroutine process_query_status
32
32
33
33
subroutine process_create (cmd , stdin_stream , stdin_file , stdout_file , stderr_file , handle , pid ) &
34
34
bind(C, name= ' process_create' )
35
- import c_char, c_ptr , process_ID
35
+ import c_char, process_handle , process_ID
36
36
implicit none
37
37
character (c_char), intent (in ) :: cmd(* )
38
38
character (c_char), intent (in ), optional :: stdin_stream(* )
39
39
character (c_char), intent (in ), optional :: stdin_file(* )
40
40
character (c_char), intent (in ), optional :: stdout_file(* )
41
41
character (c_char), intent (in ), optional :: stderr_file(* )
42
- type (c_ptr) , intent (out ) :: handle
42
+ type (process_handle) , intent (out ) :: handle
43
43
integer (process_ID), intent (out ) :: pid
44
44
end subroutine process_create
45
45
46
+ ! System implementation of a wait function
46
47
subroutine process_wait (seconds ) bind(C,name= ' process_wait' )
47
48
import c_float
48
49
implicit none
49
50
real (c_float), intent (in ) :: seconds
50
51
end subroutine process_wait
51
52
53
+ ! Return path to the null device
52
54
type (c_ptr) function process_null_device(len) bind(C,name= ' process_null_device' )
53
55
import c_ptr, c_int
54
56
implicit none
@@ -57,11 +59,16 @@ end function process_null_device
57
59
58
60
end interface
59
61
60
-
61
-
62
-
63
62
contains
64
63
64
+ ! Call system-dependent wait implementation
65
+ module subroutine sleep (millisec )
66
+ integer , intent (in ) :: millisec
67
+
68
+ call process_wait(real (0.001 * millisec,c_float))
69
+
70
+ end subroutine sleep
71
+
65
72
! > Open a new, asynchronous process
66
73
module type (process_type) function process_open(args,wait,stdin,want_stdout,want_stderr) result(process)
67
74
! > The command and arguments
@@ -243,7 +250,7 @@ module subroutine wait_for_completion(process, max_wait_time)
243
250
wait_loop: do while (process_is_running(process) .and. elapsed <= wait_time)
244
251
245
252
! Small sleep to avoid CPU hogging (1 ms)
246
- call process_wait( 0.001_c_float )
253
+ call sleep( 1 )
247
254
248
255
call system_clock (current_time)
249
256
elapsed = real (current_time - start_time, RTICKS) / count_rate
@@ -253,8 +260,8 @@ module subroutine wait_for_completion(process, max_wait_time)
253
260
end subroutine wait_for_completion
254
261
255
262
! > Update a process's state, and
256
- subroutine update_process_state (process )
257
- class (process_type), intent (inout ) :: process
263
+ module subroutine update_process_state (process )
264
+ type (process_type), intent (inout ) :: process
258
265
259
266
real (RTICKS) :: count_rate
260
267
integer (TICKS) :: count_max,current_time
0 commit comments