Skip to content

Commit 78feba9

Browse files
committed
Fix paths, print expected values
1 parent f3aba87 commit 78feba9

File tree

1 file changed

+19
-14
lines changed

1 file changed

+19
-14
lines changed

test/io/test_np.f90

Lines changed: 19 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module test_np
33
use stdlib_filesystem, only : temp_dir, exists
44
use stdlib_kinds, only : int8, int16, int32, int64, sp, dp
55
use stdlib_io_np, only : save_npy, load_npy, load_npz, add_array, save_npz
6+
use stdlib_string_type, only : char
67
use testdrive, only : new_unittest, unittest_type, error_type, check, test_failed
78
implicit none
89
private
@@ -669,7 +670,7 @@ subroutine npz_load_nonexistent_file(error)
669670

670671
integer :: stat
671672
character(*), parameter :: filename = "nonexistent.npz"
672-
character(*), parameter :: tmp = temp_dir//"nonexistent"
673+
character(*), parameter :: tmp = temp_dir//"/nonexistent"
673674

674675
call load_npz(filename, arrays, stat, tmp_dir=tmp)
675676
call check(error, stat, "Loading a non-existent npz file should fail.")
@@ -683,7 +684,7 @@ subroutine npz_load_invalid_dir(error)
683684

684685
integer :: stat
685686
character(*), parameter :: filename = "."
686-
character(*), parameter :: tmp = temp_dir//"invalid_dir"
687+
character(*), parameter :: tmp = temp_dir//"/invalid_dir"
687688

688689

689690
call load_npz(filename, arrays, stat, tmp_dir=tmp)
@@ -698,7 +699,7 @@ subroutine npz_load_empty_file(error)
698699

699700
integer :: io, stat
700701
character(*), parameter :: filename = "empty_file"
701-
character(*), parameter :: tmp = temp_dir//"empty_file"
702+
character(*), parameter :: tmp = temp_dir//"/empty_file"
702703

703704
open(newunit=io, file=filename)
704705
close(io)
@@ -717,7 +718,7 @@ subroutine npz_load_empty_zip(error)
717718
integer :: io, stat
718719

719720
character(*), parameter :: filename = "empty.zip"
720-
character(*), parameter :: tmp = temp_dir//"empty_zip"
721+
character(*), parameter :: tmp = temp_dir//"/empty_zip"
721722
character(*), parameter:: binary_data = 'PK'//char(5)//char(6)//repeat(char(0), 18)
722723

723724
open (newunit=io, file=filename, form='unformatted', access='stream')
@@ -736,7 +737,7 @@ subroutine npz_load_arr_empty_0(error)
736737
type(t_array_wrapper), allocatable :: arrays(:)
737738
integer :: stat
738739
character(*), parameter :: filename = "empty_0.npz"
739-
character(*), parameter :: tmp = temp_dir//"empty_0"
740+
character(*), parameter :: tmp = temp_dir//"/empty_0"
740741
character(:), allocatable :: path
741742

742743

@@ -762,7 +763,7 @@ subroutine npz_load_arr_rand_2_3(error)
762763
type(t_array_wrapper), allocatable :: arrays(:)
763764
integer :: stat
764765
character(*), parameter :: filename = "rand_2_3.npz"
765-
character(*), parameter :: tmp = temp_dir//"rand_2_3"
766+
character(*), parameter :: tmp = temp_dir//"/rand_2_3"
766767
character(:), allocatable :: path
767768

768769
path = get_path(filename)
@@ -787,7 +788,7 @@ subroutine npz_load_arr_arange_10_20(error)
787788
type(t_array_wrapper), allocatable :: arrays(:)
788789
integer :: stat, i
789790
character(*), parameter :: filename = "arange_10_20.npz"
790-
character(*), parameter :: tmp = temp_dir//"arange_10_20"
791+
character(*), parameter :: tmp = temp_dir//"/arange_10_20"
791792

792793
character(:), allocatable :: path
793794

