summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--fortran/test/tH5Z.F906
-rw-r--r--hl/fortran/test/tstimage.F9021
2 files changed, 21 insertions, 6 deletions
diff --git a/fortran/test/tH5Z.F90 b/fortran/test/tH5Z.F90
index 799067a..7f81383 100644
--- a/fortran/test/tH5Z.F90
+++ b/fortran/test/tH5Z.F90
@@ -192,8 +192,8 @@ CONTAINS
INTEGER(HSIZE_T), DIMENSION(2) :: chunk_dims = (/NN, MM/)
INTEGER :: rank = 2 ! Dataset rank
- INTEGER, DIMENSION(N,M) :: dset_data ! Data buffers
- INTEGER, DIMENSION(:,:), ALLOCATABLE :: data_out ! Data buffers
+ INTEGER, DIMENSION(:,:), ALLOCATABLE :: dset_data ! Data buffers
+ INTEGER, DIMENSION(:,:), ALLOCATABLE :: data_out ! Data buffers
INTEGER :: error ! Error flag
INTEGER :: num_errors = 0 ! Number of data errors
@@ -252,6 +252,7 @@ CONTAINS
!
! Initialize the dset_data array.
!
+ ALLOCATE(dset_data(1:N,1:M))
do i = 1, N
do j = 1, M
dset_data(i,j) = (i-1)*6 + j;
@@ -387,6 +388,7 @@ CONTAINS
100 IF (num_errors .GT. 0) THEN
total_error=total_error + 1
END IF
+ DEALLOCATE(dset_data)
DEALLOCATE(data_out)
!
diff --git a/hl/fortran/test/tstimage.F90 b/hl/fortran/test/tstimage.F90
index 8e7c5e0..4749f92 100644
--- a/hl/fortran/test/tstimage.F90
+++ b/hl/fortran/test/tstimage.F90
@@ -64,10 +64,10 @@ integer(hid_t) :: file_id ! file identifier
integer(hsize_t), parameter :: width = 500 ! width of image
integer(hsize_t), parameter :: height = 270 ! height of image
integer, parameter :: pal_entries = 9 ! palette number of entries
-integer, dimension(width*height) :: buf1 ! data buffer
-integer, dimension(width*height) :: bufr1 ! data buffer
-integer, dimension(width*height*3) :: buf2 ! data buffer
-integer, dimension(width*height*3) :: bufr2 ! data buffer
+integer, dimension(:), allocatable :: buf1 ! data buffer
+integer, dimension(:), allocatable :: bufr1 ! data buffer
+integer, dimension(:), allocatable :: buf2 ! data buffer
+integer, dimension(:), allocatable :: bufr2 ! data buffer
integer(hsize_t) :: widthr ! width of image
integer(hsize_t) :: heightr ! height of image
integer(hsize_t) :: planesr ! color planes
@@ -99,6 +99,12 @@ integer, dimension(pal_entries*3) :: pal_data_in = (/&
252,168,0,& ! orange
252,0,0/) ! red
+! allocate arrays
+!
+allocate(buf1(width * height))
+allocate(bufr1(width * height))
+allocate(buf2(width * height * 3))
+allocate(bufr2(width * height * 3))
! create an 8bit image of 9 values divided evenly by the array
!
@@ -336,6 +342,13 @@ call h5fclose_f(file_id, errcode)
!
call h5close_f(errcode)
+! deallocate arrays
+!
+deallocate(buf1)
+deallocate(bufr1)
+deallocate(buf2)
+deallocate(bufr2)
+
!
! end function.
!