Skip to content

Commit e8451b2

Browse files
committed
unify sleep interface
1 parent cf35194 commit e8451b2

File tree

2 files changed

+25
-48
lines changed

2 files changed

+25
-48
lines changed

src/stdlib_system.F90

Lines changed: 10 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -96,49 +96,19 @@ module subroutine wait_for_completion(process, max_wait_time)
9696
end subroutine wait_for_completion
9797
end interface wait
9898

99-
interface
100-
#ifdef _WIN32
101-
subroutine winsleep(dwMilliseconds) bind (C, name='Sleep')
102-
!! version: experimental
103-
!!
104-
!! void Sleep(DWORD dwMilliseconds)
105-
!! https://docs.microsoft.com/en-us/windows/win32/api/synchapi/nf-synchapi-sleep
106-
import c_long
107-
integer(c_long), value, intent(in) :: dwMilliseconds
108-
end subroutine winsleep
109-
#else
110-
integer(c_int) function usleep(usec) bind (C)
111-
!! version: experimental
112-
!!
113-
!! int usleep(useconds_t usec);
114-
!! https://linux.die.net/man/3/usleep
115-
import c_int
116-
integer(c_int), value, intent(in) :: usec
117-
end function usleep
118-
#endif
99+
!> Query the system to update a process's state
100+
interface update
101+
module subroutine update_process_state(process)
102+
type(process_type), intent(inout) :: process
103+
end subroutine update_process_state
119104
end interface
120105

121-
122-
123-
124-
contains
125-
126-
subroutine sleep(millisec)
127106
!! version: experimental
128107
!!
129-
integer, intent(in) :: millisec
130-
integer(c_int) :: ierr
131-
132-
#ifdef _WIN32
133-
!! PGI Windows, Ifort Windows, ....
134-
call winsleep(int(millisec, c_long))
135-
#else
136-
!! Linux, Unix, MacOS, MSYS2, ...
137-
ierr = usleep(int(millisec * 1000, c_int))
138-
if (ierr/=0) error stop 'problem with usleep() system call'
139-
#endif
140-
141-
142-
end subroutine sleep
108+
interface sleep
109+
module subroutine sleep(millisec)
110+
integer, intent(in) :: millisec
111+
end subroutine sleep
112+
end interface sleep
143113

144114
end module stdlib_system

src/stdlib_system_subprocess.F90

Lines changed: 15 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -32,23 +32,25 @@ end subroutine process_query_status
3232

3333
subroutine process_create(cmd, stdin_stream, stdin_file, stdout_file, stderr_file, handle, pid) &
3434
bind(C, name='process_create')
35-
import c_char, c_ptr, process_ID
35+
import c_char, process_handle, process_ID
3636
implicit none
3737
character(c_char), intent(in) :: cmd(*)
3838
character(c_char), intent(in), optional :: stdin_stream(*)
3939
character(c_char), intent(in), optional :: stdin_file(*)
4040
character(c_char), intent(in), optional :: stdout_file(*)
4141
character(c_char), intent(in), optional :: stderr_file(*)
42-
type(c_ptr) , intent(out) :: handle
42+
type(process_handle), intent(out) :: handle
4343
integer(process_ID), intent(out) :: pid
4444
end subroutine process_create
4545

46+
! System implementation of a wait function
4647
subroutine process_wait(seconds) bind(C,name='process_wait')
4748
import c_float
4849
implicit none
4950
real(c_float), intent(in) :: seconds
5051
end subroutine process_wait
5152

53+
! Return path to the null device
5254
type(c_ptr) function process_null_device(len) bind(C,name='process_null_device')
5355
import c_ptr, c_int
5456
implicit none
@@ -57,11 +59,16 @@ end function process_null_device
5759

5860
end interface
5961

60-
61-
62-
6362
contains
6463

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+
6572
!> Open a new, asynchronous process
6673
module type(process_type) function process_open(args,wait,stdin,want_stdout,want_stderr) result(process)
6774
!> The command and arguments
@@ -243,7 +250,7 @@ module subroutine wait_for_completion(process, max_wait_time)
243250
wait_loop: do while (process_is_running(process) .and. elapsed <= wait_time)
244251

245252
! Small sleep to avoid CPU hogging (1 ms)
246-
call process_wait(0.001_c_float)
253+
call sleep(1)
247254

248255
call system_clock(current_time)
249256
elapsed = real(current_time - start_time, RTICKS) / count_rate
@@ -253,8 +260,8 @@ module subroutine wait_for_completion(process, max_wait_time)
253260
end subroutine wait_for_completion
254261

255262
!> 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
258265

259266
real(RTICKS) :: count_rate
260267
integer(TICKS) :: count_max,current_time

0 commit comments

Comments
 (0)