@@ -820,7 +821,7 @@ subroutine npz_load_arr_cmplx(error)
820821
type(t_array_wrapper), allocatable :: arrays(:)
821822
integer :: stat
822823
character(*), parameter :: filename = "cmplx_arr.npz"
823-
character(*), parameter :: tmp = temp_dir//"cmplx_arr"
824+
character(*), parameter :: tmp = temp_dir//"/cmplx_arr"
824825
character(:), allocatable :: path
825826

826827
path = get_path(filename)
@@ -852,7 +853,7 @@ subroutine npz_load_two_arr_iint64_rdp(error)
852853
type(t_array_wrapper), allocatable :: arrays(:)
853854
integer :: stat
854855
character(*), parameter :: filename = "two_arr_iint64_rdp.npz"
855-
character(*), parameter :: tmp = temp_dir//"two_arr_iint64_rdp"
856+
character(*), parameter :: tmp = temp_dir//"/two_arr_iint64_rdp"
856857
character(:), allocatable :: path
857858

858859
path = get_path(filename)
@@ -899,7 +900,7 @@ subroutine npz_load_two_arr_iint64_rdp_comp(error)
899900
type(t_array_wrapper), allocatable :: arrays(:)
900901
integer :: stat
901902
character(*), parameter :: filename = "two_arr_iint64_rdp_comp.npz"
902-
character(*), parameter :: tmp = temp_dir//"two_arr_iint64_rdp_comp"
903+
character(*), parameter :: tmp = temp_dir//"/two_arr_iint64_rdp_comp"
903904
character(:), allocatable :: path
904905

905906
path = get_path(filename)
@@ -1099,7 +1100,7 @@ subroutine npz_save_one_array(error)
10991100
integer :: stat
11001101
real(dp), allocatable :: input_array(:,:)
11011102
character(*), parameter :: output_file = "one_array.npz"
1102-
character(*), parameter :: tmp = temp_dir//"one_array"
1103+
character(*), parameter :: tmp = temp_dir//"/one_array"
11031104

11041105
allocate(input_array(10, 4))
11051106
call random_number(input_array)
@@ -1154,7 +1155,7 @@ subroutine npz_save_two_arrays(error)
11541155
character(*), parameter :: array_name_1 = "array_1"
11551156
character(*), parameter :: array_name_2 = "array_2"
11561157
character(*), parameter :: output_file = "two_arrays.npz"
1157-
character(*), parameter :: tmp = temp_dir//"two_arrays"
1158+
character(*), parameter :: tmp = temp_dir//"/two_arrays"
11581159

11591160
allocate(input_array_1(5, 6))
11601161
call random_number(input_array_1)
@@ -1189,7 +1190,9 @@ subroutine npz_save_two_arrays(error)
11891190

11901191
select type (typed_array => arrays_reloaded(1)%array)
11911192
class is (t_array_rdp_2)
1192-
call check(error, size(typed_array%values), size(input_array_1), "First array does not match in size.")
1193+
call check(error, size(typed_array%values), size(input_array_1), &
1194+
"First array does not match in size: "//char(size(input_array_1))//" expected, " &
1195+
//char(size(typed_array%values))//" obtained.")
11931196
if (allocated(error)) then
11941197
call delete_file(output_file); return
11951198
end if
@@ -1204,7 +1207,9 @@ subroutine npz_save_two_arrays(error)
12041207

12051208
select type (typed_array => arrays_reloaded(2)%array)
12061209
class is (t_array_cdp_1)
1207-
call check(error, size(typed_array%values), size(input_array_2), "Second array does not match in size.")
1210+
call check(error, size(typed_array%values), size(input_array_2), &
1211+
"Second array does not match in size: "//char(size(input_array_2))//" expected, " &
1212+
//char(size(typed_array%values))//" obtained.")
12081213
if (allocated(error)) then
12091214
call delete_file(output_file); return
12101215
end if

0 commit comments

Comments
 (0)