@@ -48,8 +48,8 @@ subroutine collect_np(testsuite)
48
48
new_unittest(" npz_load_arr_cmplx" , npz_load_arr_cmplx), &
49
49
new_unittest(" npz_load_two_arr_iint64_rdp" , npz_load_two_arr_iint64_rdp), &
50
50
new_unittest(" npz_load_two_arr_iint64_rdp_comp" , npz_load_two_arr_iint64_rdp_comp), &
51
- new_unittest(" npz_save_empty_array_input " , npz_save_empty_array_input, should_fail = .true. ), &
52
- new_unittest(" npz_save_rdp_2 " , npz_save_rdp_2 ) &
51
+ new_unittest(" npz_add_to_empty_arr " , npz_add_to_empty_arr ), &
52
+ new_unittest(" npz_save_empty_array_input " , npz_save_empty_array_input, should_fail = .true. ) &
53
53
]
54
54
end subroutine collect_np
55
55
@@ -934,25 +934,13 @@ subroutine npz_load_two_arr_iint64_rdp_comp(error)
934
934
end select
935
935
end
936
936
937
- subroutine npz_save_empty_array_input (error )
937
+ subroutine npz_add_to_empty_arr (error )
938
938
type (error_type), allocatable , intent (out ) :: error
939
939
940
940
type (t_array_wrapper), allocatable :: arrays(:)
941
941
integer :: stat
942
- character (* ), parameter :: filename = " output.npz"
943
-
944
- allocate (arrays(0 ))
945
- call save_npz(filename, arrays, stat)
946
- call check(error, stat, " Trying to save an empty array fail." )
947
- end
948
-
949
- subroutine npz_save_rdp_2 (error )
950
- type (error_type), allocatable , intent (out ) :: error
951
-
952
- type (t_array_wrapper), allocatable :: arrays(:)
953
- integer :: stat
954
- character (* ), parameter :: filename = " npz_save_rdp_2.npz"
955
- real (dp), allocatable :: input_array(:,:), output(:,:)
942
+ character (* ), parameter :: filename = " npz_add_arr.npz"
943
+ real (dp), allocatable :: input_array(:,:)
956
944
957
945
allocate (input_array(10 , 4 ))
958
946
call random_number (input_array)
@@ -963,22 +951,47 @@ subroutine npz_save_rdp_2(error)
963
951
if (allocated (error)) return
964
952
call check(error, arrays(1 )% array% name == " arr_0.npy" , " Wrong array name." )
965
953
if (allocated (error)) return
954
+ select type (typed_array = > arrays(1 )% array)
955
+ class is (t_array_rdp_2)
956
+ call check(error, size (typed_array% values), size (input_array), " Array sizes to not match." )
957
+ if (allocated (error)) return
958
+ call check(error, any (abs (typed_array% values - input_array) <= epsilon (1.0_dp )), &
959
+ " Precision loss when adding array." )
960
+ if (allocated (error)) return
961
+ class default
962
+ call test_failed(error, " Array in '" // filename// " ' is of wrong type." )
963
+ end select
964
+ end
966
965
967
- ! call save_npz(filename, arrays, stat)
968
- ! call check(error, stat, "Writing of npz file failed")
969
- ! if (allocated(error)) return
970
-
971
- ! call load_npy(filename, output, stat)
972
- ! call delete_file(filename)
966
+ ! subroutine npz_add_arr(error)
967
+ ! type(error_type), allocatable, intent(out) :: error
968
+
969
+ ! type(t_array_wrapper), allocatable :: arrays(:)
970
+ ! integer :: stat
971
+ ! character(*), parameter :: filename = "npz_add_arr.npz"
972
+ ! real(dp), allocatable :: input_array(:,:)
973
+
974
+ ! allocate(input_array(10, 4))
975
+ ! call random_number(input_array)
976
+ ! call add_array(arrays, input_array, stat)
977
+ ! call check(error, stat, "Error adding an array to the list of arrays.")
978
+ ! if (allocated(error)) return
979
+ ! call check(error, size(arrays) == 1, "Array was not added to the list of arrays.")
980
+ ! if (allocated(error)) return
981
+ ! call check(error, arrays(1)%array%name == "arr_0.npy", "Wrong array name.")
982
+ ! if (allocated(error)) return
983
+ ! end
973
984
974
- ! call check (error, stat, "Reading of npy file failed" )
975
- ! if (allocated(error)) return
985
+ subroutine npz_save_empty_array_input (error )
986
+ type (error_type), allocatable , intent ( out ) :: error
976
987
977
- ! call check(error, size(output), size(input))
978
- ! if (allocated(error)) return
988
+ type (t_array_wrapper), allocatable :: arrays(:)
989
+ integer :: stat
990
+ character (* ), parameter :: filename = " output.npz"
979
991
980
- ! call check(error, any(abs(output - input) <= epsilon(1.0_dp)), &
981
- ! "Precision loss when rereading array")
992
+ allocate (arrays(0 ))
993
+ call save_npz(filename, arrays, stat)
994
+ call check(error, stat, " Trying to save an empty array fail." )
982
995
end
983
996
984
997
! > Makes sure that we find the file when running both `ctest` and `fpm test`.
0 commit comments