diff --git a/src/stdlib_logger.f90 b/src/stdlib_logger.f90 index 70f83b94b..7951ae643 100644 --- a/src/stdlib_logger.f90 +++ b/src/stdlib_logger.f90 @@ -308,6 +308,7 @@ subroutine add_log_unit( self, unit, stat ) integer :: lun character(12) :: specifier logical :: question + integer :: istat call validate_unit() if ( present(stat) ) then @@ -350,7 +351,8 @@ subroutine validate_unit() end if ! Check that unit is opened - inquire( unit, opened=question ) + inquire( unit, opened=question, iostat=istat ) + if(istat /= 0) question = .false. if ( .not. question ) then if ( present(stat) ) then stat = unopened_in_error diff --git a/src/stdlib_string_type.fypp b/src/stdlib_string_type.fypp index 772fa4642..144cd2716 100644 --- a/src/stdlib_string_type.fypp +++ b/src/stdlib_string_type.fypp @@ -421,7 +421,11 @@ contains type(string_type), intent(in) :: string integer :: ich - ich = merge(ichar(string%raw), 0, allocated(string%raw)) + if (allocated(string%raw) .and. len(string) > 0) then + ich = ichar(string%raw(1:1)) + else + ich = 0 + end if end function ichar_string @@ -431,7 +435,11 @@ contains type(string_type), intent(in) :: string integer :: ich - ich = merge(iachar(string%raw), 0, allocated(string%raw)) + if (allocated(string%raw) .and. len(string) > 0) then + ich = iachar(string%raw(1:1)) + else + ich = 0 + end if end function iachar_string @@ -571,8 +579,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = index(maybe(string), maybe(substring), & - merge(back, .false., present(back))) + if (present(back)) then + pos = index(maybe(string), maybe(substring), back) + else + pos = index(maybe(string), maybe(substring), .false.) + end if end function index_string_string @@ -584,8 +595,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = index(maybe(string), substring, & - merge(back, .false., present(back))) + if (present(back)) then + pos = index(maybe(string), substring, back) + else + pos = index(maybe(string), substring, .false.) + end if end function index_string_char @@ -597,8 +611,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = index(string, maybe(substring), & - merge(back, .false., present(back))) + if (present(back)) then + pos = index(string, maybe(substring), back) + else + pos = index(string, maybe(substring), .false.) + end if end function index_char_string @@ -612,8 +629,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = scan(maybe(string), maybe(set), & - merge(back, .false., present(back))) + if (present(back)) then + pos = scan(maybe(string), maybe(set), back) + else + pos = scan(maybe(string), maybe(set), .false.) + end if end function scan_string_string @@ -625,8 +645,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = scan(maybe(string), set, & - merge(back, .false., present(back))) + if (present(back)) then + pos = scan(maybe(string), set, back) + else + pos = scan(maybe(string), set, .false.) + end if end function scan_string_char @@ -638,8 +661,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = scan(string, maybe(set), & - merge(back, .false., present(back))) + if (present(back)) then + pos = scan(string, maybe(set), back) + else + pos = scan(string, maybe(set), .false.) + end if end function scan_char_string @@ -653,8 +679,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = verify(maybe(string), maybe(set), & - merge(back, .false., present(back))) + if (present(back)) then + pos = verify(maybe(string), maybe(set), back) + else + pos = verify(maybe(string), maybe(set), .false.) + end if end function verify_string_string @@ -667,8 +696,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = verify(maybe(string), set, & - merge(back, .false., present(back))) + if (present(back)) then + pos = verify(maybe(string), set, back) + else + pos = verify(maybe(string), set, .false.) + end if end function verify_string_char @@ -681,8 +713,11 @@ contains logical, intent(in), optional :: back integer :: pos - pos = verify(string, maybe(set), & - merge(back, .false., present(back))) + if (present(back)) then + pos = verify(string, maybe(set), back) + else + pos = verify(string, maybe(set), .false.) + end if end function verify_char_string diff --git a/src/tests/logger/test_stdlib_logger.f90 b/src/tests/logger/test_stdlib_logger.f90 index 649494819..d21ff1baf 100644 --- a/src/tests/logger/test_stdlib_logger.f90 +++ b/src/tests/logger/test_stdlib_logger.f90 @@ -417,6 +417,7 @@ end subroutine test_adding_log_files subroutine test_removing_log_units() logical :: opened + integer :: istat print * print *, 'running test_removing_log_units' @@ -462,7 +463,8 @@ subroutine test_removing_log_units() end if - inquire( unit4, opened=opened ) + inquire( unit4, opened=opened, iostat=istat ) + if(istat /= 0) opened = .false. if ( opened ) then error stop 'UNIT4 is opened contrary to expectations.' diff --git a/src/tests/stats/test_mean_f03.f90 b/src/tests/stats/test_mean_f03.f90 index fc90c4eaf..6ff8d997e 100644 --- a/src/tests/stats/test_mean_f03.f90 +++ b/src/tests/stats/test_mean_f03.f90 @@ -20,7 +20,7 @@ program test_mean call check( sum( abs( mean(d,2) - sum(d,2)/real(size(d,2), dp) )) < dptol) !dp rank 8 -allocate(d8(size(d,1), size(d,2), 3, 4, 5, 6, 7, 8)) +allocate(d8(size(d,1), size(d,2), 3, 4, 5, 6, 7, 8), source=0.0_dp) d8(:, :, 1, 4, 5 ,6 ,7 ,8)=d; d8(:, :, 2, 4, 5 ,6 ,7 ,8)=d * 1.5_dp; d8(:, :, 3, 4, 5 ,6 ,7 ,8)=d * 4._dp;