Skip to content

Commit 8a10f26

Browse files
committed
tests added
1 parent 572ad46 commit 8a10f26

File tree

2 files changed

+146
-0
lines changed

2 files changed

+146
-0
lines changed

test/system/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,3 +2,4 @@ ADDTEST(filesystem)
22
ADDTEST(os)
33
ADDTEST(sleep)
44
ADDTEST(subprocess)
5+
ADDTEST(path)

test/system/test_path.f90

Lines changed: 145 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,145 @@
1+
module test_path
2+
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3+
use stdlib_system, only: joinpath, operator(/), splitpath, ISWIN
4+
implicit none
5+
contains
6+
!> Collect all exported unit tests
7+
subroutine collect_suite(testsuite)
8+
!> Collection of tests
9+
type(unittest_type), allocatable, intent(out) :: testsuite(:)
10+
11+
testsuite = [ &
12+
new_unittest('test_joinpath', test_joinpath), &
13+
new_unittest('test_joinpath_operator', test_joinpath_op), &
14+
new_unittest('test_splitpath', test_splitpath) &
15+
]
16+
end subroutine collect_suite
17+
18+
subroutine checkpath(error, funcname, expected, got)
19+
type(error_type), allocatable, intent(out) :: error
20+
character(len=*), intent(in) :: funcname
21+
character(len=*), intent(in) :: expected
22+
character(len=:), allocatable :: got
23+
character(len=:), allocatable :: message
24+
25+
message = "'"//funcname//"'"//" error: Expected '"// expected // "' but got '" // got // "'"
26+
call check(error, expected == got, message)
27+
28+
end subroutine checkpath
29+
30+
subroutine test_joinpath(error)
31+
type(error_type), allocatable, intent(out) :: error
32+
character(len=:), allocatable :: path
33+
character(len=20) :: paths(5)
34+
35+
if (ISWIN) then
36+
path = joinpath('C:\Users', 'Alice')
37+
call checkpath(error, 'joinpath', 'C:\Users\Alice', path)
38+
if (allocated(error)) return
39+
40+
paths = [character(20) :: 'C:','Users','Bob','Pictures','2025']
41+
path = joinpath(paths)
42+
43+
call checkpath(error, 'joinpath', 'C:\Users\Bob\Pictures\2025', path)
44+
if (allocated(error)) return
45+
else
46+
path = joinpath('/home', 'Alice')
47+
call checkpath(error, 'joinpath', '/home/Alice', path)
48+
if (allocated(error)) return
49+
50+
paths = [character(20) :: '','home','Bob','Pictures','2025']
51+
path = joinpath(paths)
52+
53+
call checkpath(error, 'joinpath', '/home/Bob/Pictures/2025', path)
54+
if (allocated(error)) return
55+
end if
56+
end subroutine test_joinpath
57+
58+
!> Test the operator
59+
subroutine test_joinpath_op(error)
60+
type(error_type), allocatable, intent(out) :: error
61+
character(len=:), allocatable :: path
62+
63+
if (ISWIN) then
64+
path = 'C:'/'Users'/'Alice'/'Desktop'
65+
call checkpath(error, 'joinpath operator', 'C:\Users\Alice\Desktop', path)
66+
if (allocated(error)) return
67+
else
68+
path = ''/'home'/'Alice'/'.config'
69+
call checkpath(error, 'joinpath operator', '/home/Alice/.config', path)
70+
if (allocated(error)) return
71+
end if
72+
end subroutine test_joinpath_op
73+
74+
subroutine test_splitpath(error)
75+
type(error_type), allocatable, intent(out) :: error
76+
character(len=:), allocatable :: head, tail
77+
78+
call splitpath('', head, tail)
79+
call checkpath(error, 'splitpath-head', '.', head)
80+
if (allocated(error)) return
81+
call checkpath(error, 'splitpath-tail', '', tail)
82+
if (allocated(error)) return
83+
84+
if (ISWIN) then
85+
call splitpath('\\\\', head, tail)
86+
call checkpath(error, 'splitpath-head', '\', head)
87+
if (allocated(error)) return
88+
call checkpath(error, 'splitpath-tail', '', tail)
89+
if (allocated(error)) return
90+
91+
call splitpath('C:\', head, tail)
92+
call checkpath(error, 'splitpath-head', 'C:\', head)
93+
if (allocated(error)) return
94+
call checkpath(error, 'splitpath-tail', '', tail)
95+
if (allocated(error)) return
96+
97+
call splitpath('C:\Users\Alice\\\\\', head, tail)
98+
call checkpath(error, 'splitpath-head', 'C:\Users', head)
99+
if (allocated(error)) return
100+
call checkpath(error, 'splitpath-tail', 'Alice', tail)
101+
if (allocated(error)) return
102+
else
103+
call splitpath('/////', head, tail)
104+
call checkpath(error, 'splitpath-head', '/', head)
105+
if (allocated(error)) return
106+
call checkpath(error, 'splitpath-tail', '', tail)
107+
if (allocated(error)) return
108+
109+
call splitpath('/home/Alice/foo/bar.f90///', head, tail)
110+
call checkpath(error, 'splitpath-head', '/home/Alice/foo', head)
111+
if (allocated(error)) return
112+
call checkpath(error, 'splitpath-tail', 'bar.f90', tail)
113+
if (allocated(error)) return
114+
end if
115+
end subroutine test_splitpath
116+
117+
end module test_path
118+
119+
program tester
120+
use, intrinsic :: iso_fortran_env, only : error_unit
121+
use testdrive, only : run_testsuite, new_testsuite, testsuite_type
122+
use test_path, only : collect_suite
123+
124+
implicit none
125+
126+
integer :: stat, is
127+
type(testsuite_type), allocatable :: testsuites(:)
128+
character(len=*), parameter :: fmt = '("#", *(1x, a))'
129+
130+
stat = 0
131+
132+
testsuites = [ &
133+
new_testsuite("path", collect_suite) &
134+
]
135+
136+
do is = 1, size(testsuites)
137+
write(error_unit, fmt) "Testing:", testsuites(is)%name
138+
call run_testsuite(testsuites(is)%collect, error_unit, stat)
139+
end do
140+
141+
if (stat > 0) then
142+
write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
143+
error stop
144+
end if
145+
end program tester

0 commit comments

Comments
 (0)