@@ -50,6 +50,9 @@ subroutine collect_np(testsuite)
50
50
new_unittest(" npz_load_two_arr_iint64_rdp_comp" , npz_load_two_arr_iint64_rdp_comp), &
51
51
new_unittest(" npz_add_arr_to_empty" , npz_add_arr_to_empty), &
52
52
new_unittest(" npz_add_two_arrays" , npz_add_two_arrays), &
53
+ new_unittest(" npz_add_arr_custom_name" , npz_add_arr_custom_name), &
54
+ new_unittest(" npz_add_arr_empty_name" , npz_add_arr_empty_name, should_fail= .true. ), &
55
+ new_unittest(" npz_add_arr_duplicate_names" , npz_add_arr_duplicate_names, should_fail= .true. ), &
53
56
new_unittest(" npz_save_empty_array_input" , npz_save_empty_array_input, should_fail= .true. ) &
54
57
]
55
58
end subroutine collect_np
@@ -1012,6 +1015,69 @@ subroutine npz_add_two_arrays(error)
1012
1015
end select
1013
1016
end
1014
1017
1018
+ subroutine npz_add_arr_custom_name (error )
1019
+ type (error_type), allocatable , intent (out ) :: error
1020
+
1021
+ type (t_array_wrapper), allocatable :: arrays(:)
1022
+ integer :: stat
1023
+ real (dp), allocatable :: input_array(:,:)
1024
+ character (* ), parameter :: arr_name = " custom_name.npy"
1025
+
1026
+ allocate (input_array(10 , 4 ))
1027
+ call random_number (input_array)
1028
+ call add_array(arrays, input_array, stat, name= arr_name)
1029
+ call check(error, stat, " Error adding an array to the list of arrays." )
1030
+ if (allocated (error)) return
1031
+ call check(error, size (arrays) == 1 , " Array was not added to the list of arrays." )
1032
+ if (allocated (error)) return
1033
+ call check(error, arrays(1 )% array% name == arr_name, " Wrong array name." )
1034
+ if (allocated (error)) return
1035
+ select type (typed_array = > arrays(1 )% array)
1036
+ class is (t_array_rdp_2)
1037
+ call check(error, size (typed_array% values), size (input_array), " Array sizes to not match." )
1038
+ if (allocated (error)) return
1039
+ call check(error, any (abs (typed_array% values - input_array) <= epsilon (1.0_dp )), &
1040
+ " Precision loss when adding array." )
1041
+ if (allocated (error)) return
1042
+ class default
1043
+ call test_failed(error, " Array is of wrong type." )
1044
+ end select
1045
+ end
1046
+
1047
+ subroutine npz_add_arr_empty_name (error )
1048
+ type (error_type), allocatable , intent (out ) :: error
1049
+
1050
+ type (t_array_wrapper), allocatable :: arrays(:)
1051
+ integer :: stat
1052
+ real (dp), allocatable :: input_array(:,:)
1053
+ character (* ), parameter :: arr_name = " "
1054
+
1055
+ allocate (input_array(10 , 4 ))
1056
+ call random_number (input_array)
1057
+ call add_array(arrays, input_array, stat, name= arr_name)
1058
+ call check(error, stat, " Empty file names are not allowed." )
1059
+ end
1060
+
1061
+ subroutine npz_add_arr_duplicate_names (error )
1062
+ type (error_type), allocatable , intent (out ) :: error
1063
+
1064
+ type (t_array_wrapper), allocatable :: arrays(:)
1065
+ integer :: stat
1066
+ real (dp), allocatable :: array_1(:,:)
1067
+ real (sp), allocatable :: array_2(:)
1068
+ character (* ), parameter :: arr_name = " arr_0.npy"
1069
+
1070
+ allocate (array_1(10 , 4 ))
1071
+ call random_number (array_1)
1072
+ call add_array(arrays, array_1, stat, name= arr_name)
1073
+ call check(error, stat, " Error adding the first array to the list of arrays." )
1074
+
1075
+ allocate (array_2(10 ))
1076
+ call random_number (array_2)
1077
+ call add_array(arrays, array_2, stat, name= arr_name)
1078
+ call check(error, stat, " Adding a second array with the same name shouldn't work." )
1079
+ end
1080
+
1015
1081
! subroutine npz_add_arr(error)
1016
1082
! type(error_type), allocatable, intent(out) :: error
1017
1083
0 commit comments