Skip to content

Commit 62e1efc

Browse files
committed
is_abs -> is_abs_path and small doc changes
1 parent 53a4368 commit 62e1efc

File tree

5 files changed

+41
-38
lines changed

5 files changed

+41
-38
lines changed

doc/specs/stdlib_system.md

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -981,7 +981,7 @@ A character string or `type(string_type)`.
981981

982982
---
983983

984-
## `is_abs` - Checks if the path is absolute
984+
## `is_abs_path` - Checks if the path is absolute
985985

986986
### Status
987987

@@ -996,7 +996,7 @@ a path starting with a drive letter (like `C:\Users\`)
996996

997997
### Syntax
998998

999-
`res = ` [[stdlib_system(module):is_abs(interface)]]`(p)`
999+
`res = ` [[stdlib_system(module):is_abs_path(interface)]]`(p)`
10001000

10011001
### Class
10021002

@@ -1009,7 +1009,10 @@ Function
10091009

10101010
### Return values
10111011

1012-
A `logical` indicating if the the path is absolute.
1012+
The function returns a `logical` value:
1013+
1014+
- `.true.` if the path is absolute.
1015+
- `.false.` otherwise.
10131016

10141017
### Example
10151018

@@ -1047,7 +1050,7 @@ Function
10471050

10481051
`res`: the absolutized version of the path, It is of type `character(:), allocatable`.
10491052

1050-
`err`: It is an optional state return flag. On error if not requested, an `FS_ERROR` will trigger an error stop.
1053+
`err`: it is an optional state return flag. On error if not requested, an `FS_ERROR` will trigger an error stop.
10511054

10521055
### Example
10531056

example/system/example_path_abs.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,14 @@
1-
! Illustrate the usage of `abs_path`, `is_abs`
1+
! Illustrate the usage of `abs_path`, `is_abs_path`
22
program example_path_abs
3-
use stdlib_system, only: abs_path, is_abs
3+
use stdlib_system, only: abs_path, is_abs_path
44
use stdlib_error, only: state_type
55
implicit none
66

77
character(*), parameter :: path = "path/to/check"
88
character(:), allocatable :: absolute_path
99
type(state_type) :: err
1010

11-
if (is_abs(path)) then
11+
if (is_abs_path(path)) then
1212
print *, "Path is absolute!"
1313
! terminate the program since path is already absolute
1414
stop

src/stdlib_system.F90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,7 @@ module stdlib_system
9393
public :: split_path
9494
public :: base_name
9595
public :: dir_name
96-
public :: is_abs
96+
public :: is_abs_path
9797
public :: abs_path
9898

9999
!! version: experimental
@@ -783,26 +783,26 @@ module function dir_name_string(p) result(dir)
783783
end function dir_name_string
784784
end interface dir_name
785785

786-
interface is_abs
786+
interface is_abs_path
787787
!! version: experimental
788788
!!
789789
!!### Summary
790790
!! This function checks if the path is absolute.
791-
!! ([Specification](../page/specs/stdlib_system.html#is_abs))
791+
!! ([Specification](../page/specs/stdlib_system.html#is_abs_path))
792792
!!
793793
!!### Description
794794
!! This function checks if the path is absolute (i.e not relative).
795795
!! - On POSIX systems this means the path starts with `/`.
796796
!! - On Windows systems this means the path is either an UNC path (like `\\host\path\share`) or
797797
!! a path starting with a drive letter (like `C:\Users\`)
798-
module logical function is_abs_char(p)
798+
module logical function is_abs_path_char(p)
799799
character(len=*), intent(in) :: p
800-
end function is_abs_char
800+
end function is_abs_path_char
801801

802-
module logical function is_abs_string(p)
802+
module logical function is_abs_path_string(p)
803803
type(string_type), intent(in) :: p
804-
end function is_abs_string
805-
end interface is_abs
804+
end function is_abs_path_string
805+
end interface is_abs_path
806806

807807
interface abs_path
808808
!! version: experimental

src/stdlib_system_path.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -168,27 +168,27 @@ module function dir_name_string(p) result(dir)
168168
call split_path(p, dir, temp)
169169
end function dir_name_string
170170

171-
module logical function is_abs_char(p)
171+
module logical function is_abs_path_char(p)
172172
character(len=*), intent(in) :: p
173173
character(len=1) :: sep
174174

175175
sep = path_sep()
176176

177177
if (sep == '/') then
178178
! should start with '/'
179-
is_abs_char = starts_with(p, sep)
179+
is_abs_path_char = starts_with(p, sep)
180180
else
181181
! should be either an UNC path like '\\server\host...'
182182
! or should be starting with a drive letter like 'C:\Users\...'
183-
is_abs_char = starts_with(p(2:), ':\') .or. starts_with(p, '\\')
183+
is_abs_path_char = starts_with(p(2:), ':\') .or. starts_with(p, '\\')
184184
end if
185-
end function is_abs_char
185+
end function is_abs_path_char
186186

187-
module logical function is_abs_string(p)
187+
module logical function is_abs_path_string(p)
188188
type(string_type), intent(in) :: p
189189

190-
is_abs_string = is_abs(char(p))
191-
end function is_abs_string
190+
is_abs_path_string = is_abs_path(char(p))
191+
end function is_abs_path_string
192192

193193
module function abs_path_char(p, err) result(abs_p)
194194
character(len=*), intent(in) :: p

test/system/test_path.f90

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module test_path
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
33
use stdlib_system, only: join_path, operator(/), split_path, OS_TYPE, OS_WINDOWS, &
4-
is_abs, abs_path, get_cwd
4+
is_abs_path, abs_path, get_cwd
55
use stdlib_error, only: state_type
66
implicit none
77
contains
@@ -14,7 +14,7 @@ subroutine collect_suite(testsuite)
1414
new_unittest('test_join_path', test_join_path), &
1515
new_unittest('test_join_path_operator', test_join_path_op), &
1616
new_unittest('test_split_path', test_split_path), &
17-
new_unittest('test_is_abs', test_is_abs), &
17+
new_unittest('test_is_abs_path', test_is_abs_path), &
1818
new_unittest('test_abs_path', test_abs_path) &
1919
]
2020
end subroutine collect_suite
@@ -122,68 +122,68 @@ subroutine test_split_path(error)
122122
end if
123123
end subroutine test_split_path
124124

125-
subroutine test_is_abs(error)
125+
subroutine test_is_abs_path(error)
126126
type(error_type), allocatable, intent(out) :: error
127127
character(:), allocatable :: p
128128
logical :: res
129129

130-
character(*), parameter :: msg = "is_abs: "
130+
character(*), parameter :: msg = "is_abs_path: "
131131

132132
if (OS_TYPE() == OS_WINDOWS) then
133133
p = '.'
134-
res = is_abs(p)
134+
res = is_abs_path(p)
135135
call check(error, .not. res, msg // p // " returns incorrect result")
136136
if (allocated(error)) return
137137

138138
p = '..'
139-
res = is_abs(p)
139+
res = is_abs_path(p)
140140
call check(error, .not. res, msg // p // " returns incorrect result")
141141
if (allocated(error)) return
142142

143143
p = 'C:\Windows'
144-
res = is_abs(p)
144+
res = is_abs_path(p)
145145
call check(error, res, msg // p // " returns incorrect result")
146146
if (allocated(error)) return
147147

148148
! a relative path pointing to the `Windows` folder
149149
! in the current working directory in the drive C
150150
p = 'C:Windows'
151-
res = is_abs(p)
151+
res = is_abs_path(p)
152152
call check(error, .not. res, msg // p // " returns incorrect result")
153153
if (allocated(error)) return
154154

155155
! UNC paths
156156
p = '\\server_name\share_name\path'
157-
res = is_abs(p)
157+
res = is_abs_path(p)
158158
call check(error, res, msg // p // " returns incorrect result")
159159
if (allocated(error)) return
160160
else
161161
p = '.'
162-
res = is_abs(p)
162+
res = is_abs_path(p)
163163
call check(error, .not. res, msg // p // " returns incorrect result")
164164
if (allocated(error)) return
165165

166166
p = '..'
167-
res = is_abs(p)
167+
res = is_abs_path(p)
168168
call check(error, .not. res, msg // p // " returns incorrect result")
169169
if (allocated(error)) return
170170

171171
p = '/'
172-
res = is_abs(p)
172+
res = is_abs_path(p)
173173
call check(error, res, msg // p // " returns incorrect result")
174174
if (allocated(error)) return
175175

176176
p = '/home/Alice'
177-
res = is_abs(p)
177+
res = is_abs_path(p)
178178
call check(error, res, msg // p // " returns incorrect result")
179179
if (allocated(error)) return
180180

181181
p = './home/Alice'
182-
res = is_abs(p)
182+
res = is_abs_path(p)
183183
call check(error, .not. res, msg // p // " returns incorrect result")
184184
if (allocated(error)) return
185185
end if
186-
end subroutine test_is_abs
186+
end subroutine test_is_abs_path
187187

188188
subroutine test_abs_path(error)
189189
type(error_type), allocatable, intent(out) :: error
@@ -201,7 +201,7 @@ subroutine test_abs_path(error)
201201
call check(error, err%ok(), "Could not get absolute path: " // err%print())
202202
if (allocated(error)) return
203203

204-
call check(error, is_abs(absolute_path), "absolute path created is not absolute")
204+
call check(error, is_abs_path(absolute_path), "absolute path created is not absolute")
205205
if (allocated(error)) return
206206

207207
call get_cwd(cwd, err)

0 commit comments

Comments
 (0)