Skip to content
Merged
Show file tree
Hide file tree
Changes from 6 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion src/stdlib_logger.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
75 changes: 55 additions & 20 deletions src/stdlib_string_type.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -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_trim(string%raw) > 0) then
ich = ichar(string%raw(1:1))
else
ich = 0
end if

end function ichar_string

Expand All @@ -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_trim(string%raw) > 0) then
ich = iachar(string%raw(1:1))
else
ich = 0
end if

end function iachar_string

Expand Down Expand Up @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand All @@ -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

Expand Down
4 changes: 3 additions & 1 deletion src/tests/logger/test_stdlib_logger.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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'
Expand Down Expand Up @@ -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.'

Expand Down
2 changes: 1 addition & 1 deletion src/tests/stats/test_mean_f03.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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;
Expand Down