2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @author Vitesh Shah, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Yi-Chin Yang, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Jennifer Nastola, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-15 11:58:34 +05:30
|
|
|
module HDF5_utilities
|
2018-11-27 23:20:51 +05:30
|
|
|
use prec
|
|
|
|
use IO
|
|
|
|
use HDF5
|
2018-08-05 10:11:35 +05:30
|
|
|
#ifdef PETSc
|
2018-11-27 23:20:51 +05:30
|
|
|
use PETSC
|
2018-08-05 10:11:35 +05:30
|
|
|
#endif
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
implicit none
|
2018-12-12 12:15:20 +05:30
|
|
|
public
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(pInt), parameter, private :: &
|
|
|
|
HDF5_ERR_TYPE = 4_pInt !< kind of the integer return in the HDF5 library
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief reads pInt or pReal data of defined shape from file
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 17:27:29 +05:30
|
|
|
interface HDF5_read
|
2018-11-27 23:20:51 +05:30
|
|
|
module procedure HDF5_read_pReal1
|
|
|
|
module procedure HDF5_read_pReal2
|
|
|
|
module procedure HDF5_read_pReal3
|
|
|
|
module procedure HDF5_read_pReal4
|
|
|
|
module procedure HDF5_read_pReal5
|
|
|
|
module procedure HDF5_read_pReal6
|
|
|
|
module procedure HDF5_read_pReal7
|
|
|
|
|
|
|
|
module procedure HDF5_read_pInt1
|
|
|
|
module procedure HDF5_read_pInt2
|
|
|
|
module procedure HDF5_read_pInt3
|
|
|
|
module procedure HDF5_read_pInt4
|
|
|
|
module procedure HDF5_read_pInt5
|
|
|
|
module procedure HDF5_read_pInt6
|
2018-12-17 20:45:16 +05:30
|
|
|
module procedure HDF5_read_pInt7
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-09 17:27:29 +05:30
|
|
|
end interface HDF5_read
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief writes pInt or pReal data of defined shape to file
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 17:27:29 +05:30
|
|
|
interface HDF5_write
|
2018-10-10 21:24:55 +05:30
|
|
|
module procedure HDF5_write_pReal1
|
|
|
|
module procedure HDF5_write_pReal2
|
|
|
|
module procedure HDF5_write_pReal3
|
|
|
|
module procedure HDF5_write_pReal4
|
|
|
|
module procedure HDF5_write_pReal5
|
|
|
|
module procedure HDF5_write_pReal6
|
|
|
|
module procedure HDF5_write_pReal7
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
module procedure HDF5_write_pInt1
|
|
|
|
module procedure HDF5_write_pInt2
|
|
|
|
module procedure HDF5_write_pInt3
|
|
|
|
module procedure HDF5_write_pInt4
|
|
|
|
module procedure HDF5_write_pInt5
|
|
|
|
module procedure HDF5_write_pInt6
|
2018-12-17 20:45:16 +05:30
|
|
|
module procedure HDF5_write_pInt7
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-09 17:27:29 +05:30
|
|
|
end interface HDF5_write
|
2018-12-17 20:45:16 +05:30
|
|
|
|
2018-12-15 21:51:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief attached attributes of type char,pInt or pReal to a file/dataset/group
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
interface HDF5_addAttribute
|
|
|
|
module procedure HDF5_addAttribute_str
|
|
|
|
module procedure HDF5_addAttribute_pInt
|
|
|
|
module procedure HDF5_addAttribute_pReal
|
|
|
|
end interface HDF5_addAttribute
|
|
|
|
|
|
|
|
|
2018-12-15 21:51:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-08-03 12:23:37 +05:30
|
|
|
public :: &
|
2018-11-15 11:37:59 +05:30
|
|
|
HDF5_utilities_init, &
|
2018-11-18 17:11:05 +05:30
|
|
|
HDF5_openFile, &
|
|
|
|
HDF5_closeFile, &
|
2018-12-17 20:45:16 +05:30
|
|
|
HDF5_addAttribute, &
|
2018-08-03 12:23:37 +05:30
|
|
|
HDF5_closeGroup ,&
|
2018-12-05 03:39:25 +05:30
|
|
|
HDF5_openGroup, &
|
|
|
|
HDF5_addGroup, &
|
2018-10-09 17:27:29 +05:30
|
|
|
HDF5_read, &
|
2018-12-12 12:15:20 +05:30
|
|
|
HDF5_write, &
|
|
|
|
HDF5_setLink
|
2018-08-03 12:23:37 +05:30
|
|
|
contains
|
|
|
|
|
2018-11-15 11:58:34 +05:30
|
|
|
subroutine HDF5_utilities_init
|
2018-08-03 12:23:37 +05:30
|
|
|
use, intrinsic :: &
|
2018-10-11 21:30:01 +05:30
|
|
|
iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(SIZE_T) :: typeSize
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
write(6,'(/,a)') ' <<<+- HDF5_Utilities init -+>>>'
|
|
|
|
#include "compilation_info.f90"
|
|
|
|
|
2018-10-09 17:43:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!initialize HDF5 library and check if integer and float type size match
|
|
|
|
call h5open_f(hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_Utilities_init: h5open_f')
|
|
|
|
call h5tget_size_f(H5T_NATIVE_INTEGER,typeSize, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_Utilities_init: h5tget_size_f (int)')
|
|
|
|
if (int(pInt,SIZE_T)/=typeSize) call IO_error(0_pInt,ext_msg='pInt does not match H5T_NATIVE_INTEGER')
|
|
|
|
call h5tget_size_f(H5T_NATIVE_DOUBLE,typeSize, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_Utilities_init: h5tget_size_f (double)')
|
|
|
|
if (int(pReal,SIZE_T)/=typeSize) call IO_error(0_pInt,ext_msg='pReal does not match H5T_NATIVE_DOUBLE')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-15 11:58:34 +05:30
|
|
|
end subroutine HDF5_utilities_init
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
|
2018-10-04 20:30:24 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief open and initializes HDF5 output file
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-15 11:58:34 +05:30
|
|
|
integer(HID_T) function HDF5_openFile(fileName,mode,parallel)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-04 20:30:24 +05:30
|
|
|
implicit none
|
2018-10-09 19:42:32 +05:30
|
|
|
character(len=*), intent(in) :: fileName
|
2018-10-09 18:45:08 +05:30
|
|
|
character, intent(in), optional :: mode
|
2018-11-15 11:58:34 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-09 18:45:08 +05:30
|
|
|
character :: m
|
2018-11-15 11:58:34 +05:30
|
|
|
integer(HID_T) :: plist_id
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-10-04 20:30:24 +05:30
|
|
|
|
2018-10-09 18:45:08 +05:30
|
|
|
if (present(mode)) then
|
|
|
|
m = mode
|
|
|
|
else
|
|
|
|
m = 'r'
|
|
|
|
endif
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-16 11:35:43 +05:30
|
|
|
call h5pcreate_f(H5P_FILE_ACCESS_F, plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5pcreate_f')
|
2018-11-16 11:35:43 +05:30
|
|
|
|
2018-11-15 11:58:34 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_fapl_mpio_f(plist_id, PETSC_COMM_WORLD, MPI_INFO_NULL, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5pset_fapl_mpio_f')
|
2018-11-15 11:58:34 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
|
2018-11-16 11:35:43 +05:30
|
|
|
if (m == 'w') then
|
|
|
|
call h5fcreate_f(fileName,H5F_ACC_TRUNC_F,HDF5_openFile,hdferr,access_prp = plist_id)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fcreate_f')
|
2018-10-09 19:42:32 +05:30
|
|
|
elseif(m == 'a') then
|
2018-11-16 11:35:43 +05:30
|
|
|
call h5fopen_f(fileName,H5F_ACC_RDWR_F,HDF5_openFile,hdferr,access_prp = plist_id)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f (a)')
|
2018-10-09 18:45:08 +05:30
|
|
|
elseif(m == 'r') then
|
2018-11-16 11:35:43 +05:30
|
|
|
call h5fopen_f(fileName,H5F_ACC_RDONLY_F,HDF5_openFile,hdferr,access_prp = plist_id)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f (r)')
|
2018-10-09 18:45:08 +05:30
|
|
|
else
|
2018-11-16 11:35:43 +05:30
|
|
|
call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f unknown access mode')
|
2018-10-09 18:45:08 +05:30
|
|
|
endif
|
2018-10-04 20:30:24 +05:30
|
|
|
|
2018-11-16 11:35:43 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5pclose_f')
|
2018-11-16 11:35:43 +05:30
|
|
|
|
2018-10-04 20:30:24 +05:30
|
|
|
end function HDF5_openFile
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-11-15 11:37:59 +05:30
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 14:27:06 +05:30
|
|
|
!> @brief close the opened HDF5 output file
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_closeFile(fileHandle)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
implicit none
|
|
|
|
integer(HID_T), intent(in) :: fileHandle
|
2018-11-20 19:56:49 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
call h5fclose_f(fileHandle,hdferr)
|
2018-11-20 19:56:49 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_closeFile: h5fclose_f')
|
2018-09-20 23:12:58 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_closeFile
|
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
!> @brief adds a new group to the fileHandle
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HID_T) function HDF5_addGroup(fileHandle,groupName)
|
2018-09-20 23:12:58 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-10-11 21:30:01 +05:30
|
|
|
integer(HID_T), intent(in) :: fileHandle
|
2018-12-05 03:39:25 +05:30
|
|
|
character(len=*), intent(in) :: groupName
|
2018-11-22 00:05:37 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: aplist_id
|
2018-11-22 00:05:37 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
! creating a property list for data access properties
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5pcreate_f(H5P_GROUP_ACCESS_F, aplist_id, hdferr)
|
2018-12-05 03:39:25 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup: h5pcreate_f ('//trim(groupName)//')')
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
! setting I/O mode to collective
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-12-05 03:39:25 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup: h5pset_all_coll_metadata_ops_f ('//trim(groupName)//')')
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
! Create group
|
|
|
|
call h5gcreate_f(fileHandle, trim(groupName), HDF5_addGroup, hdferr, OBJECT_NAMELEN_DEFAULT_F,gapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup: h5gcreate_f ('//trim(groupName)//')')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
end function HDF5_addGroup
|
2018-09-20 23:12:58 +05:30
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-10-04 20:30:24 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-09 20:41:19 +05:30
|
|
|
!> @brief open an existing group of a file
|
2018-10-04 20:30:24 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HID_T) function HDF5_openGroup(fileHandle,groupName)
|
2018-10-04 20:30:24 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-05 03:39:25 +05:30
|
|
|
integer(HID_T), intent(in) :: fileHandle
|
2018-11-09 20:41:19 +05:30
|
|
|
character(len=*), intent(in) :: groupName
|
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-30 14:46:04 +05:30
|
|
|
integer(HID_T) :: aplist_id
|
2018-11-30 22:03:30 +05:30
|
|
|
logical :: is_collective
|
|
|
|
|
2018-11-30 14:46:04 +05:30
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
! creating a property list for data access properties
|
2018-11-30 14:46:04 +05:30
|
|
|
call h5pcreate_f(H5P_GROUP_ACCESS_F, aplist_id, hdferr)
|
2018-12-05 03:39:25 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup: h5pcreate_f ('//trim(groupName)//')')
|
|
|
|
|
2018-11-30 14:46:04 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
2018-12-05 03:39:25 +05:30
|
|
|
! setting I/O mode to collective
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5pget_all_coll_metadata_ops_f(aplist_id, is_collective, hdferr)
|
2018-12-05 03:39:25 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup: h5pset_all_coll_metadata_ops_f ('//trim(groupName)//')')
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! opening the group
|
|
|
|
call h5gopen_f(fileHandle, trim(groupName), HDF5_openGroup, hdferr, gapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup: h5gopen_f ('//trim(groupName)//')')
|
2018-10-04 20:30:24 +05:30
|
|
|
|
2018-12-05 03:39:25 +05:30
|
|
|
end function HDF5_openGroup
|
2018-10-04 20:30:24 +05:30
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-09 20:41:19 +05:30
|
|
|
!> @brief close a group
|
2018-08-03 12:23:37 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_closeGroup(ID)
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(HID_T), intent(in) :: ID
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
call h5gclose_f(ID, hdferr)
|
2018-08-03 19:46:50 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_closeGroup: h5gclose_f (el is ID)', el = int(ID,pInt))
|
2018-08-03 12:23:37 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_closeGroup
|
|
|
|
|
|
|
|
|
2018-11-18 17:11:05 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
!> @brief adds a string attribute to the path given relative to the location
|
2018-11-18 17:11:05 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
subroutine HDF5_addAttribute_str(loc_id,attrLabel,attrValue,path)
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-17 20:45:16 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id
|
2018-11-18 17:11:05 +05:30
|
|
|
character(len=*), intent(in) :: attrLabel, attrValue
|
2018-12-17 20:45:16 +05:30
|
|
|
character(len=*), intent(in), optional :: path
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 17:11:05 +05:30
|
|
|
integer(HID_T) :: attr_id, space_id, type_id
|
2018-12-17 20:45:16 +05:30
|
|
|
logical :: attrExists
|
|
|
|
character(len=256) :: p
|
|
|
|
|
|
|
|
if (present(path)) then
|
|
|
|
p = trim(path)
|
|
|
|
else
|
|
|
|
p = '.'
|
|
|
|
endif
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
call h5screate_f(H5S_SCALAR_F,space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5screate_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5tcopy_f(H5T_NATIVE_CHARACTER, type_id, hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5tcopy_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5tset_size_f(type_id, int(len(trim(attrValue)),HSIZE_T), hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5tset_size_f')
|
|
|
|
call h5aexists_by_name_f(loc_id,trim(p),attrLabel,attrExists,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5aexists_by_name_f')
|
|
|
|
if (attrExists) then
|
|
|
|
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5adelete_by_name_f')
|
|
|
|
endif
|
|
|
|
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),type_id,space_id,attr_id,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5acreate_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5awrite_f(attr_id, type_id, trim(attrValue), int([1],HSIZE_T), hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5awrite_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5aclose_f(attr_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5aclose_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5tclose_f(type_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5tclose_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5sclose_f(space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_str: h5sclose_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
|
2018-12-17 20:45:16 +05:30
|
|
|
end subroutine HDF5_addAttribute_str
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
!> @brief adds a integer attribute to the path given relative to the location
|
2018-11-18 17:11:05 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
subroutine HDF5_addAttribute_pInt(loc_id,attrLabel,attrValue,path)
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-17 20:45:16 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id
|
2018-11-18 17:11:05 +05:30
|
|
|
character(len=*), intent(in) :: attrLabel
|
|
|
|
integer(pInt), intent(in) :: attrValue
|
2018-12-17 20:45:16 +05:30
|
|
|
character(len=*), intent(in), optional :: path
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 17:11:05 +05:30
|
|
|
integer(HID_T) :: attr_id, space_id, type_id
|
2018-12-17 20:45:16 +05:30
|
|
|
logical :: attrExists
|
|
|
|
character(len=256) :: p
|
|
|
|
|
|
|
|
if (present(path)) then
|
|
|
|
p = trim(path)
|
|
|
|
else
|
|
|
|
p = '.'
|
|
|
|
endif
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
call h5screate_f(H5S_SCALAR_F,space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5screate_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5tcopy_f(H5T_NATIVE_INTEGER, type_id, hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5tcopy_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5tset_size_f(type_id, 1_HSIZE_T, hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5tset_size_f')
|
|
|
|
call h5aexists_by_name_f(loc_id,trim(p),attrLabel,attrExists,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5aexists_by_name_f')
|
|
|
|
if (attrExists) then
|
|
|
|
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5adelete_by_name_f')
|
|
|
|
endif
|
|
|
|
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),type_id,space_id,attr_id,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5acreate_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5awrite_f(attr_id, type_id, attrValue, int([1],HSIZE_T), hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5awrite_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5aclose_f(attr_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5aclose_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5tclose_f(type_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5tclose_f')
|
2018-11-18 17:11:05 +05:30
|
|
|
call h5sclose_f(space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pInt: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_addAttribute_pInt
|
2018-11-18 17:11:05 +05:30
|
|
|
|
|
|
|
|
2018-12-15 21:51:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
!> @brief adds a integer attribute to the path given relative to the location
|
2018-12-15 21:51:03 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
subroutine HDF5_addAttribute_pReal(loc_id,attrLabel,attrValue,path)
|
2018-12-15 21:51:03 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-12-17 20:45:16 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id
|
2018-12-15 21:51:03 +05:30
|
|
|
character(len=*), intent(in) :: attrLabel
|
2018-12-17 20:45:16 +05:30
|
|
|
real(pReal), intent(in) :: attrValue
|
|
|
|
character(len=*), intent(in), optional :: path
|
2018-12-15 21:51:03 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: attr_id, space_id, type_id
|
2018-12-17 20:45:16 +05:30
|
|
|
logical :: attrExists
|
|
|
|
character(len=256) :: p
|
|
|
|
|
|
|
|
if (present(path)) then
|
|
|
|
p = trim(path)
|
|
|
|
else
|
|
|
|
p = '.'
|
|
|
|
endif
|
2018-12-15 21:51:03 +05:30
|
|
|
|
|
|
|
call h5screate_f(H5S_SCALAR_F,space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5screate_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5tcopy_f(H5T_NATIVE_DOUBLE, type_id, hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5tcopy_f')
|
|
|
|
call h5tset_size_f(type_id, 8_HSIZE_T, hdferr) ! ToDo
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5tset_size_f')
|
|
|
|
call h5aexists_by_name_f(loc_id,trim(p),attrLabel,attrExists,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5aexists_by_name_f')
|
|
|
|
if (attrExists) then
|
|
|
|
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5adelete_by_name_f')
|
|
|
|
endif
|
|
|
|
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),type_id,space_id,attr_id,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5acreate_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5awrite_f(attr_id, type_id, attrValue, int([1],HSIZE_T), hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5awrite_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5aclose_f(attr_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5aclose_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5tclose_f(type_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5tclose_f')
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5sclose_f(space_id,hdferr)
|
2018-12-17 20:45:16 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addAttribute_pReal: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_addAttribute_pReal
|
2018-12-15 21:51:03 +05:30
|
|
|
|
|
|
|
|
2018-12-12 12:15:20 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief set link to object in results file
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-17 20:45:16 +05:30
|
|
|
subroutine HDF5_setLink(loc_id,target_name,link_name)
|
2018-12-12 12:15:20 +05:30
|
|
|
use hdf5
|
|
|
|
|
|
|
|
implicit none
|
2018-12-17 20:45:16 +05:30
|
|
|
character(len=*), intent(in) :: target_name, link_name
|
|
|
|
integer(HID_T), intent(in) :: loc_id
|
2018-12-12 12:15:20 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
logical :: linkExists
|
|
|
|
|
2018-12-17 20:45:16 +05:30
|
|
|
call h5lexists_f(loc_id, link_name,linkExists, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lexists_soft_f ('//trim(link_name)//')')
|
2018-12-12 12:15:20 +05:30
|
|
|
if (linkExists) then
|
2018-12-17 20:45:16 +05:30
|
|
|
call h5ldelete_f(loc_id,link_name, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5ldelete_soft_f ('//trim(link_name)//')')
|
2018-12-12 12:15:20 +05:30
|
|
|
endif
|
2018-12-17 20:45:16 +05:30
|
|
|
call h5lcreate_soft_f(target_name, loc_id, link_name, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lcreate_soft_f ('//trim(target_name)//' '//trim(link_name)//')')
|
2018-11-18 17:11:05 +05:30
|
|
|
|
2018-12-12 12:15:20 +05:30
|
|
|
end subroutine HDF5_setLink
|
2018-11-27 23:20:51 +05:30
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pReal with 1 dimensions
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal1(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(1) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(1)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal1: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:0),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal1: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal1
|
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pReal with 2 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal2(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(2) :: myStart
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(2)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal2: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:1),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5dopen_f')
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5dget_space_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-30 22:03:30 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5sselect_hyperslab_f')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5dread_f')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-30 22:03:30 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: plist_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-30 22:03:30 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal2: h5dclose_f')
|
2018-11-27 23:20:51 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
end subroutine HDF5_read_pReal2
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pReal with 3 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal3(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(3) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(3)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal3: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:2),sum(readSize)]
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5dopen_f')
|
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal3: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal3
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of type pReal with 4 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal4(loc_id,dataset,datasetName,parallel)
|
2018-11-23 20:19:43 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-23 20:19:43 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-27 23:20:51 +05:30
|
|
|
|
2018-11-23 20:19:43 +05:30
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
2018-11-27 23:20:51 +05:30
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(4) :: myStart
|
2018-11-23 20:19:43 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
2018-11-23 20:19:43 +05:30
|
|
|
localShape = shape(dataset)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-23 20:19:43 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-23 20:19:43 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(4)
|
2018-11-23 20:19:43 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal4: MPI_allreduce')
|
2018-11-23 20:19:43 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-11-27 23:20:51 +05:30
|
|
|
myStart = int([0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:3),sum(readSize)]
|
2018-11-23 20:19:43 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5dopen_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
2018-11-23 20:19:43 +05:30
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5dread_f')
|
2018-11-23 20:19:43 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-23 20:19:43 +05:30
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: plist_id')
|
2018-11-23 20:19:43 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal4: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal4
|
2018-10-09 18:16:57 +05:30
|
|
|
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pReal with 5 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal5(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(5) :: myStart
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(5)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal5: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:4),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5dread_f')
|
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal5: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal5
|
|
|
|
|
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pReal with 6 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal6(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(6) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(6)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal6: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:5),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal6: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal6
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of type pReal with 7 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pReal7(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:,:,:) :: dataset
|
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(7) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(7)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5pset_dxpl_mpio_f')
|
2018-11-30 14:46:04 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pReal7: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:6),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5pset_all_coll_metadata_ops_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr, dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pReal7: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal7
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of type pInt with 1 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt1(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(inout), dimension(:) :: dataset
|
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(1) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(1)
|
|
|
|
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt1: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
|
|
|
|
myStart = int([sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:0),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5pset_all_coll_metadata_ops_f')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt1
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of type pInt with 2 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt2(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(pInt), intent(inout), dimension(:,:) :: dataset
|
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(2) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(2)
|
|
|
|
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt2: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
|
|
|
|
myStart = int([0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:1),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5pset_all_coll_metadata_ops_f')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5dopen_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5dget_space_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5dread_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5sclose_f/memspace_id')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
end subroutine HDF5_read_pInt2
|
2018-10-09 18:16:57 +05:30
|
|
|
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pInt with 3 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt3(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(3) :: myStart
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(3)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt3: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
myStart = int([0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:2),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5pset_all_coll_metadata_ops_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5dopen_f')
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5dget_space_f')
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5sselect_hyperslab_f')
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5dread_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5sclose_f/memspace_id')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
end subroutine HDF5_read_pInt3
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pInt with 4 dimensions
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt4(loc_id,dataset,datasetName,parallel)
|
2018-11-26 20:08:31 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-26 20:08:31 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
2018-11-27 23:20:51 +05:30
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(4) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-23 22:24:02 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-11-26 20:08:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
2018-11-27 23:20:51 +05:30
|
|
|
readSize(worldrank+1) = localShape(4)
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt4: MPI_allreduce')
|
2018-11-26 20:08:31 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
myStart = int([0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:3),sum(readSize)]
|
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5pset_all_coll_metadata_ops_f')
|
2018-11-26 20:08:31 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5dopen_f')
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
2018-11-26 20:08:31 +05:30
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5dget_space_f')
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5sselect_hyperslab_f')
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
2018-11-27 23:20:51 +05:30
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5dread_f')
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!close types, dataspaces
|
2018-11-26 20:08:31 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: plist_id')
|
2018-11-26 20:08:31 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5sclose_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt4
|
2018-10-09 18:16:57 +05:30
|
|
|
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pInt with 5 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt5(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(5) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(5)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt5: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
myStart = int([0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:4),sum(readSize)]
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5pset_all_coll_metadata_ops_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5dopen_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5dget_space_f')
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5sselect_hyperslab_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5dread_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5sclose_f/memspace_id')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
end subroutine HDF5_read_pInt5
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pInt with 6 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt6(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-09-25 20:12:43 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(6) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-09-28 12:11:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(6)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt6: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
myStart = int([0,0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:5),sum(readSize)]
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5pset_all_coll_metadata_ops_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5dopen_f')
|
2018-09-25 20:12:43 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5dget_space_f')
|
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5sselect_hyperslab_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5dread_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5sclose_f/memspace_id')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
end subroutine HDF5_read_pInt6
|
2018-10-05 12:26:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
!> @brief subroutine for reading dataset of type pInt with 7 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_read_pInt7(loc_id,dataset,datasetName,parallel)
|
2018-11-27 23:20:51 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-27 23:20:51 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
readSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id, aplist_id
|
|
|
|
integer(HSIZE_T), dimension(7) :: myStart
|
|
|
|
|
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! creating a property list for data access properties
|
|
|
|
call h5pcreate_f(H5P_DATASET_ACCESS_F, aplist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
allocate(readSize(worldsize), source = 0_pInt)
|
|
|
|
readSize(worldrank+1) = localShape(7)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,readSize,worldsize,MPI_LONG,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-27 23:20:51 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt7: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
myStart = int([0,0,0,0,0,0,sum(readSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:6),sum(readSize)]
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-30 22:03:30 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-30 14:46:04 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
2018-12-15 21:51:03 +05:30
|
|
|
int(localShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt{}: h5screate_simple_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! set I/O mode for read operations to collective
|
|
|
|
call h5pset_all_coll_metadata_ops_f(aplist_id, .true., hdferr)
|
2018-11-30 14:46:04 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5pset_all_coll_metadata_ops_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! open the dataset in the file
|
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr,dapl_id = aplist_id)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5dopen_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-27 23:20:51 +05:30
|
|
|
! get the space_id of dataset in the file
|
|
|
|
call h5dget_space_f(dset_id, filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5dget_space_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5sselect_hyperslab_f')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! read
|
|
|
|
call h5dread_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr, &
|
2018-11-30 22:03:30 +05:30
|
|
|
file_space_id = filespace_id, xfer_prp = plist_id, mem_space_id = memspace_id)
|
2018-11-27 23:20:51 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5pclose_f(plist_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: plist_id')
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5dclose_f')
|
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5sclose_f/filespace_id')
|
2018-11-30 22:03:30 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-27 23:20:51 +05:30
|
|
|
end subroutine HDF5_read_pInt7
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 1 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal1(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(1) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(1)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal1: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:0),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5sselect_hyperslab_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dread_f')
|
2018-10-05 12:26:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
end subroutine HDF5_write_pReal1
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 2 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal2(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(2) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(2)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal2: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:1),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5sselect_hyperslab_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dread_f')
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-05 12:26:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 14:27:06 +05:30
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: plist_id')
|
2018-10-09 14:27:06 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal2
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 3 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal3(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(3) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(3)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal3: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:2),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5sselect_hyperslab_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal3
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 4 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal4(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(4) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(4)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal4: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:3),sum(outputSize)]
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5sselect_hyperslab_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal4
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 5 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal5(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(5) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(5)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal5: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:4),sum(outputSize)]
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5sselect_hyperslab_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal5
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 6 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal6(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(6) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(6)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal6: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:5),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5sselect_hyperslab_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal6
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pReal with 7 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pReal7(loc_id,dataset,datasetName,parallel)
|
2018-11-18 14:17:50 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
real(pReal), intent(inout), dimension(:,:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-18 14:17:50 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
2018-11-26 20:08:31 +05:30
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-18 14:17:50 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(7) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-20 19:56:49 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(7)
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-11-18 14:17:50 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_write_pReal7: MPI_allreduce')
|
|
|
|
endif; endif
|
|
|
|
#endif
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
myStart = int([0,0,0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:6),sum(outputSize)]
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-18 14:17:50 +05:30
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dopen_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-18 14:17:50 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dget_space_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, filespace_id, dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dcreate_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5sselect_hyperslab_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-11-21 20:40:17 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dclose_f')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5sclose_f/filespace_id')
|
2018-11-18 14:17:50 +05:30
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal7
|
|
|
|
|
2018-11-18 14:17:50 +05:30
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-26 20:08:31 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 1 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt1(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(1) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(1)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt1: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:0),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5dopen_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt1: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt1
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 2 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt2(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(2) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(2)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt2: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:1),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt2: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt2
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 3 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt3(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(3) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(3)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt3: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:2),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt3: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt3
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 4 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt4(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(4) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(4)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt4: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:3),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt4: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt4
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 5 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt5(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(5) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(5)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt5: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:4),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt5: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt5
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 6 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt6(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(6) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(6)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt6: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:5),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt6: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt6
|
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
!> @brief subroutine for writing dataset of type pInt with 7 dimensions
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-12-14 16:05:41 +05:30
|
|
|
subroutine HDF5_write_pInt7(loc_id,dataset,datasetName,parallel)
|
2018-11-21 21:27:36 +05:30
|
|
|
use numerics, only: &
|
|
|
|
worldrank, &
|
|
|
|
worldsize
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
implicit none
|
2018-11-20 16:24:51 +05:30
|
|
|
integer(pInt), intent(inout), dimension(:,:,:,:,:,:,:) :: dataset
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T), intent(in) :: loc_id !< file or group handle
|
|
|
|
character(len=*), intent(in) :: datasetName !< name of the dataset in the file
|
2018-11-21 21:27:36 +05:30
|
|
|
logical, intent(in), optional :: parallel
|
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: &
|
|
|
|
globalShape, & !< shape of the dataset (all processes)
|
|
|
|
localShape, & !< shape of the dataset (this process)
|
|
|
|
outputSize !< contribution of all processes
|
|
|
|
integer :: ierr
|
2018-11-20 19:56:49 +05:30
|
|
|
integer(HDF5_ERR_TYPE) :: hdferr
|
2018-11-21 21:27:36 +05:30
|
|
|
integer(HID_T) :: dset_id, filespace_id, memspace_id, plist_id
|
|
|
|
integer(HSIZE_T), dimension(7) :: myStart
|
|
|
|
|
2018-11-26 20:08:31 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! determine shape of dataset
|
|
|
|
localShape = shape(dataset)
|
2018-12-15 21:51:03 +05:30
|
|
|
if (any(localShape(1:size(localShape)) == 0)) return
|
2018-11-26 20:08:31 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
!-------------------------------------------------------------------------------------------------
|
|
|
|
! creating a property list for transfer properties
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-11-21 21:27:36 +05:30
|
|
|
allocate(outputSize(worldsize), source = 0_pInt)
|
|
|
|
outputSize(worldrank+1) = localShape(7)
|
|
|
|
#ifdef PETSc
|
|
|
|
if (present(parallel)) then; if (parallel) then
|
|
|
|
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5pset_dxpl_mpio_f')
|
2018-11-30 22:03:30 +05:30
|
|
|
call MPI_allreduce(MPI_IN_PLACE,outputSize,worldsize,MPI_INT,MPI_SUM,PETSC_COMM_WORLD,ierr) ! get total output size over each process
|
2018-12-14 16:05:41 +05:30
|
|
|
if (ierr /= 0) call IO_error(894_pInt,ext_msg='HDF5_read_pInt7: MPI_allreduce')
|
2018-11-21 21:27:36 +05:30
|
|
|
endif; endif
|
|
|
|
#endif
|
|
|
|
myStart = int([0,0,0,0,0,0,sum(outputSize(1:worldrank))],HSIZE_T)
|
|
|
|
globalShape = [localShape(1:6),sum(outputSize)]
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in memory (local shape)
|
|
|
|
call h5screate_simple_f(size(localShape), int(localShape,HSIZE_T), memspace_id, hdferr, &
|
|
|
|
int(localShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5dopen_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace in file (global shape)
|
2018-12-15 21:51:03 +05:30
|
|
|
call h5screate_simple_f(size(globalShape), int(globalShape,HSIZE_T), filespace_id, hdferr, &
|
2018-11-21 21:27:36 +05:30
|
|
|
int(globalShape,HSIZE_T))
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5dget_space_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, filespace_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5dcreate_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! select a hyperslab (the portion of the current process) in the file
|
|
|
|
call h5sselect_hyperslab_f(filespace_id, H5S_SELECT_SET_F, myStart, int(localShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5sselect_hyperslab_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! write
|
|
|
|
call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(globalShape,HSIZE_T), hdferr,&
|
|
|
|
file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5dread_f')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5pclose_f(plist_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: plist_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-12-14 16:05:41 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_read_pInt7: h5dclose_f')
|
2018-11-21 21:27:36 +05:30
|
|
|
call h5sclose_f(filespace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5sclose_f/filespace_id')
|
|
|
|
call h5sclose_f(memspace_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5sclose_f/memspace_id')
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt7
|
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-11-15 11:37:59 +05:30
|
|
|
end module HDF5_Utilities
|
2018-12-14 16:05:41 +05:30
|
|
|
|
2018-12-15 21:51:03 +05:30
|
|
|
|
2018-12-14 16:05:41 +05:30
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|