summaryrefslogtreecommitdiffstats
path: root/fortran/test/tH5Z.f90
diff options
context:
space:
mode:
authorQuincey Koziol <koziol@hdfgroup.org>2004-01-02 05:05:26 (GMT)
committerQuincey Koziol <koziol@hdfgroup.org>2004-01-02 05:05:26 (GMT)
commit2a14f37bda3d3d5a0adcbd21affdb337024a9fa3 (patch)
tree9a378282cace63f3cb0f544f2aeb3530f5f56bc8 /fortran/test/tH5Z.f90
parenta550ccd1d2832842d89df32e7c30aac5fc8bfde3 (diff)
downloadhdf5-2a14f37bda3d3d5a0adcbd21affdb337024a9fa3.zip
hdf5-2a14f37bda3d3d5a0adcbd21affdb337024a9fa3.tar.gz
hdf5-2a14f37bda3d3d5a0adcbd21affdb337024a9fa3.tar.bz2
[svn-r8012] Purpose:
Bug fix Description: Fix szip FORTRAN tests.. Solution: Increase the chunk size to be bigger than the szip 'pixels per block'. Also add in code that checks for a maximum number of errors and doesn't keep reporting that thousands of errors have occurred. Platforms tested: Linux 2.4 (verbena) w/szip & FORTRAN Not tested w/h5committest since this combination isn't covered by it.
Diffstat (limited to 'fortran/test/tH5Z.f90')
-rw-r--r--fortran/test/tH5Z.f9015
1 files changed, 12 insertions, 3 deletions
diff --git a/fortran/test/tH5Z.f90 b/fortran/test/tH5Z.f90
index f5cc83e..7425f14 100644
--- a/fortran/test/tH5Z.f90
+++ b/fortran/test/tH5Z.f90
@@ -108,9 +108,9 @@
CHARACTER(LEN=80) :: fix_filename
CHARACTER(LEN=4), PARAMETER :: dsetname = "dset" ! Dataset name
INTEGER, PARAMETER :: N = 1024
- INTEGER, PARAMETER :: NN = 16
+ INTEGER, PARAMETER :: NN = 64
INTEGER, PARAMETER :: M = 512
- INTEGER, PARAMETER :: MM = 8
+ INTEGER, PARAMETER :: MM = 32
INTEGER(HID_T) :: file_id ! File identifier
INTEGER(HID_T) :: dset_id ! Dataset identifier
@@ -124,6 +124,7 @@
INTEGER, DIMENSION(N,M) :: dset_data, data_out ! Data buffers
INTEGER :: error ! Error flag
+ INTEGER :: num_errors = 0 ! Number of data errors
INTEGER :: i, j !general purpose integers
INTEGER(HSIZE_T), DIMENSION(7) :: data_dims_b
@@ -265,10 +266,18 @@
do j = 1, M
IF (data_out(i,j) .NE. dset_data(i, j)) THEN
write(*, *) "dataset test error occured"
- write(*,*) "data read is not the same as the data writen"
+ write(*,*) "data read is not the same as the data written"
+ num_errors = num_errors + 1
+ IF (num_errors .GE. 512) THEN
+ write(*, *) "maximum data errors reached"
+ goto 100
+ END IF
END IF
end do
end do
+100 IF (num_errors .GT. 0) THEN
+ total_error=total_error + 1
+ END IF
!
! End access to the dataset and release resources used by it.