Skip to content

Commit 1ed053f

Browse files
authored
Merge pull request #53 from scivision/returncode
error_stop to stderr and optional returncode
2 parents 924ee54 + 0364305 commit 1ed053f

9 files changed

+115
-21
lines changed

Diff for: CMakeLists.txt

+4
Original file line numberDiff line numberDiff line change
@@ -5,4 +5,8 @@ enable_testing()
55
# this avoids stdlib and projects using stdlib from having to introspect stdlib's directory structure
66
set(CMAKE_Fortran_MODULE_DIRECTORY ${CMAKE_BINARY_DIR})
77

8+
# compiler feature checks
9+
include(CheckFortranSourceCompiles)
10+
check_fortran_source_compiles("error stop i; end" f18errorstop SRC_EXT f90)
11+
812
add_subdirectory(src)

Diff for: src/CMakeLists.txt

+6
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,12 @@ set(SRC
66

77
add_library(fortran_stdlib ${SRC})
88

9+
if(f18errorstop)
10+
target_sources(fortran_stdlib PRIVATE f18estop.f90)
11+
else()
12+
target_sources(fortran_stdlib PRIVATE f08estop.f90)
13+
endif()
14+
915
add_subdirectory(tests)
1016

1117
install(TARGETS fortran_stdlib

Diff for: src/f08estop.f90

+39
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
submodule (stdlib_experimental_error) estop
2+
3+
contains
4+
5+
module procedure error_stop
6+
! Aborts the program with nonzero exit code
7+
! this is a fallback for Fortran 2008 error stop (e.g. Intel 19.1/2020 compiler)
8+
!
9+
! The "stop <character>" statement generally has return code 0.
10+
! To allow non-zero return code termination with character message,
11+
! error_stop() uses the statement "error stop", which by default
12+
! has exit code 1 and prints the message to stderr.
13+
! An optional integer return code "code" may be specified.
14+
!
15+
! Example
16+
! -------
17+
!
18+
! call error_stop("Invalid argument")
19+
20+
write(stderr,*) msg
21+
22+
if(present(code)) then
23+
select case (code)
24+
case (1)
25+
error stop 1
26+
case (2)
27+
error stop 2
28+
case (77)
29+
error stop 77
30+
case default
31+
write(stderr,*) 'ERROR: code ',code,' was specified.'
32+
error stop
33+
end select
34+
else
35+
error stop
36+
endif
37+
end procedure
38+
39+
end submodule

Diff for: src/f18estop.f90

+27
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,27 @@
1+
submodule (stdlib_experimental_error) estop
2+
3+
contains
4+
5+
module procedure error_stop
6+
! Aborts the program with nonzero exit code
7+
!
8+
! The "stop <character>" statement generally has return code 0.
9+
! To allow non-zero return code termination with character message,
10+
! error_stop() uses the statement "error stop", which by default
11+
! has exit code 1 and prints the message to stderr.
12+
! An optional integer return code "code" may be specified.
13+
!
14+
! Example
15+
! -------
16+
!
17+
! call error_stop("Invalid argument")
18+
19+
if(present(code)) then
20+
write(stderr,*) msg
21+
error stop code
22+
else
23+
error stop msg
24+
endif
25+
end procedure
26+
27+
end submodule estop

Diff for: src/stdlib_experimental_error.f90

+12-19
Original file line numberDiff line numberDiff line change
@@ -1,41 +1,34 @@
11
module stdlib_experimental_error
2+
use, intrinsic :: iso_fortran_env, only: stderr=>error_unit
23
implicit none
34
private
5+
6+
interface ! f{08,18}estop.f90
7+
module subroutine error_stop(msg, code)
8+
character(*), intent(in) :: msg
9+
integer, intent(in), optional :: code
10+
end subroutine error_stop
11+
end interface
12+
413
public :: assert, error_stop
514

615
contains
716

8-
subroutine assert(condition)
17+
subroutine assert(condition, code)
918
! If condition == .false., it aborts the program.
1019
!
1120
! Arguments
1221
! ---------
1322
!
1423
logical, intent(in) :: condition
24+
integer, intent(in), optional :: code
1525
!
1626
! Example
1727
! -------
1828
!
1929
! call assert(a == 5)
2030

21-
if (.not. condition) call error_stop("Assert failed.")
22-
end subroutine
23-
24-
subroutine error_stop(msg)
25-
! Aborts the program with nonzero exit code
26-
!
27-
! The statement "stop msg" will return 0 exit code when compiled using
28-
! gfortran. error_stop() uses the statement "stop 1" which returns an exit code
29-
! 1 and a print statement to print the message.
30-
!
31-
! Example
32-
! -------
33-
!
34-
! call error_stop("Invalid argument")
35-
36-
character(len=*) :: msg ! Message to print on stdout
37-
print *, msg
38-
stop 1
31+
if (.not. condition) call error_stop("Assert failed.", code)
3932
end subroutine
4033

4134
end module

Diff for: src/tests/CMakeLists.txt

+9
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,12 @@
11
add_subdirectory(ascii)
22
add_subdirectory(loadtxt)
33

4+
add_executable(test_skip test_skip.f90)
5+
target_link_libraries(test_skip fortran_stdlib)
6+
add_test(NAME AlwaysSkip COMMAND $<TARGET_FILE:test_skip>)
7+
set_tests_properties(AlwaysSkip PROPERTIES SKIP_RETURN_CODE 77)
8+
9+
add_executable(test_fail test_fail.f90)
10+
target_link_libraries(test_fail fortran_stdlib)
11+
add_test(NAME AlwaysFail COMMAND $<TARGET_FILE:test_fail>)
12+
set_tests_properties(AlwaysFail PROPERTIES WILL_FAIL true)

Diff for: src/tests/loadtxt/test_loadtxt.f90

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
program test_loadtxt
22
use iso_fortran_env, only: sp=>real32, dp=>real64
33
use stdlib_experimental_io, only: loadtxt
4+
use stdlib_experimental_error, only: error_stop
45
implicit none
56

67
real(sp), allocatable :: s(:, :)
@@ -38,8 +39,7 @@ subroutine print_array(a)
3839
print *, a(i, :)
3940
end do
4041
class default
41-
write(*,'(a)')'The proposed type is not supported'
42-
error stop
42+
call error_stop('The proposed type is not supported')
4343
end select
4444

4545
end subroutine

Diff for: src/tests/test_fail.f90

+8
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program AlwaysFail
2+
3+
use stdlib_experimental_error, only : assert
4+
implicit none
5+
6+
call assert(.false.)
7+
8+
end program

Diff for: src/tests/test_skip.f90

+8
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program AlwaysSkip
2+
3+
use stdlib_experimental_error, only : assert
4+
implicit none
5+
6+
call assert(.false., 77)
7+
8+
end program

0 commit comments

Comments
 (0)