Skip to content

Commit 03c76c9

Browse files
committed
capitalize functions + some doc changes
1 parent 4d1e6d0 commit 03c76c9

File tree

4 files changed

+35
-33
lines changed

4 files changed

+35
-33
lines changed

doc/specs/stdlib_system.md

Lines changed: 10 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -418,7 +418,7 @@ Returns one of the `integer` `OS_*` parameters representing the OS type, from th
418418

419419
---
420420

421-
## `fs_error` - Helper function for error handling
421+
## `FS_ERROR` - Helper function for error handling
422422

423423
### Status
424424

@@ -430,15 +430,15 @@ A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_
430430

431431
### Syntax
432432

433-
`err = fs_error([a1,a2,a3,a4...... a20])`
433+
`err = FS_ERROR([a1,a2,a3,a4...... a20])`
434434

435435
### Class
436436
Pure Function
437437

438438
### Arguments
439439

440-
`a1,a2,a3.....a20`(optional) : They are of type `class(*), dimension(..), optional, intent(in)`.
441-
An arbitrary list of `integer`, `real`, `complex`, or `character` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
440+
`a1,a2,a3.....a20`(optional): They are of type `class(*), dimension(..), optional, intent(in)`.
441+
An arbitrary list of `integer`, `real`, `complex`, `character` or `string_type` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
442442

443443
### Behavior
444444

@@ -456,7 +456,7 @@ Formats all the arguments into a nice error message, utilizing the constructor o
456456

457457
---
458458

459-
## `fs_error_code` - Helper function for error handling (with error code)
459+
## `FS_ERROR_CODE` - Helper function for error handling (with error code)
460460

461461
### Status
462462

@@ -469,15 +469,17 @@ It also formats and prefixes the `code` passed to it as the first argument.
469469

470470
### Syntax
471471

472-
`err = fs_error(code [, a1,a2,a3,a4...... a19])`
472+
`err = FS_ERROR_CODE(code [, a1,a2,a3,a4...... a19])`
473473

474474
### Class
475475
Pure Function
476476

477477
### Arguments
478478

479-
`a1,a2,a3.....a19`: They are of type `class(*), dimension(..), optional, intent(in)`.
480-
An arbitrary list of `integer`, `real`, `complex`, or `character` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
479+
`code`: An `integer` code.
480+
481+
`a1,a2,a3.....a19`(optional): They are of type `class(*), dimension(..), optional, intent(in)`.
482+
An arbitrary list of `integer`, `real`, `complex`, `character` or `string_type` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
481483

482484
### Behavior
483485

example/system/example_fs_error.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,19 @@
1-
! Demonstrate usage of `fs_error`, `fs_error_code`
1+
! Demonstrate usage of `FS_ERROR`, `FS_ERROR_CODE`
22
program example_fs_error
3-
use stdlib_system, only: fs_error, fs_error_code
3+
use stdlib_system, only: FS_ERROR, FS_ERROR_CODE
44
use stdlib_error, only: state_type, STDLIB_FS_ERROR
55
implicit none
66

77
type(state_type) :: err0, err1
88

9-
err0 = fs_error("Could not create directory", "`temp.dir`", "- Already exists")
9+
err0 = FS_ERROR("Could not create directory", "`temp.dir`", "- Already exists")
1010

1111
if (err0%state == STDLIB_FS_ERROR) then
1212
! Error encountered: Filesystem Error: Could not create directory `temp.dir` - Already exists
1313
print *, err0%print()
1414
end if
1515

16-
err1 = fs_error_code(1, "Could not create directory", "`temp.dir`", "- Already exists")
16+
err1 = FS_ERROR_CODE(1, "Could not create directory", "`temp.dir`", "- Already exists")
1717

1818
if (err1%state == STDLIB_FS_ERROR) then
1919
! Error encountered: Filesystem Error: code - 1, Could not create directory `temp.dir` - Already exists

src/stdlib_system.F90

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -137,17 +137,17 @@ 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-
!! ([Specification](../page/specs/stdlib_system.html#fs_error))
140+
!! ([Specification](../page/specs/stdlib_system.html#FS_ERROR))
141141
!!
142-
public :: fs_error
142+
public :: FS_ERROR
143143

144144
!! version: experimental
145145
!!
146146
!! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
147147
!! It also formats and prefixes the `code` passed to it as the first argument
148-
!! ([Specification](../page/specs/stdlib_system.html#fs_error_code))
148+
!! ([Specification](../page/specs/stdlib_system.html#FS_ERROR_CODE))
149149
!!
150-
public :: fs_error_code
150+
public :: FS_ERROR_CODE
151151

152152
! CPU clock ticks storage
153153
integer, parameter, private :: TICKS = int64
@@ -785,34 +785,34 @@ subroutine delete_file(path, err)
785785
end if
786786
end subroutine delete_file
787787

788-
pure function fs_error_code(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
789-
a11,a12,a13,a14,a15,a16,a17,a18, a19) result(state)
788+
pure function FS_ERROR_CODE(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
789+
a11,a12,a13,a14,a15,a16,a17,a18,a19) result(state)
790790

791791
type(state_type) :: state
792792
!> Platform specific error code
793793
integer, intent(in) :: code
794794
!> Optional rank-agnostic arguments
795-
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
796-
a11,a12,a13,a14,a15,a16,a17,a18, a19
795+
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
796+
a11,a12,a13,a14,a15,a16,a17,a18,a19
797797

798798
character(32) :: code_msg
799799

800800
write(code_msg, "('code - ', i0, ',')") code
801801

802-
state = state_type(STDLIB_FS_ERROR, code_msg,a1,a2,a3,a4,a5,a6,a7,a8, &
803-
a9,a10,a11,a12,a13,a14,a15,a16,a17,a18, a19)
804-
end function fs_error_code
802+
state = state_type(STDLIB_FS_ERROR, code_msg,a1,a2,a3,a4,a5,a6,a7,a8,&
803+
a9,a10,a11,a12,a13,a14,a15,a16,a17,a18,a19)
804+
end function FS_ERROR_CODE
805805

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

809809
type(state_type) :: state
810810
!> Optional rank-agnostic arguments
811-
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
811+
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
812812
a11,a12,a13,a14,a15,a16,a17,a18,a19,a20
813813

814-
state = state_type(STDLIB_FS_ERROR, a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12, &
814+
state = state_type(STDLIB_FS_ERROR, a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12,&
815815
a13,a14,a15,a16,a17,a18,a19,a20)
816-
end function fs_error
816+
end function FS_ERROR
817817

818818
end module stdlib_system

test/system/test_filesystem.f90

Lines changed: 6 additions & 6 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), &
@@ -28,17 +28,17 @@ subroutine test_fs_error(error)
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_code: 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
4343
end subroutine test_fs_error
4444

0 commit comments

Comments
 (0)