Skip to content

Commit c1fb65f

Browse files
committed
Inject tmp folder so tests don't use the same one
1 parent e134c9d commit c1fb65f

File tree

4 files changed

+47
-26
lines changed

4 files changed

+47
-26
lines changed

src/stdlib_io_np.fypp

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -121,11 +121,12 @@ module stdlib_io_np
121121
!> Load multiple multidimensional arrays from a (compressed) npz file.
122122
!> ([Specification](../page/specs/stdlib_io.html#load_npz))
123123
interface load_npz
124-
module subroutine load_npz_to_arrays(filename, arrays, iostat, iomsg)
124+
module subroutine load_npz_to_arrays(filename, arrays, iostat, iomsg, tmp_dir)
125125
character(len=*), intent(in) :: filename
126126
type(t_array_wrapper), allocatable, intent(out) :: arrays(:)
127127
integer, intent(out), optional :: iostat
128128
character(len=:), allocatable, intent(out), optional :: iomsg
129+
character(len=*), intent(in), optional :: tmp_dir
129130
end
130131
end interface
131132

src/stdlib_io_np_load.fypp

Lines changed: 12 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ submodule(stdlib_io_np) stdlib_io_np_load
99
use stdlib_array
1010
use stdlib_error, only: error_stop
1111
use stdlib_filesystem, only: exists, list_dir, temp_dir
12-
use stdlib_io_zip, only: unzip, unzipped_folder, zip_contents
12+
use stdlib_io_zip, only: unzip, default_unzip_dir, zip_contents
1313
use stdlib_strings, only: to_string, starts_with
1414
use stdlib_string_type, only: string_type, as_string => char
1515
implicit none
@@ -105,33 +105,39 @@ contains
105105
!>
106106
!> Load multidimensional arrays from a compressed or uncompressed npz file.
107107
!> ([Specification](../page/specs/stdlib_io.html#load_npz))
108-
module subroutine load_npz_to_arrays(filename, arrays, iostat, iomsg)
108+
module subroutine load_npz_to_arrays(filename, arrays, iostat, iomsg, tmp_dir)
109109
character(len=*), intent(in) :: filename
110110
type(t_array_wrapper), allocatable, intent(out) :: arrays(:)
111111
integer, intent(out), optional :: iostat
112112
character(len=:), allocatable, intent(out), optional :: iomsg
113+
character(*), intent(in), optional :: tmp_dir
113114

114115
integer :: stat
115-
character(len=:), allocatable :: msg
116+
character(len=:), allocatable :: msg, unzip_dir
116117
type(string_type), allocatable :: files(:)
117118

118119
if (present(iostat)) iostat = 0
120+
if (present(tmp_dir)) then
121+
unzip_dir = tmp_dir
122+
else
123+
unzip_dir = default_unzip_dir
124+
end if
119125

120-
call unzip(filename, unzipped_folder, stat, msg)
126+
call unzip(filename, unzip_dir, stat, msg)
121127
if (stat /= 0) then
122128
if (present(iostat)) iostat = stat
123129
if (present(iomsg) .and. allocated(msg)) call move_alloc(msg, iomsg)
124130
return
125131
end if
126132

127-
call list_dir(unzipped_folder, files, stat, msg)
133+
call list_dir(unzip_dir, files, stat, msg)
128134
if (stat /= 0) then
129135
if (present(iostat)) iostat = stat
130136
if (present(iomsg) .and. allocated(msg)) call move_alloc(msg, iomsg)
131137
return
132138
end if
133139

134-
call load_unzipped_files_to_arrays(files, unzipped_folder, arrays, stat, msg)
140+
call load_unzipped_files_to_arrays(files, unzip_dir, arrays, stat, msg)
135141
if (stat /= 0) then
136142
if (present(iostat)) iostat = stat
137143
if (present(iomsg) .and. allocated(msg)) call move_alloc(msg, iomsg)

src/stdlib_io_zip.f90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -3,10 +3,10 @@ module stdlib_io_zip
33
implicit none
44
private
55

6-
public :: unzip, unzipped_folder, zip_contents
6+
public :: unzip, default_unzip_dir, zip_contents
77

8-
character(*), parameter :: unzipped_folder = temp_dir//'/unzipped_files'
9-
character(*), parameter :: zip_contents = unzipped_folder//'/zip_contents.txt'
8+
character(*), parameter :: default_unzip_dir = temp_dir//'/unzipped_files'
9+
character(*), parameter :: zip_contents = default_unzip_dir//'/zip_contents.txt'
1010

1111
contains
1212

@@ -22,16 +22,16 @@ subroutine unzip(filename, outputdir, stat, msg)
2222
if (present(outputdir)) then
2323
output_dir = outputdir
2424
else
25-
output_dir = unzipped_folder
25+
output_dir = default_unzip_dir
2626
end if
2727

2828
if (present(stat)) stat = 0
2929
run_stat = 0
3030

31-
call run('rm -rf '//unzipped_folder, run_stat)
31+
call run('rm -rf '//default_unzip_dir, run_stat)
3232
if (run_stat /= 0) then
3333
if (present(stat)) stat = run_stat
34-
if (present(msg)) msg = "Error removing folder '"//unzipped_folder//"'."
34+
if (present(msg)) msg = "Error removing folder '"//default_unzip_dir//"'."
3535
return
3636
end if
3737

@@ -44,7 +44,7 @@ subroutine unzip(filename, outputdir, stat, msg)
4444
end if
4545
end if
4646

47-
call run('unzip '//filename//' -d '//unzipped_folder, run_stat)
47+
call run('unzip '//filename//' -d '//output_dir, run_stat)
4848
if (run_stat /= 0) then
4949
if (present(stat)) stat = run_stat
5050
if (present(msg)) msg = "Error unzipping '"//filename//"'."

test/io/test_np.f90

Lines changed: 26 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module test_np
22
use stdlib_array
3+
use stdlib_filesystem, only : temp_dir
34
use stdlib_kinds, only : int8, int16, int32, int64, sp, dp
45
use stdlib_io_np, only : save_npy, load_npy, load_npz
56
use testdrive, only : new_unittest, unittest_type, error_type, check, test_failed
@@ -659,9 +660,10 @@ subroutine npz_load_nonexistent_file(error)
659660
type(t_array_wrapper), allocatable :: arrays(:)
660661

661662
integer :: stat
662-
character(len=*), parameter :: filename = "nonexistent.npz"
663+
character(*), parameter :: filename = "nonexistent.npz"
664+
character(*), parameter :: tmp = temp_dir//"nonexistent"
663665

664-
call load_npz(filename, arrays, stat)
666+
call load_npz(filename, arrays, stat, tmp_dir=tmp)
665667
call check(error, stat, "Loading a non-existent npz file should fail.")
666668
end
667669

@@ -672,9 +674,11 @@ subroutine npz_load_invalid_dir(error)
672674
type(t_array_wrapper), allocatable :: arrays(:)
673675

674676
integer :: stat
675-
character(len=*), parameter :: filename = "."
677+
character(*), parameter :: filename = "."
678+
character(*), parameter :: tmp = temp_dir//"invalid_dir"
676679

677-
call load_npz(filename, arrays, stat)
680+
681+
call load_npz(filename, arrays, stat, tmp_dir=tmp)
678682
call check(error, stat, "A file name that points towards a directory should fail.")
679683
end
680684

@@ -686,11 +690,12 @@ subroutine npz_load_empty_file(error)
686690

687691
integer :: io, stat
688692
character(*), parameter :: filename = "empty_file"
693+
character(*), parameter :: tmp = temp_dir//"empty_file"
689694

690695
open(newunit=io, file=filename)
691696
close(io)
692697

693-
call load_npz(filename, arrays, stat)
698+
call load_npz(filename, arrays, stat, tmp_dir=tmp)
694699
call check(error, stat, "Try loading an empty file as an npz file should fail.")
695700

696701
call delete_file(filename)
@@ -704,13 +709,14 @@ subroutine npz_load_empty_zip(error)
704709
integer :: io, stat
705710

706711
character(*), parameter :: filename = "empty.zip"
712+
character(*), parameter :: tmp = temp_dir//"empty_zip"
707713
character(*), parameter:: binary_data = 'PK'//char(5)//char(6)//repeat(char(0), 18)
708714

709715
open (newunit=io, file=filename, form='unformatted', access='stream')
710716
write (io) binary_data
711717
close (io)
712718

713-
call load_npz(filename, arrays, stat)
719+
call load_npz(filename, arrays, stat, tmp_dir=tmp)
714720
call check(error, stat, "Trying to load an npz file that is an empty zip file should fail.")
715721

716722
call delete_file(filename)
@@ -722,10 +728,12 @@ subroutine npz_load_arr_empty_0(error)
722728
type(t_array_wrapper), allocatable :: arrays(:)
723729
integer :: stat
724730
character(*), parameter :: filename = "empty_0.npz"
731+
character(*), parameter :: tmp = temp_dir//"empty_0"
725732
character(:), allocatable :: path
726733

734+
727735
path = get_path(filename)
728-
call load_npz(path, arrays, stat)
736+
call load_npz(path, arrays, stat, tmp_dir=tmp)
729737
call check(error, stat, "Loading an npz that contains a single empty array shouldn't fail.")
730738
if (stat /= 0) return
731739
call check(error, size(arrays) == 1, "'"//filename//"' is supposed to contain a single array.")
@@ -746,10 +754,11 @@ subroutine npz_load_arr_rand_2_3(error)
746754
type(t_array_wrapper), allocatable :: arrays(:)
747755
integer :: stat
748756
character(*), parameter :: filename = "rand_2_3.npz"
757+
character(*), parameter :: tmp = temp_dir//"rand_2_3"
749758
character(:), allocatable :: path
750759

751760
path = get_path(filename)
752-
call load_npz(path, arrays, stat)
761+
call load_npz(path, arrays, stat, tmp_dir=tmp)
753762
call check(error, stat, "Loading an npz file that contains a valid nd_array shouldn't fail.")
754763
if (stat /= 0) return
755764
call check(error, size(arrays) == 1, "'"//filename//"' is supposed to contain a single array.")
@@ -770,10 +779,12 @@ subroutine npz_load_arr_arange_10_20(error)
770779
type(t_array_wrapper), allocatable :: arrays(:)
771780
integer :: stat, i
772781
character(*), parameter :: filename = "arange_10_20.npz"
782+
character(*), parameter :: tmp = temp_dir//"arange_10_20"
783+
773784
character(:), allocatable :: path
774785

775786
path = get_path(filename)
776-
call load_npz(path, arrays, stat)
787+
call load_npz(path, arrays, stat, tmp_dir=tmp)
777788
call check(error, stat, "Loading an npz file that contains a valid nd_array shouldn't fail.")
778789
if (stat /= 0) return
779790
call check(error, size(arrays) == 1, "'"//filename//"' is supposed to contain a single array.")
@@ -801,10 +812,11 @@ subroutine npz_load_arr_cmplx(error)
801812
type(t_array_wrapper), allocatable :: arrays(:)
802813
integer :: stat
803814
character(*), parameter :: filename = "cmplx_arr.npz"
815+
character(*), parameter :: tmp = temp_dir//"cmplx_arr"
804816
character(:), allocatable :: path
805817

806818
path = get_path(filename)
807-
call load_npz(path, arrays, stat)
819+
call load_npz(path, arrays, stat, tmp_dir=tmp)
808820
call check(error, stat, "Loading an npz file that contains a valid nd_array shouldn't fail.")
809821
if (stat /= 0) return
810822
call check(error, size(arrays) == 1, "'"//filename//"' is supposed to contain a single array.")
@@ -832,10 +844,11 @@ subroutine npz_load_two_arr_iint64_rdp(error)
832844
type(t_array_wrapper), allocatable :: arrays(:)
833845
integer :: stat
834846
character(*), parameter :: filename = "two_arr_iint64_rdp.npz"
847+
character(*), parameter :: tmp = temp_dir//"two_arr_iint64_rdp"
835848
character(:), allocatable :: path
836849

837850
path = get_path(filename)
838-
call load_npz(path, arrays, stat)
851+
call load_npz(path, arrays, stat, tmp_dir=tmp)
839852
call check(error, stat, "Loading an npz file that contains valid nd_arrays shouldn't fail.")
840853
if (stat /= 0) return
841854
call check(error, size(arrays) == 2, "'"//filename//"' is supposed to contain two arrays.")
@@ -878,10 +891,11 @@ subroutine npz_load_two_arr_iint64_rdp_comp(error)
878891
type(t_array_wrapper), allocatable :: arrays(:)
879892
integer :: stat, i
880893
character(*), parameter :: filename = "two_arr_iint64_rdp_comp.npz"
894+
character(*), parameter :: tmp = temp_dir//"two_arr_iint64_rdp_comp"
881895
character(:), allocatable :: path
882896

883897
path = get_path(filename)
884-
call load_npz(path, arrays, stat)
898+
call load_npz(path, arrays, stat, tmp_dir=tmp)
885899
call check(error, stat, "Loading a compressed npz file that contains valid nd_arrays shouldn't fail.")
886900
if (stat /= 0) return
887901
call check(error, size(arrays) == 2, "'"//filename//"' is supposed to contain two arrays.")

0 commit comments

Comments
 (0)