summaryrefslogtreecommitdiffstats
path: root/fortran/testpar/hyper.f90
diff options
context:
space:
mode:
authorPedro Vicente Nunes <pvn@hdfgroup.org>2005-05-03 19:27:05 (GMT)
committerPedro Vicente Nunes <pvn@hdfgroup.org>2005-05-03 19:27:05 (GMT)
commit9d3222d00fd09b0a69030c7f3746eacaf620369c (patch)
treeaef5f4b0b8de84b7f2667039b525c5eb5bd2b18e /fortran/testpar/hyper.f90
parentde185388e9f0119bbd494e43ef1b0c8e5aa865a9 (diff)
downloadhdf5-9d3222d00fd09b0a69030c7f3746eacaf620369c.zip
hdf5-9d3222d00fd09b0a69030c7f3746eacaf620369c.tar.gz
hdf5-9d3222d00fd09b0a69030c7f3746eacaf620369c.tar.bz2
[svn-r10721] Purpose:
added more checks to failure conditions Description: Solution: Platforms tested: linux (PGI, intel) AIX Misc. update:
Diffstat (limited to 'fortran/testpar/hyper.f90')
-rw-r--r--fortran/testpar/hyper.f90119
1 files changed, 107 insertions, 12 deletions
diff --git a/fortran/testpar/hyper.f90 b/fortran/testpar/hyper.f90
index 79ede6a..f055d3e 100644
--- a/fortran/testpar/hyper.f90
+++ b/fortran/testpar/hyper.f90
@@ -43,12 +43,12 @@ integer(hid_t) :: file_id ! file identifier
integer(hid_t) :: dset_id ! dataset identifier
integer(hid_t) :: fspace_id ! file space identifier
integer(hid_t) :: mspace_id ! memory space identifier
+integer(hid_t) :: driver_id ! low-level file driver identifier
integer :: istart ! start position in array
integer :: iend ! end position in array
integer :: icount ! number of elements in array
integer :: i
-
call mpi_comm_rank( MPI_COMM_WORLD, mpi_rank, mpierror )
call mpi_comm_size( MPI_COMM_WORLD, mpi_size, mpierror )
@@ -60,8 +60,17 @@ call mpi_comm_size( MPI_COMM_WORLD, mpi_size, mpierror )
! p2 = 9,10,11,12
!//////////////////////////////////////////////////////////
-allocate(wbuf(0:lenght-1))
-allocate(rbuf(0:lenght-1))
+allocate(wbuf(0:lenght-1),stat=hdferror)
+if (hdferror /= 0) then
+ write(*,*) 'allocate error'
+ return
+endif
+
+allocate(rbuf(0:lenght-1),stat=hdferror)
+if (hdferror /= 0) then
+ write(*,*) 'allocate error'
+ return
+endif
icount = lenght/mpi_size ! divide the array by the number of processes
istart = mpi_rank*icount ! start position
@@ -78,25 +87,55 @@ enddo
dims(1) = lenght
cdims(1) = lenght/mpi_size ! define chunks as the number of processes
+!//////////////////////////////////////////////////////////
+! setup file access property list with parallel I/O access
+!//////////////////////////////////////////////////////////
+
call h5pcreate_f(H5P_FILE_ACCESS_F, fapl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5pset_fapl_mpio_f(fapl_id, MPI_COMM_WORLD, MPI_INFO_NULL, hdferror)
+call check("h5pset_fapl_mpio_f", hdferror, nerrors)
+
+call h5pget_driver_f(fapl_id, driver_id, hdferror)
+call check("h5pget_driver_f", hdferror, nerrors)
+
+if( driver_id /= H5FD_MPIO_F) then
+ write(*,*) "Wrong driver information returned"
+ nerrors = nerrors + 1
+endif
+
+!//////////////////////////////////////////////////////////
+! create the file collectively
+!//////////////////////////////////////////////////////////
+
call h5fcreate_f("parf.h5", H5F_ACC_TRUNC_F, file_id, hdferror, access_prp = fapl_id)
+call check("h5fcreate_f", hdferror, nerrors)
call h5screate_simple_f(1, dims, fspace_id, hdferror)
+call check("h5screate_simple_f", hdferror, nerrors)
+
call h5screate_simple_f(1, dims, mspace_id, hdferror)
+call check("h5screate_simple_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! modify dataset creation properties to enable chunking
!//////////////////////////////////////////////////////////
call h5pcreate_f(H5P_DATASET_CREATE_F, dcpl_id, hdferror)
-if (do_chunk) call h5pset_chunk_f(dcpl_id, 1, cdims, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
+if (do_chunk) then
+ call h5pset_chunk_f(dcpl_id, 1, cdims, hdferror)
+ call check("h5pset_chunk_f", hdferror, nerrors)
+endif
!//////////////////////////////////////////////////////////
! create the dataset
!//////////////////////////////////////////////////////////
call h5dcreate_f(file_id, "dset", H5T_NATIVE_INTEGER, fspace_id, dset_id, hdferror, dcpl_id)
+call check("h5dcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! define hyperslab
@@ -110,81 +149,137 @@ start(1) = istart
!//////////////////////////////////////////////////////////
call h5sselect_hyperslab_f(mspace_id, H5S_SELECT_SET_F, start, counti, hdferror)
+call check("h5sselect_hyperslab_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! select hyperslab in the file
!//////////////////////////////////////////////////////////
call h5sselect_hyperslab_f(fspace_id, H5S_SELECT_SET_F, start, counti, hdferror)
+call check("h5sselect_hyperslab_f", hdferror, nerrors)
+
!//////////////////////////////////////////////////////////
! create a property list for collective dataset write
!//////////////////////////////////////////////////////////
-call h5pcreate_f(H5P_DATASET_XFER_F, dxpl_id, hdferror)
-if (do_collective) call h5pset_dxpl_mpio_f(dxpl_id, H5FD_MPIO_COLLECTIVE_F, hdferror)
+call h5pcreate_f(H5P_DATASET_XFER_F, dxpl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
+if (do_collective) then
+ call h5pset_dxpl_mpio_f(dxpl_id, H5FD_MPIO_COLLECTIVE_F, hdferror)
+ call check("h5pset_dxpl_mpio_f", hdferror, nerrors)
+endif
!//////////////////////////////////////////////////////////
! write dataset
!//////////////////////////////////////////////////////////
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, wbuf, dims, hdferror, file_space_id = fspace_id, mem_space_id = mspace_id, xfer_prp = dxpl_id)
+call check("h5dwrite_f", hdferror, nerrors)
+
!//////////////////////////////////////////////////////////
! close HDF5 I/O
!//////////////////////////////////////////////////////////
+call h5pclose_f(fapl_id, hdferror)
+call check("h5pclose_f", hdferror, nerrors)
+
+call h5pclose_f(dcpl_id, hdferror)
+call check("h5pclose_f", hdferror, nerrors)
+
+call h5pclose_f(dxpl_id, hdferror)
+call check("h5pclose_f", hdferror, nerrors)
+
+call h5sclose_f(mspace_id, hdferror)
+call check("h5sclose_f", hdferror, nerrors)
+
call h5sclose_f(fspace_id, hdferror)
+call check("h5sclose_f", hdferror, nerrors)
+
call h5dclose_f(dset_id, hdferror)
-call h5pclose_f(fapl_id, hdferror)
+call check("h5dclose_f", hdferror, nerrors)
+
call h5fclose_f(file_id, hdferror)
+call check("h5fclose_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! reopen file with read access
!//////////////////////////////////////////////////////////
call h5pcreate_f(H5P_FILE_ACCESS_F, fapl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5pset_fapl_mpio_f(fapl_id, MPI_COMM_WORLD, MPI_INFO_NULL, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5fopen_f("parf.h5", H5F_ACC_RDWR_F, file_id, hdferror, access_prp = fapl_id)
+call check("h5pcreate_f", hdferror, nerrors)
call h5screate_simple_f(1, dims, fspace_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5screate_simple_f(1, dims, mspace_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5dopen_f(file_id, "dset", dset_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! select hyperslab in memory
!//////////////////////////////////////////////////////////
call h5sselect_hyperslab_f(mspace_id, H5S_SELECT_SET_F, start, counti, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! select hyperslab in the file
!//////////////////////////////////////////////////////////
call h5sselect_hyperslab_f(fspace_id, H5S_SELECT_SET_F, start, counti, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
-! create a property list for collective dataset write
+! create a property list for collective dataset read
!//////////////////////////////////////////////////////////
-call h5pcreate_f(H5P_DATASET_XFER_F, dxpl_id, hdferror)
-if (do_collective) call h5pset_dxpl_mpio_f(dxpl_id, H5FD_MPIO_COLLECTIVE_F, hdferror)
+call h5pcreate_f(H5P_DATASET_XFER_F, dxpl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
+if (do_collective) then
+ call h5pset_dxpl_mpio_f(dxpl_id, H5FD_MPIO_COLLECTIVE_F, hdferror)
+ call check("h5pcreate_f", hdferror, nerrors)
+endif
!//////////////////////////////////////////////////////////
! read dataset
!//////////////////////////////////////////////////////////
call h5dread_f(dset_id, H5T_NATIVE_INTEGER, rbuf, dims, hdferror, file_space_id = fspace_id, mem_space_id = mspace_id, xfer_prp = dxpl_id)
+call check("h5pcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! close HDF5 I/O
!//////////////////////////////////////////////////////////
+call h5pclose_f(fapl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
+call h5pclose_f(dxpl_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5sclose_f(fspace_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
+call h5sclose_f(mspace_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+
call h5dclose_f(dset_id, hdferror)
-call h5pclose_f(fapl_id, hdferror)
-call h5fclose_f(file_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
+call h5fclose_f(file_id, hdferror)
+call check("h5pcreate_f", hdferror, nerrors)
!//////////////////////////////////////////////////////////
! compare read and write data. each process compares a subset of the array