1
1
module test_path
2
2
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3
- use stdlib_system, only: join_path, operator (/ ), split_path, OS_TYPE, OS_WINDOWS
3
+ use stdlib_system, only: join_path, operator (/ ), split_path, OS_TYPE, OS_WINDOWS, &
4
+ is_abs, abs_path, get_cwd
5
+ use stdlib_error, only: state_type
4
6
implicit none
5
7
contains
6
8
! > Collect all exported unit tests
@@ -11,7 +13,9 @@ subroutine collect_suite(testsuite)
11
13
testsuite = [ &
12
14
new_unittest(' test_join_path' , test_join_path), &
13
15
new_unittest(' test_join_path_operator' , test_join_path_op), &
14
- new_unittest(' test_split_path' , test_split_path) &
16
+ new_unittest(' test_split_path' , test_split_path), &
17
+ new_unittest(' test_is_abs' , test_is_abs), &
18
+ new_unittest(' test_abs_path' , test_abs_path) &
15
19
]
16
20
end subroutine collect_suite
17
21
@@ -118,6 +122,101 @@ subroutine test_split_path(error)
118
122
end if
119
123
end subroutine test_split_path
120
124
125
+ subroutine test_is_abs (error )
126
+ type (error_type), allocatable , intent (out ) :: error
127
+ character (:), allocatable :: p
128
+ logical :: res
129
+
130
+ character (* ), parameter :: msg = " is_abs: "
131
+
132
+ if (OS_TYPE() == OS_WINDOWS) then
133
+ p = ' .'
134
+ res = is_abs(p)
135
+ call check(error, .not. res, msg // p // " returns incorrect result" )
136
+ if (allocated (error)) return
137
+
138
+ p = ' ..'
139
+ res = is_abs(p)
140
+ call check(error, .not. res, msg // p // " returns incorrect result" )
141
+ if (allocated (error)) return
142
+
143
+ p = ' C:\Windows'
144
+ res = is_abs(p)
145
+ call check(error, res, msg // p // " returns incorrect result" )
146
+ if (allocated (error)) return
147
+
148
+ ! a relative path pointing to the `Windows` folder
149
+ ! in the current working directory in the drive C
150
+ p = ' C:Windows'
151
+ res = is_abs(p)
152
+ call check(error, .not. res, msg // p // " returns incorrect result" )
153
+ if (allocated (error)) return
154
+
155
+ ! UNC paths
156
+ p = ' \\server_name\share_name\path'
157
+ res = is_abs(p)
158
+ call check(error, res, msg // p // " returns incorrect result" )
159
+ if (allocated (error)) return
160
+ else
161
+ p = ' .'
162
+ res = is_abs(p)
163
+ call check(error, .not. res, msg // p // " returns incorrect result" )
164
+ if (allocated (error)) return
165
+
166
+ p = ' ..'
167
+ res = is_abs(p)
168
+ call check(error, .not. res, msg // p // " returns incorrect result" )
169
+ if (allocated (error)) return
170
+
171
+ p = ' /'
172
+ res = is_abs(p)
173
+ call check(error, res, msg // p // " returns incorrect result" )
174
+ if (allocated (error)) return
175
+
176
+ p = ' /home/Alice'
177
+ res = is_abs(p)
178
+ call check(error, res, msg // p // " returns incorrect result" )
179
+ if (allocated (error)) return
180
+
181
+ p = ' ./home/Alice'
182
+ res = is_abs(p)
183
+ call check(error, .not. res, msg // p // " returns incorrect result" )
184
+ if (allocated (error)) return
185
+ end if
186
+ end subroutine test_is_abs
187
+
188
+ subroutine test_abs_path (error )
189
+ type (error_type), allocatable , intent (out ) :: error
190
+ character (:), allocatable :: rel_path, absolute_path, cwd, absolute_path0
191
+ type (state_type) :: err
192
+
193
+ if (OS_TYPE() == OS_WINDOWS) then
194
+ rel_path = " .\Folder\File"
195
+ else
196
+ rel_path = " ./Folder/File"
197
+ end if
198
+
199
+ absolute_path = abs_path(rel_path, err)
200
+
201
+ call check(error, err% ok(), " Could not get absolute path: " // err% print ())
202
+ if (allocated (error)) return
203
+
204
+ call check(error, is_abs(absolute_path), " absolute path created is not absolute" )
205
+ if (allocated (error)) return
206
+
207
+ call get_cwd(cwd, err)
208
+
209
+ ! ideally shouldn't error out but just in case it does
210
+ call check(error, err% ok(), " Could not get CWD: " // err% print ())
211
+ if (allocated (error)) return
212
+
213
+ absolute_path0 = cwd / rel_path
214
+
215
+ call check(error, absolute_path == absolute_path0, " absolute path != (CWD / relative path)" &
216
+ // " absolute_path: " // absolute_path // " and (CWD / relative path): " // absolute_path0)
217
+ if (allocated (error)) return
218
+ end subroutine test_abs_path
219
+
121
220
end module test_path
122
221
123
222
program tester
0 commit comments