Skip to content

Commit 3beff30

Browse files
committed
Print
1 parent 5035d21 commit 3beff30

File tree

2 files changed

+25
-16
lines changed

2 files changed

+25
-16
lines changed

src/stdlib_io_np_save.fypp

Lines changed: 13 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -199,7 +199,7 @@ contains
199199
module subroutine save_arrays_to_npz(filename, arrays, iostat, iomsg, compressed)
200200
!> Name of the npz file to save to.
201201
character(len=*), intent(in) :: filename
202-
!> Array of arrays to be saved.
202+
!> Arrays to be saved.
203203
type(t_array_wrapper), intent(in) :: arrays(:)
204204
!> Optional error status of saving, zero on success.
205205
integer, intent(out), optional :: iostat
@@ -221,8 +221,19 @@ contains
221221
else
222222
is_compressed = .false.
223223
end if
224+
print *, 'in subroutine'
225+
do j = 1, size(arrays)
226+
print *, arrays(j)%array%name
227+
select type (typed_array => arrays(1)%array)
228+
class is (t_array_rdp_2)
229+
print *, typed_array%values
230+
class is (t_array_cdp_1)
231+
print *, typed_array%values
232+
class default
233+
end select
234+
end do
224235

225-
if (.not. allocated(files)) allocate(files(0))
236+
allocate(files(0))
226237
do i = 1, size(arrays)
227238
select type (typed_array => arrays(i)%array)
228239
#:for k1, t1 in KINDS_TYPES
@@ -257,19 +268,6 @@ contains
257268
end select
258269
end do
259270

260-
do j = 1, size(files)
261-
print *, as_string(files(j))
262-
end do
263-
do j = 1, size(arrays)
264-
print *, arrays(j)%array%name
265-
select type (typed_array => arrays(1)%array)
266-
class is (t_array_rdp_2)
267-
print *, typed_array%values
268-
class is (t_array_cdp_1)
269-
print *, typed_array%values
270-
class default
271-
end select
272-
end do
273271
call zip(filename, files, stat, msg, is_compressed)
274272
if (stat /= 0) then
275273
if (present(iostat)) iostat = stat

test/io/test_np.f90

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1148,7 +1148,7 @@ subroutine npz_save_two_arrays(error)
11481148
type(error_type), allocatable, intent(out) :: error
11491149

11501150
type(t_array_wrapper), allocatable :: arrays(:), arrays_reloaded(:)
1151-
integer :: stat
1151+
integer :: stat, j
11521152
real(dp), allocatable :: input_array_1(:,:)
11531153
complex(dp), allocatable :: input_array_2(:)
11541154
character(*), parameter :: array_name_1 = "array_1"
@@ -1167,6 +1167,17 @@ subroutine npz_save_two_arrays(error)
11671167
if (allocated(error)) return
11681168
call check(error, size(arrays) == 2, "Wrong array size.")
11691169
if (allocated(error)) return
1170+
print *, 'in test'
1171+
do j = 1, size(arrays)
1172+
print *, arrays(j)%array%name
1173+
select type (typed_array => arrays(1)%array)
1174+
class is (t_array_rdp_2)
1175+
print *, typed_array%values
1176+
class is (t_array_cdp_1)
1177+
print *, typed_array%values
1178+
class default
1179+
end select
1180+
end do
11701181
call save_npz(output_file, arrays, stat)
11711182
call check(error, stat, "Error saving arrays as an npz file.")
11721183
if (allocated(error)) then

0 commit comments

Comments
 (0)