Skip to content

Commit

Permalink
Merge pull request #163 from milancurcic/121-replace-assert-with-check
Browse files Browse the repository at this point in the history
121 replace assert with check
  • Loading branch information
milancurcic authored Mar 25, 2020
2 parents 5d1e091 + daeb19e commit bdd15c8
Show file tree
Hide file tree
Showing 16 changed files with 940 additions and 909 deletions.
1 change: 1 addition & 0 deletions src/Makefile.manual
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ clean:

# Fortran module dependencies
f18estop.o: stdlib_experimental_error.o
stdlib_experimental_error.o: stdlib_experimental_optval.o
stdlib_experimental_io.o: \
stdlib_experimental_error.o \
stdlib_experimental_optval.o \
Expand Down
78 changes: 54 additions & 24 deletions src/stdlib_experimental_error.f90
Original file line number Diff line number Diff line change
@@ -1,34 +1,64 @@
module stdlib_experimental_error
use, intrinsic :: iso_fortran_env, only: stderr=>error_unit
use, intrinsic :: iso_fortran_env, only: stderr => error_unit
use stdlib_experimental_optval, only: optval
implicit none
private

interface ! f{08,18}estop.f90
module subroutine error_stop(msg, code)
character(*), intent(in) :: msg
integer, intent(in), optional :: code
end subroutine error_stop
module subroutine error_stop(msg, code)
character(*), intent(in) :: msg
integer, intent(in), optional :: code
end subroutine error_stop
end interface

public :: assert, error_stop
public :: check, error_stop

contains

subroutine assert(condition, code)
! If condition == .false., it aborts the program.
!
! Arguments
! ---------
!
logical, intent(in) :: condition
integer, intent(in), optional :: code
!
! Example
! -------
!
! call assert(a == 5)

if (.not. condition) call error_stop("Assert failed.", code)
end subroutine

end module
subroutine check(condition, msg, code, warn)

! Checks the value of a logical condition. If condition == .false. and:
!
! * No other arguments are provided, it stops the program with the default
! message and exit code 1;
! * msg is provided, it prints the value of msg;
! * code is provided, it stops the program with the given exit code;
! * warn is provided and .true., it doesn't stop the program and prints
! * the message.
!
! Arguments
! ---------

logical, intent(in) :: condition
character(*), intent(in), optional :: msg
integer, intent(in), optional :: code
logical, intent(in), optional :: warn
character(*), parameter :: msg_default = 'Check failed.'

! Examples
! --------
!
! ! If a /= 5, stops the program with exit code 1
! ! and prints 'Check failed.'
! call check(a == 5)
!
! ! As above, but prints 'a == 5 failed.'
! call check(a == 5, msg='a == 5 failed.')
!
! ! As above, but doesn't stop the program.
! call check(a == 5, msg='a == 5 failed.', warn=.true.)
!
! ! As example #2, but stops the program with exit code 77
! call check(a == 5, msg='a == 5 failed.', code=77)

if (.not. condition) then
if (optval(warn, .false.)) then
write(stderr,*) optval(msg, msg_default)
else
call error_stop(optval(msg, msg_default), optval(code, 1))
end if
end if

end subroutine check

end module stdlib_experimental_error
Loading

0 comments on commit bdd15c8

Please sign in to comment.