Skip to content

Commit f765b04

Browse files
committed
Use test for npz file containing two arrays
1 parent c93b9ae commit f765b04

File tree

2 files changed

+48
-1
lines changed

2 files changed

+48
-1
lines changed

test/io/test_np.f90

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,8 @@ subroutine collect_np(testsuite)
4444
new_unittest("npz_load_arr_empty_0", npz_load_arr_empty_0), &
4545
new_unittest("npz_load_arr_rand_2_3", npz_load_arr_rand_2_3), &
4646
new_unittest("npz_load_arr_arange_10_20", npz_load_arr_arange_10_20), &
47-
new_unittest("npz_load_arr_cmplx", npz_load_arr_cmplx) &
47+
new_unittest("npz_load_arr_cmplx", npz_load_arr_cmplx), &
48+
new_unittest("npz_load_two_arr_iint64_rdp", npz_load_two_arr_iint64_rdp) &
4849
]
4950
end subroutine collect_np
5051

@@ -824,6 +825,52 @@ subroutine npz_load_arr_cmplx(error)
824825
end select
825826
end
826827

828+
subroutine npz_load_two_arr_iint64_rdp(error)
829+
type(error_type), allocatable, intent(out) :: error
830+
831+
type(t_array_wrapper), allocatable :: arrays(:)
832+
integer :: stat, i
833+
character(*), parameter :: filename = "two_arr_iint64_rdp.npz"
834+
character(:), allocatable :: path
835+
836+
path = get_path(filename)
837+
call load_npz(path, arrays, stat)
838+
call check(error, stat, "Loading an npz file that contains a valid nd_array shouldn't fail.")
839+
if (stat /= 0) return
840+
call check(error, size(arrays) == 2, "'"//filename//"' is supposed to contain two arrays.")
841+
if (size(arrays) /= 2) return
842+
call check(error, arrays(1)%array%name == "arr_0.npy", "Wrong array name.")
843+
if (arrays(1)%array%name /= "arr_0.npy") return
844+
call check(error, arrays(2)%array%name == "arr_1.npy", "Wrong array name.")
845+
if (arrays(2)%array%name /= "arr_1.npy") return
846+
select type (typed_array => arrays(1)%array)
847+
class is (t_array_iint64_1)
848+
call check(error, size(typed_array%values) == 3, "Array in '"//filename//"' is supposed to have 3 entries.")
849+
if (size(typed_array%values) /= 3) return
850+
call check(error, typed_array%values(1) == 1, "First integer does not match.")
851+
if (typed_array%values(1) /= 1) return
852+
call check(error, typed_array%values(2) == 2, "Second integer does not match.")
853+
if (typed_array%values(2) /= 2) return
854+
call check(error, typed_array%values(3) == 3, "Third integer does not match.")
855+
if (typed_array%values(3) /= 3) return
856+
class default
857+
call test_failed(error, "Array in '"//filename//"' is of wrong type.")
858+
end select
859+
select type (typed_array => arrays(2)%array)
860+
class is (t_array_rdp_1)
861+
call check(error, size(typed_array%values) == 3, "Array in '"//filename//"' is supposed to have 3 entries.")
862+
if (size(typed_array%values) /= 3) return
863+
call check(error, typed_array%values(1) == 1., "First number does not match.")
864+
if (typed_array%values(1) /= 1.) return
865+
call check(error, typed_array%values(2) == 1., "Second number does not match.")
866+
if (typed_array%values(2) /= 1.) return
867+
call check(error, typed_array%values(3) == 1., "Third number does not match.")
868+
if (typed_array%values(3) /= 1.) return
869+
class default
870+
call test_failed(error, "Array in '"//filename//"' is of wrong type.")
871+
end select
872+
end
873+
827874
!> Makes sure that we find the file when running both `ctest` and `fpm test`.
828875
function get_path(file) result(path)
829876
character(*), intent(in) :: file
554 Bytes
Binary file not shown.

0 commit comments

Comments
 (0)