Skip to content

Commit c4072cb

Browse files
committed
Add option to either compress zip file or not
1 parent f8e0e0e commit c4072cb

File tree

5 files changed

+65
-28
lines changed

5 files changed

+65
-28
lines changed

src/stdlib_io_np.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ module stdlib_io_np
135135
!> Save multidimensional arrays to a compressed or an uncompressed npz file.
136136
!> ([Specification](../page/specs/stdlib_io.html#save_npz))
137137
interface save_npz
138-
module subroutine save_npz_from_arrays(filename, arrays, iostat, iomsg, compressed)
138+
module subroutine save_arrays_to_npz(filename, arrays, iostat, iomsg, compressed)
139139
character(len=*), intent(in) :: filename
140140
type(t_array_wrapper), intent(in) :: arrays(:)
141141
integer, intent(out), optional :: iostat

src/stdlib_io_np_save.fypp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -196,7 +196,7 @@ contains
196196
!>
197197
!> Save multidimensional arrays to a compressed or an uncompressed npz file.
198198
!> ([Specification](../page/specs/stdlib_io.html#save_npz))
199-
module subroutine save_npz_from_arrays(filename, arrays, iostat, iomsg, compressed)
199+
module subroutine save_arrays_to_npz(filename, arrays, iostat, iomsg, compressed)
200200
character(len=*), intent(in) :: filename
201201
type(t_array_wrapper), intent(in) :: arrays(:)
202202
integer, intent(out), optional :: iostat
@@ -252,7 +252,7 @@ contains
252252
end select
253253
end do
254254

255-
call zip(filename, files, stat, msg)
255+
call zip(filename, files, stat, msg, is_compressed)
256256
if (stat /= 0) then
257257
if (present(iostat)) iostat = stat
258258
if (present(iomsg)) iomsg = msg

src/stdlib_io_zip.f90

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -12,18 +12,26 @@ module stdlib_io_zip
1212

1313
contains
1414

15-
subroutine zip(output_file, files, stat, msg)
15+
subroutine zip(output_file, files, stat, msg, compressed)
1616
character(*), intent(in) :: output_file
1717
type(string_type), intent(in) :: files(:)
1818
integer, intent(out), optional :: stat
1919
character(len=:), allocatable, intent(out), optional :: msg
20+
logical, intent(in), optional :: compressed
2021

2122
integer :: run_stat, i
22-
character(:), allocatable :: files_str
23+
character(:), allocatable :: files_str, cmd
24+
logical :: is_compressed
2325

2426
if (present(stat)) stat = 0
2527
run_stat = 0
2628

29+
if (present(compressed)) then
30+
is_compressed = compressed
31+
else
32+
is_compressed = .true.
33+
end if
34+
2735
if (trim(output_file) == '') then
2836
if (present(stat)) stat = 1
2937
if (present(msg)) msg = "Output file is empty."
@@ -35,7 +43,10 @@ subroutine zip(output_file, files, stat, msg)
3543
files_str = files_str//' '//char(files(i))
3644
end do
3745

38-
call run('zip '//output_file//files_str, run_stat)
46+
cmd = 'zip '//''//output_file//' '//files_str
47+
if (.not. is_compressed) cmd = cmd//' -0'
48+
49+
call run(cmd, run_stat)
3950
if (run_stat /= 0) then
4051
if (present(stat)) stat = run_stat
4152
if (present(msg)) msg = "Error creating zip file '"//output_file//"'."

test/io/test_np.f90

Lines changed: 0 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1078,25 +1078,6 @@ subroutine npz_add_arr_duplicate_names(error)
10781078
call check(error, stat, "Adding a second array with the same name shouldn't work.")
10791079
end
10801080

1081-
! subroutine npz_add_arr(error)
1082-
! type(error_type), allocatable, intent(out) :: error
1083-
1084-
! type(t_array_wrapper), allocatable :: arrays(:)
1085-
! integer :: stat
1086-
! character(*), parameter :: filename = "npz_add_arr.npz"
1087-
! real(dp), allocatable :: input_array(:,:)
1088-
1089-
! allocate(input_array(10, 4))
1090-
! call random_number(input_array)
1091-
! call add_array(arrays, input_array, stat)
1092-
! call check(error, stat, "Error adding an array to the list of arrays.")
1093-
! if (allocated(error)) return
1094-
! call check(error, size(arrays) == 1, "Array was not added to the list of arrays.")
1095-
! if (allocated(error)) return
1096-
! call check(error, arrays(1)%array%name == "arr_0.npy", "Wrong array name.")
1097-
! if (allocated(error)) return
1098-
! end
1099-
11001081
subroutine npz_save_empty_array_input(error)
11011082
type(error_type), allocatable, intent(out) :: error
11021083

test/io/test_zip.f90

Lines changed: 48 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
module test_zip
2+
use stdlib_filesystem, only: exists
23
use stdlib_io_zip
3-
use stdlib_string_type, only : string_type, char
4-
use testdrive, only : new_unittest, unittest_type, error_type, check, test_failed
4+
use stdlib_string_type, only: string_type, char
5+
use testdrive, only: new_unittest, unittest_type, error_type, check, test_failed
56
implicit none
67
private
78

@@ -28,7 +29,8 @@ subroutine collect_zip(testsuite)
2829
new_unittest("zip_invalid_file", zip_invalid_file, should_fail=.true.), &
2930
new_unittest("zip_empty_file", zip_empty_file), &
3031
new_unittest("zip_invalid_output_file", zip_invalid_output_file, should_fail=.true.), &
31-
new_unittest("zip_two_files", zip_two_files) &
32+
new_unittest("zip_two_files", zip_two_files), &
33+
new_unittest("zip_without_comp", zip_without_comp) &
3234
]
3335
end
3436

@@ -199,6 +201,13 @@ subroutine zip_empty_file(error)
199201

200202
call zip(output_file, files, stat)
201203
call check(error, stat, "Compressing a valid empty file should not fail.")
204+
if (allocated(error)) then
205+
call delete_file(input_file)
206+
call delete_file(output_file)
207+
return
208+
end if
209+
210+
call check(error, exists(output_file), "The output file should exist.")
202211

203212
call delete_file(input_file)
204213
call delete_file(output_file)
@@ -241,12 +250,48 @@ subroutine zip_two_files(error)
241250

242251
call zip(output_file, files, stat)
243252
call check(error, stat, "Compressing two valid files should not fail.")
253+
if (allocated(error)) then
254+
call delete_file(input_file_1)
255+
call delete_file(input_file_2)
256+
call delete_file(output_file)
257+
return
258+
end if
259+
260+
call check(error, exists(output_file), "The output file should exist.")
244261

245262
call delete_file(input_file_1)
246263
call delete_file(input_file_2)
247264
call delete_file(output_file)
248265
end
249266

267+
268+
subroutine zip_without_comp(error)
269+
type(error_type), allocatable, intent(out) :: error
270+
271+
integer :: stat, unit
272+
character(*), parameter :: output_file = "temp.zip"
273+
character(*), parameter :: input_file = "abc.txt"
274+
type(string_type), allocatable :: files(:)
275+
276+
files = [string_type(input_file)]
277+
278+
open(newunit= unit, file=input_file)
279+
close(unit)
280+
281+
call zip(output_file, files, stat, compressed=.false.)
282+
call check(error, stat, "Zipping a valid file without compression shouldn't fail.")
283+
if (allocated(error)) then
284+
call delete_file(input_file)
285+
call delete_file(output_file)
286+
return
287+
end if
288+
289+
call check(error, exists(output_file), "The output file should exist.")
290+
291+
call delete_file(input_file)
292+
call delete_file(output_file)
293+
end
294+
250295
!> Makes sure that we find the file when running both `ctest` and `fpm test`.
251296
function get_path(file) result(path)
252297
character(*), intent(in) :: file

0 commit comments

Comments
 (0)