Skip to content

Commit e134c9d

Browse files
committed
Add test for a compressed npz file
1 parent f765b04 commit e134c9d

File tree

4 files changed

+52
-5
lines changed

4 files changed

+52
-5
lines changed

test/io/test_np.f90

Lines changed: 51 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,8 @@ subroutine collect_np(testsuite)
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), &
4747
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) &
48+
new_unittest("npz_load_two_arr_iint64_rdp", npz_load_two_arr_iint64_rdp), &
49+
new_unittest("npz_load_two_arr_iint64_rdp_comp", npz_load_two_arr_iint64_rdp_comp) &
4950
]
5051
end subroutine collect_np
5152

@@ -798,7 +799,7 @@ subroutine npz_load_arr_cmplx(error)
798799
type(error_type), allocatable, intent(out) :: error
799800

800801
type(t_array_wrapper), allocatable :: arrays(:)
801-
integer :: stat, i
802+
integer :: stat
802803
character(*), parameter :: filename = "cmplx_arr.npz"
803804
character(:), allocatable :: path
804805

@@ -829,13 +830,59 @@ subroutine npz_load_two_arr_iint64_rdp(error)
829830
type(error_type), allocatable, intent(out) :: error
830831

831832
type(t_array_wrapper), allocatable :: arrays(:)
832-
integer :: stat, i
833+
integer :: stat
833834
character(*), parameter :: filename = "two_arr_iint64_rdp.npz"
834835
character(:), allocatable :: path
835836

836837
path = get_path(filename)
837838
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+
call check(error, stat, "Loading an npz file that contains valid nd_arrays shouldn't fail.")
840+
if (stat /= 0) return
841+
call check(error, size(arrays) == 2, "'"//filename//"' is supposed to contain two arrays.")
842+
if (size(arrays) /= 2) return
843+
call check(error, arrays(1)%array%name == "arr_0.npy", "Wrong array name.")
844+
if (arrays(1)%array%name /= "arr_0.npy") return
845+
call check(error, arrays(2)%array%name == "arr_1.npy", "Wrong array name.")
846+
if (arrays(2)%array%name /= "arr_1.npy") return
847+
select type (typed_array => arrays(1)%array)
848+
class is (t_array_iint64_1)
849+
call check(error, size(typed_array%values) == 3, "Array in '"//filename//"' is supposed to have 3 entries.")
850+
if (size(typed_array%values) /= 3) return
851+
call check(error, typed_array%values(1) == 1, "First integer does not match.")
852+
if (typed_array%values(1) /= 1) return
853+
call check(error, typed_array%values(2) == 2, "Second integer does not match.")
854+
if (typed_array%values(2) /= 2) return
855+
call check(error, typed_array%values(3) == 3, "Third integer does not match.")
856+
if (typed_array%values(3) /= 3) return
857+
class default
858+
call test_failed(error, "Array in '"//filename//"' is of wrong type.")
859+
end select
860+
select type (typed_array => arrays(2)%array)
861+
class is (t_array_rdp_1)
862+
call check(error, size(typed_array%values) == 3, "Array in '"//filename//"' is supposed to have 3 entries.")
863+
if (size(typed_array%values) /= 3) return
864+
call check(error, typed_array%values(1) == 1., "First number does not match.")
865+
if (typed_array%values(1) /= 1.) return
866+
call check(error, typed_array%values(2) == 1., "Second number does not match.")
867+
if (typed_array%values(2) /= 1.) return
868+
call check(error, typed_array%values(3) == 1., "Third number does not match.")
869+
if (typed_array%values(3) /= 1.) return
870+
class default
871+
call test_failed(error, "Array in '"//filename//"' is of wrong type.")
872+
end select
873+
end
874+
875+
subroutine npz_load_two_arr_iint64_rdp_comp(error)
876+
type(error_type), allocatable, intent(out) :: error
877+
878+
type(t_array_wrapper), allocatable :: arrays(:)
879+
integer :: stat, i
880+
character(*), parameter :: filename = "two_arr_iint64_rdp_comp.npz"
881+
character(:), allocatable :: path
882+
883+
path = get_path(filename)
884+
call load_npz(path, arrays, stat)
885+
call check(error, stat, "Loading a compressed npz file that contains valid nd_arrays shouldn't fail.")
839886
if (stat /= 0) return
840887
call check(error, size(arrays) == 2, "'"//filename//"' is supposed to contain two arrays.")
841888
if (size(arrays) /= 2) return

test/io/test_zip.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,7 @@ subroutine unzip_compressed_npz(error)
142142
type(error_type), allocatable, intent(out) :: error
143143

144144
integer :: stat
145-
character(*), parameter :: filename = "two_files_compressed.npz"
145+
character(*), parameter :: filename = "two_arr_iint64_rdp_comp.npz"
146146
character(:), allocatable :: path
147147

148148
path = get_path(filename)
402 Bytes
Binary file not shown.
-415 Bytes
Binary file not shown.

0 commit comments

Comments
 (0)