|
1 | 1 | module test_np
|
2 | 2 | use stdlib_kinds, only: int8, int16, int32, int64, sp, dp
|
3 |
| - use stdlib_array, only: t_array_wrapper |
| 3 | + use stdlib_array |
| 4 | + use stdlib_strings, only: to_string |
4 | 5 | use stdlib_io_np, only: load_npy, save_npy, load_npz
|
5 |
| - use testdrive, only: new_unittest, unittest_type, error_type, check |
| 6 | + use testdrive, only: new_unittest, unittest_type, error_type, check, test_failed |
6 | 7 | implicit none
|
7 | 8 | private
|
8 | 9 |
|
@@ -42,7 +43,9 @@ subroutine collect_np(testsuite)
|
42 | 43 | new_unittest("npz-empty-zip", test_npz_empty_zip, should_fail=.true.), &
|
43 | 44 | new_unittest("npz-not-zip", test_npz_not_zip, should_fail=.true.), &
|
44 | 45 | new_unittest("npz-empty-array", test_npz_empty_array), &
|
45 |
| - new_unittest("npz-exceeded-rank", test_npz_exceeded_rank, should_fail=.true.) & |
| 46 | + new_unittest("npz-exceeded-rank", test_npz_exceeded_rank, should_fail=.true.), & |
| 47 | + new_unittest("npz-single-file-one-dim", test_npz_single_file_one_dim), & |
| 48 | + new_unittest("npz-two-files-one-dim", test_npz_two_files) & |
46 | 49 | ]
|
47 | 50 | end subroutine collect_np
|
48 | 51 |
|
@@ -743,6 +746,16 @@ subroutine test_npz_empty_array(error)
|
743 | 746 | call delete_file(filename)
|
744 | 747 |
|
745 | 748 | call check(error, stat, msg)
|
| 749 | + call check(error, size(arrays) == 1, 'Size of arrays not 1: '//trim(to_string(size(arrays)))) |
| 750 | + call check(error, allocated(arrays(1)%array), 'Array not allocated.') |
| 751 | + |
| 752 | + select type (array => arrays(1)%array) |
| 753 | + type is (t_array_rdp_1) |
| 754 | + call check(error, allocated(array%values), 'Values not allocated.') |
| 755 | + call check(error, size(array%values) == 0, 'Values not empty: '//trim(to_string(size(array%values)))) |
| 756 | + class default |
| 757 | + call test_failed(error, 'Array not allocated for correct type.') |
| 758 | + end select |
746 | 759 | end
|
747 | 760 |
|
748 | 761 | subroutine test_npz_exceeded_rank(error)
|
@@ -774,6 +787,118 @@ subroutine test_npz_exceeded_rank(error)
|
774 | 787 | call check(error, stat, msg)
|
775 | 788 | end
|
776 | 789 |
|
| 790 | + subroutine test_npz_single_file_one_dim(error) |
| 791 | + type(error_type), allocatable, intent(out) :: error |
| 792 | + |
| 793 | + ! arr_0.npy = [2,4,8] |
| 794 | + character(*), parameter :: binary_data = 'PK'//char(3)//char(4)//'-'//repeat(char(0), 7)//'!'//char(0)//'&M'// & |
| 795 | + & char(int(z'b0'))//char(int(z'd8'))//repeat(char(int(z'ff')), 8)//char(9)//char(0)//char(int(z'14'))// & |
| 796 | + & char(0)//'arr_0.npy'//char(1)//char(0)//char(int(z'10'))//char(0)//char(int(z'98'))//repeat(char(0), 7)// & |
| 797 | + & char(int(z'98'))//repeat(char(0), 7)//char(int(z'93'))//'NUMPY'//char(1)//char(0)//'v'//char(0)// & |
| 798 | + & "{'descr': '<i8', 'fortran_order': False, 'shape': (3,), }"//repeat(' ', 60)//char(int(z'0a'))// & |
| 799 | + & char(2)//repeat(char(0), 7)//char(4)//repeat(char(0), 7)//char(8)//repeat(char(0), 7)//'PK'//char(1)//char(2)// & |
| 800 | + & '-'//char(3)//'-'//repeat(char(0), 7)//'!'//char(0)//'&M'//char(int(z'b0'))//char(int(z'd8'))//char(int(z'98'))// & |
| 801 | + & repeat(char(0), 3)//char(int(z'98'))//repeat(char(0), 3)//char(9)//repeat(char(0), 11)//char(int(z'80'))//char(1)// & |
| 802 | + & repeat(char(0), 4)//'arr_0.npyPK'//char(5)//char(6)//repeat(char(0), 4)//char(1)//char(0)//char(1)// & |
| 803 | + & char(0)//'7'//repeat(char(0), 3)//char(int(z'd3'))//repeat(char(0), 5) |
| 804 | + |
| 805 | + integer :: io, stat |
| 806 | + character(len=:), allocatable :: msg |
| 807 | + character(len=*), parameter :: filename = '.test-single-file-one-dim.npz' |
| 808 | + type(t_array_wrapper), allocatable :: arrays(:) |
| 809 | + |
| 810 | + open (newunit=io, file=filename, form='unformatted', access='stream') |
| 811 | + write (io) binary_data |
| 812 | + close (io) |
| 813 | + |
| 814 | + call load_npz(filename, arrays, stat, msg) |
| 815 | + call delete_file(filename) |
| 816 | + |
| 817 | + call check(error, stat, msg) |
| 818 | + call check(error, size(arrays) == 1, 'Size of arrays not 1: '//trim(to_string(size(arrays)))) |
| 819 | + call check(error, allocated(arrays(1)%array), 'Array not allocated.') |
| 820 | + |
| 821 | + select type (array => arrays(1)%array) |
| 822 | + type is (t_array_iint64_1) |
| 823 | + call check(error, array%name == 'arr_0.npy', 'Wrong name: '//trim(array%name)) |
| 824 | + call check(error, allocated(array%values), 'Values not allocated.') |
| 825 | + call check(error, size(array%values) == 3, 'Not 3 entries in values: '//trim(to_string(size(array%values)))) |
| 826 | + call check(error, array%values(1) == 2, 'First value is not 2: '//trim(to_string(array%values(1)))) |
| 827 | + call check(error, array%values(2) == 4, 'Second value is not 4: '//trim(to_string(array%values(2)))) |
| 828 | + call check(error, array%values(3) == 8, 'Third value is not 8: '//trim(to_string(array%values(3)))) |
| 829 | + class default |
| 830 | + call test_failed(error, 'Array not allocated for correct type.') |
| 831 | + end select |
| 832 | + end |
| 833 | + |
| 834 | + subroutine test_npz_two_files(error) |
| 835 | + type(error_type), allocatable, intent(out) :: error |
| 836 | + |
| 837 | + ! arr_0.npy = [[1,2],[3,4]] |
| 838 | + ! arr_1.npy = [1.2,3.4] |
| 839 | + character(*), parameter :: binary_data = 'PK'//char(3)//char(4)//'-'//repeat(char(0), 7)//'!'//char(0)//char(int(z'a0'))// & |
| 840 | + & 'DK['//repeat(char(int(z'ff')), 8)//char(9)//char(0)//char(int(z'14'))//char(0)//'arr_0.npy'//char(1)// & |
| 841 | + & char(0)//char(int(z'10'))//char(0)//char(int(z'a0'))//repeat(char(0), 7)//char(int(z'a0'))// & |
| 842 | + & repeat(char(0), 7)//char(int(z'93'))//'NUMPY'//char(1)//char(0)//'v'//char(0)// & |
| 843 | + & "{'descr': '<i8', 'fortran_order': False, 'shape': (2, 2), }"//repeat(' ', 58)//char(int(z'0a'))//char(1)// & |
| 844 | + & repeat(char(0), 7)//char(2)//repeat(char(0), 7)//char(3)//repeat(char(0), 7)//char(4)//repeat(char(0), 7)//'PK'// & |
| 845 | + & char(3)//char(4)//'-'//repeat(char(0), 7)//'!'//char(0)//char(int(z'f0'))//'zM?'//repeat(char(int(z'ff')), 8)// & |
| 846 | + & char(9)//char(0)//char(int(z'14'))//char(0)//'arr_1.npy'//char(1)//char(0)//char(int(z'10'))//char(0)// & |
| 847 | + & char(int(z'90'))//repeat(char(0), 7)//char(int(z'90'))//repeat(char(0), 7)//char(int(z'93'))//'NUMPY'//char(1)// & |
| 848 | + & char(0)//'v'//char(0)//"{'descr': '<f8', 'fortran_order': False, 'shape': (2,), }"//repeat(' ', 60)// & |
| 849 | + & char(int(z'0a'))//'333333'//char(int(z'f3'))//'?333333'//char(int(z'0b'))//'@PK'//char(1)//char(2)//'-'// & |
| 850 | + & char(3)//'-'//repeat(char(0), 7)//'!'//char(0)//char(int(z'a0'))//'DK['//char(int(z'a0'))//repeat(char(0), 3)// & |
| 851 | + & char(int(z'a0'))//repeat(char(0), 3)//char(9)//repeat(char(0), 11)//char(int(z'80'))//char(1)//repeat(char(0), 4)// & |
| 852 | + & 'arr_0.npyPK'//char(1)//char(2)//'-'//char(3)//'-'//repeat(char(0), 7)//'!'//char(0)//char(int(z'f0'))//'zM?'// & |
| 853 | + & char(int(z'90'))//repeat(char(0), 3)//char(int(z'90'))//repeat(char(0), 3)//char(9)//repeat(char(0), 11)// & |
| 854 | + & char(int(z'80'))//char(1)//char(int(z'db'))//repeat(char(0), 3)//'arr_1.npyPK'//char(5)//char(6)// & |
| 855 | + & repeat(char(0), 4)//char(2)//char(0)//char(2)//char(0)//'n'//repeat(char(0), 3)//char(int(z'a6'))//char(1)// & |
| 856 | + & repeat(char(0), 4) |
| 857 | + |
| 858 | + integer :: io, stat |
| 859 | + character(len=:), allocatable :: msg |
| 860 | + character(len=*), parameter :: filename = '.test-two-files.npz' |
| 861 | + type(t_array_wrapper), allocatable :: arrays(:) |
| 862 | + |
| 863 | + open (newunit=io, file=filename, form='unformatted', access='stream') |
| 864 | + write (io) binary_data |
| 865 | + close (io) |
| 866 | + |
| 867 | + call load_npz(filename, arrays, stat, msg) |
| 868 | + call delete_file(filename) |
| 869 | + |
| 870 | + call check(error, stat, msg) |
| 871 | + call check(error, size(arrays) == 2, 'Size of arrays not 2: '//trim(to_string(size(arrays)))) |
| 872 | + call check(error, allocated(arrays(1)%array), 'Array 1 not allocated.') |
| 873 | + call check(error, allocated(arrays(2)%array), 'Array 2 not allocated.') |
| 874 | + |
| 875 | + select type (array => arrays(1)%array) |
| 876 | + type is (t_array_iint64_2) |
| 877 | + call check(error, array%name == 'arr_0.npy', 'Wrong name: '//trim(array%name)) |
| 878 | + call check(error, allocated(array%values), 'Values not allocated.') |
| 879 | + call check(error, size(array%values) == 4, 'Not 4 entries in values: '//trim(to_string(size(array%values)))) |
| 880 | + call check(error, size(array%values, 1) == 2, 'Not 2 entries in dim 1: '//trim(to_string(size(array%values, 2)))) |
| 881 | + call check(error, size(array%values, 2) == 2, 'Not 2 entries in dim 2: '//trim(to_string(size(array%values, 2)))) |
| 882 | + call check(error, array%values(1, 1) == 1, 'First value in dim 1 not 1: '//trim(to_string(array%values(1, 1)))) |
| 883 | + call check(error, array%values(2, 1) == 2, 'Second value in dim 1 not 2: '//trim(to_string(array%values(2, 1)))) |
| 884 | + call check(error, array%values(1, 2) == 3, 'First value in dim 2 not 3: '//trim(to_string(array%values(1, 2)))) |
| 885 | + call check(error, array%values(2, 2) == 4, 'Second value in dim 2 not 4: '//trim(to_string(array%values(2, 2)))) |
| 886 | + class default |
| 887 | + call test_failed(error, 'Array not allocated for correct type.') |
| 888 | + end select |
| 889 | + |
| 890 | + select type (array => arrays(2)%array) |
| 891 | + type is (t_array_rdp_1) |
| 892 | + call check(error, array%name == 'arr_1.npy', 'Wrong name: '//trim(array%name)) |
| 893 | + call check(error, allocated(array%values), 'Values not allocated.') |
| 894 | + call check(error, size(array%values) == 2, 'Not 2 entries in values: '//trim(to_string(size(array%values)))) |
| 895 | + call check(error, array%values(1) == 1.2_dp, 'First value in dim 1 not 1.2: '//trim(to_string(array%values(1)))) |
| 896 | + call check(error, array%values(2) == 3.4_dp, 'Second value in dim 1 not 3.4: '//trim(to_string(array%values(2)))) |
| 897 | + class default |
| 898 | + call test_failed(error, 'Array not allocated for correct type.') |
| 899 | + end select |
| 900 | + end |
| 901 | + |
777 | 902 | subroutine delete_file(filename)
|
778 | 903 | character(len=*), intent(in) :: filename
|
779 | 904 |
|
|
0 commit comments