Skip to content

Commit 1f4de32

Browse files
committed
add tests
1 parent 48da380 commit 1f4de32

File tree

2 files changed

+101
-0
lines changed

2 files changed

+101
-0
lines changed

test/system/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1 +1,2 @@
11
ADDTEST(sleep)
2+
ADDTEST(subprocess)

test/system/test_subprocess.f90

Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
module test_subprocess
2+
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3+
use stdlib_system, only: process_type, run, is_running, wait, update
4+
5+
implicit none
6+
7+
contains
8+
9+
!> Collect all exported unit tests
10+
subroutine collect_suite(testsuite)
11+
!> Collection of tests
12+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
13+
14+
testsuite = [ &
15+
new_unittest('test_run_synchronous', test_run_synchronous), &
16+
new_unittest('test_run_asynchronous', test_run_asynchronous), &
17+
new_unittest('test_process_state', test_process_state) &
18+
]
19+
end subroutine collect_suite
20+
21+
!> Test running a synchronous process
22+
subroutine test_run_synchronous(error)
23+
type(error_type), allocatable, intent(out) :: error
24+
type(process_type) :: process
25+
character(len=*), parameter :: command = "echo Hello"
26+
27+
process = run(command, wait=.true., want_stdout=.true.)
28+
call check(error, process%completed)
29+
if (allocated(error)) return
30+
31+
call check(error, trim(process%stdout) == "Hello")
32+
end subroutine test_run_synchronous
33+
34+
!> Test running an asynchronous process
35+
subroutine test_run_asynchronous(error)
36+
type(error_type), allocatable, intent(out) :: error
37+
type(process_type) :: process
38+
logical :: running
39+
character(len=*), parameter :: command = "sleep 1"
40+
41+
process = run(command, wait=.false.)
42+
call check(error, .not. process%completed)
43+
if (allocated(error)) return
44+
45+
running = is_running(process)
46+
call check(error, running)
47+
if (allocated(error)) return
48+
49+
call wait(process)
50+
call check(error, process%completed)
51+
end subroutine test_run_asynchronous
52+
53+
!> Test updating and checking process state
54+
subroutine test_process_state(error)
55+
type(error_type), allocatable, intent(out) :: error
56+
type(process_type) :: process
57+
character(len=*), parameter :: command = "echo Testing"
58+
59+
process = run(command, wait=.true., want_stdout=.true., want_stderr=.true.)
60+
61+
call update(process)
62+
call check(error, process%completed)
63+
if (allocated(error)) return
64+
65+
call check(error, process%exit_code == 0)
66+
if (allocated(error)) return
67+
68+
call check(error, trim(process%stdout) == "Testing")
69+
if (allocated(error)) return
70+
end subroutine test_process_state
71+
72+
end module test_subprocess
73+
74+
program tester
75+
use, intrinsic :: iso_fortran_env, only : error_unit
76+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
77+
use test_subprocess, only : collect_suite
78+
79+
implicit none
80+
81+
integer :: stat, is
82+
type(testsuite_type), allocatable :: testsuites(:)
83+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
84+
85+
stat = 0
86+
87+
testsuites = [ &
88+
new_testsuite("subprocess", collect_suite) &
89+
]
90+
91+
do is = 1, size(testsuites)
92+
write(error_unit, fmt) "Testing:", testsuites(is)%name
93+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
94+
end do
95+
96+
if (stat > 0) then
97+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
98+
error stop
99+
end if
100+
end program

0 commit comments

Comments
 (0)