Skip to content

Commit 2c47354

Browse files
committed
snake case names
1 parent 5197a0c commit 2c47354

File tree

2 files changed

+19
-14
lines changed

2 files changed

+19
-14
lines changed

src/stdlib_system.F90

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -137,9 +137,14 @@ module stdlib_system
137137
!! version: experimental
138138
!!
139139
!! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
140-
!! `FS_ERROR_CODE` also prefixes the `code` passed to it as the first argument
141140
!!
142-
public :: FS_ERROR, FS_ERROR_CODE
141+
public :: fs_error
142+
!! version: experimental
143+
!!
144+
!! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
145+
!! It also formats and prefixes the `code` passed to it as the first argument
146+
!!
147+
public :: fs_error_code
143148

144149
! CPU clock ticks storage
145150
integer, parameter, private :: TICKS = int64
@@ -777,7 +782,7 @@ subroutine delete_file(path, err)
777782
end if
778783
end subroutine delete_file
779784

780-
pure function FS_ERROR_CODE(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
785+
pure function fs_error_code(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
781786
a11,a12,a13,a14,a15,a16,a17,a18) result(state)
782787

783788
type(state_type) :: state
@@ -789,9 +794,9 @@ pure function FS_ERROR_CODE(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
789794

790795
state = state_type(STDLIB_FS_ERROR, "code -", to_string(code)//",",a1,a2,a3,a4,a5,a6,a7,a8, &
791796
a9,a10,a11,a12,a13,a14,a15,a16,a17,a18)
792-
end function FS_ERROR_CODE
797+
end function fs_error_code
793798

794-
pure function FS_ERROR(a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11, &
799+
pure function fs_error(a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11, &
795800
a12,a13,a14,a15,a16,a17,a18,a19,a20) result(state)
796801

797802
type(state_type) :: state
@@ -801,6 +806,6 @@ pure function FS_ERROR(a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11, &
801806

802807
state = state_type(STDLIB_FS_ERROR, a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12, &
803808
a13,a14,a15,a16,a17,a18,a19,a20)
804-
end function FS_ERROR
809+
end function fs_error
805810

806811
end module stdlib_system

test/system/test_filesystem.f90

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module test_filesystem
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3-
use stdlib_system, only: is_directory, delete_file, FS_ERROR, FS_ERROR_CODE
3+
use stdlib_system, only: is_directory, delete_file, fs_error, fs_error_code
44
use stdlib_error, only: state_type, STDLIB_FS_ERROR
55

66
implicit none
@@ -13,7 +13,7 @@ subroutine collect_suite(testsuite)
1313
type(unittest_type), allocatable, intent(out) :: testsuite(:)
1414

1515
testsuite = [ &
16-
new_unittest("FS_ERROR", test_FS_ERROR), &
16+
new_unittest("fs_error", test_FS_ERROR), &
1717
new_unittest("fs_is_directory_dir", test_is_directory_dir), &
1818
new_unittest("fs_is_directory_file", test_is_directory_file), &
1919
new_unittest("fs_delete_non_existent", test_delete_file_non_existent), &
@@ -22,25 +22,25 @@ subroutine collect_suite(testsuite)
2222
]
2323
end subroutine collect_suite
2424

25-
subroutine test_FS_ERROR(error)
25+
subroutine test_fs_error(error)
2626
type(error_type), allocatable, intent(out) :: error
2727
type(state_type) :: s1, s2
2828
character(:), allocatable :: msg
2929

3030
msg = "code - 10, Cannot create File temp.txt - File already exists"
31-
s1 = FS_ERROR_CODE(10, "Cannot create File temp.txt -", "File already exists")
31+
s1 = fs_error_code(10, "Cannot create File temp.txt -", "File already exists")
3232

3333
call check(error, s1%state == STDLIB_FS_ERROR .and. s1%message == msg, &
34-
"FS_ERROR: Could not construct the state with code correctly")
34+
"fs_error_code: Could not construct the state with code correctly")
3535
if (allocated(error)) return
3636

3737
msg = "Cannot create File temp.txt - File already exists"
38-
s2 = FS_ERROR("Cannot create File temp.txt -", "File already exists")
38+
s2 = fs_error("Cannot create File temp.txt -", "File already exists")
3939

4040
call check(error, s2%state == STDLIB_FS_ERROR .and. s2%message == msg, &
41-
"FS_ERROR: Could not construct state without code correctly")
41+
"fs_error: Could not construct state without code correctly")
4242
if (allocated(error)) return
43-
end subroutine test_FS_ERROR
43+
end subroutine test_fs_error
4444

4545
! Test `is_directory` for a directory
4646
subroutine test_is_directory_dir(error)

0 commit comments

Comments
 (0)