Skip to content

Commit

Permalink
Merge pull request #600 from ivan-pi/npy
Browse files Browse the repository at this point in the history
Fix iomsg allocation in save_npy
  • Loading branch information
milancurcic authored Dec 17, 2021
2 parents 4069d81 + 1974cb4 commit 10f9438
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 2 deletions.
4 changes: 3 additions & 1 deletion src/stdlib_io_npy_save.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,9 @@ contains
end if

if (present(iomsg)) then
iomsg = "Failed to write array to file '"//filename//"'"
if (stat /= 0) then
iomsg = "Failed to write array to file '"//filename//"'"
end if
end if
end subroutine save_npy_${t1[0]}$${k1}$_${rank}$
#:endfor
Expand Down
24 changes: 23 additions & 1 deletion src/tests/io/test_npy.f90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,8 @@ subroutine collect_npy(testsuite)
new_unittest("duplicate-descr", test_duplicate_descr, should_fail=.true.), &
new_unittest("missing-descr", test_missing_descr, should_fail=.true.), &
new_unittest("missing-fortran_order", test_missing_fortran_order, should_fail=.true.), &
new_unittest("missing-shape", test_missing_shape, should_fail=.true.) &
new_unittest("missing-shape", test_missing_shape, should_fail=.true.), &
new_unittest("iomsg-deallocated", test_iomsg_deallocated) &
]
end subroutine collect_npy

Expand Down Expand Up @@ -619,6 +620,27 @@ subroutine test_missing_shape(error)
call check(error, stat, msg)
end subroutine test_missing_shape

subroutine test_iomsg_deallocated(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error

integer :: stat
character(len=:), allocatable :: msg

character(len=*), parameter :: filename = ".test-iomsg-deallocated.npy"
real(sp), allocatable :: input(:, :), output(:, :)

msg = "This message should be deallocated."

allocate(input(12, 5))
call random_number(input)
call save_npy(filename, input, stat, msg)
call delete_file(filename)

call check(error,.not. allocated(msg), "Message wrongly allocated.")

end subroutine

subroutine delete_file(filename)
character(len=*), intent(in) :: filename

Expand Down

0 comments on commit 10f9438

Please sign in to comment.