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-08-03 12:23:37 +05:30
|
|
|
use prec
|
|
|
|
use IO
|
|
|
|
use HDF5
|
2018-08-05 10:11:35 +05:30
|
|
|
#ifdef PETSc
|
2018-08-03 12:23:37 +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
|
|
|
|
private
|
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-10-10 21:24:55 +05:30
|
|
|
module procedure HDF5_read_pReal_1
|
|
|
|
module procedure HDF5_read_pReal_2
|
|
|
|
module procedure HDF5_read_pReal_3
|
|
|
|
module procedure HDF5_read_pReal_4
|
|
|
|
module procedure HDF5_read_pReal_5
|
|
|
|
module procedure HDF5_read_pReal_6
|
|
|
|
module procedure HDF5_read_pReal_7
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
module procedure HDF5_read_pInt_1
|
|
|
|
module procedure HDF5_read_pInt_2
|
|
|
|
module procedure HDF5_read_pInt_3
|
|
|
|
module procedure HDF5_read_pInt_4
|
|
|
|
module procedure HDF5_read_pInt_5
|
|
|
|
module procedure HDF5_read_pInt_6
|
2018-10-11 21:30:01 +05:30
|
|
|
module procedure HDF5_read_pInt_7 !ABOVE 8 DIMENSIONS IT GIVES ERROR: THE CALL TO H5DREAD_F DOESNT WORK
|
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-10-11 21:30:01 +05:30
|
|
|
module procedure HDF5_write_pInt7 !ABOVE 8 DIMENSIONS IT GIVES ERROR: THE CALL TO H5DREAD_F DOESNT WORK
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-09 17:27:29 +05:30
|
|
|
end interface HDF5_write
|
2018-10-05 12:26:06 +05:30
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
public :: &
|
2018-11-15 11:37:59 +05:30
|
|
|
HDF5_utilities_init, &
|
2018-08-03 12:23:37 +05:30
|
|
|
HDF5_closeGroup ,&
|
2018-10-04 20:30:24 +05:30
|
|
|
HDF5_openGroup2, &
|
2018-09-20 23:12:58 +05:30
|
|
|
HDF5_closeFile, &
|
2018-10-09 14:27:06 +05:30
|
|
|
HDF5_addGroup2, &
|
|
|
|
HDF5_openFile, &
|
2018-10-09 17:27:29 +05:30
|
|
|
HDF5_read, &
|
|
|
|
HDF5_write
|
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
|
|
|
|
integer :: hdferr
|
2018-11-09 20:41:19 +05:30
|
|
|
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-10-04 20:30:24 +05:30
|
|
|
integer :: hdferr
|
|
|
|
|
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)
|
|
|
|
if (hdferr /= 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5pcreate_f')
|
|
|
|
|
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-16 11:35:43 +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)
|
|
|
|
if (hdferr /= 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fcreate_f',el=hdferr)
|
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)
|
|
|
|
if (hdferr /= 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f (a)',el=hdferr)
|
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)
|
|
|
|
if (hdferr /= 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5fopen_f (r)',el=hdferr)
|
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)
|
|
|
|
if (hdferr /= 0) call IO_error(1_pInt,ext_msg='HDF5_openFile: h5pclose_f')
|
|
|
|
|
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 :: hdferr
|
|
|
|
integer(HID_T), intent(in) :: fileHandle
|
|
|
|
call h5fclose_f(fileHandle,hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_closeFile: h5fclose_f',el=hdferr)
|
|
|
|
|
|
|
|
end subroutine HDF5_closeFile
|
|
|
|
|
2018-08-03 12:23:37 +05:30
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 14:27:06 +05:30
|
|
|
!> @brief adds a new group to the fileHandle (additional to addGroup2)
|
2018-09-20 23:12:58 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-09-28 12:11:29 +05:30
|
|
|
integer(HID_T) function HDF5_addGroup2(fileHandle,groupName)
|
2018-09-20 23:12:58 +05:30
|
|
|
use hdf5
|
|
|
|
|
|
|
|
implicit none
|
2018-09-28 12:11:29 +05:30
|
|
|
character(len=*), intent(in) :: groupName
|
2018-10-11 21:30:01 +05:30
|
|
|
integer(HID_T), intent(in) :: fileHandle
|
2018-09-20 23:12:58 +05:30
|
|
|
integer :: hdferr
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-09-28 12:11:29 +05:30
|
|
|
call h5gcreate_f(fileHandle, trim(groupName), HDF5_addGroup2, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup2: h5gcreate_f ('//trim(groupName)//')')
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-09-20 23:12:58 +05:30
|
|
|
end function HDF5_addGroup2
|
|
|
|
|
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-11-09 20:41:19 +05:30
|
|
|
integer(HID_T) function HDF5_openGroup2(FileReadID,groupName)
|
2018-10-04 20:30:24 +05:30
|
|
|
use hdf5
|
|
|
|
|
|
|
|
implicit none
|
2018-11-09 20:41:19 +05:30
|
|
|
character(len=*), intent(in) :: groupName
|
2018-10-04 20:30:24 +05:30
|
|
|
integer :: hdferr
|
2018-10-11 21:30:01 +05:30
|
|
|
integer(HID_T), intent(in) :: FileReadID
|
2018-11-09 20:41:19 +05:30
|
|
|
|
|
|
|
call h5gopen_f(FileReadID, trim(groupName), HDF5_openGroup2, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup2: h5gopen_f ('//trim(groupName)//')')
|
2018-10-04 20:30:24 +05:30
|
|
|
|
|
|
|
end function HDF5_openGroup2
|
|
|
|
|
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)
|
|
|
|
use hdf5
|
|
|
|
|
|
|
|
implicit none
|
|
|
|
integer(HID_T), intent(in) :: ID
|
|
|
|
integer :: hdferr
|
|
|
|
|
|
|
|
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-09-25 20:12:43 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-11 21:30:01 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 1 dimension
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
subroutine HDF5_read_pReal_1(dataset,loc_id,datasetName)
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape1: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape1: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape1: h5dclose_f')
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
end subroutine HDF5_read_pReal_1
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 2 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pReal_2(dataset,loc_id,datasetName)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape2: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape2: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape2: h5dclose_f')
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
end subroutine HDF5_read_pReal_2
|
2018-10-09 14:27:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 3 dimensions
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
subroutine HDF5_read_pReal_3(dataset,loc_id,datasetName)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape3: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape3: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape3: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal_3
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 4 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pReal_4(dataset,loc_id,datasetName)
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape4: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape4: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape4: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal_4
|
|
|
|
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 5 dimensions
|
2018-10-09 18:16:57 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
subroutine HDF5_read_pReal_5(dataset,loc_id,datasetName)
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape5: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape5: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape5: h5dclose_f')
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
end subroutine HDF5_read_pReal_5
|
2018-10-09 18:16:57 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 6 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pReal_6(dataset,loc_id,datasetName)
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape6: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape6: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape6: h5dclose_f')
|
2018-10-09 14:27:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
end subroutine HDF5_read_pReal_6
|
2018-10-09 14:27:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pReal with 7 dimensions
|
2018-10-09 14:27:06 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
subroutine HDF5_read_pReal_7(dataset,loc_id,datasetName)
|
|
|
|
|
2018-10-09 14:27:06 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape7: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape7: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pReal_shape7: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pReal_7
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-11 21:30:01 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 1 dimension
|
2018-10-10 21:24:55 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_1(dataset,loc_id,datasetName)
|
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-09-25 20:12:43 +05:30
|
|
|
integer :: hdferr
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape1: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape1: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape1: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_1
|
2018-09-25 20:12:43 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 2 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_2(dataset,loc_id,datasetName)
|
2018-09-25 20:12:43 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape2: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape2: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape2: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_2
|
|
|
|
|
2018-09-28 12:11:29 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 3 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_3(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape3: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape3: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape3: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_3
|
2018-09-25 20:12:43 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 4 dimensions
|
2018-09-25 20:12:43 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
subroutine HDF5_read_pInt_4(dataset,loc_id,datasetName)
|
|
|
|
|
2018-10-05 12:26:06 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape4: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape4: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape4: h5dclose_f')
|
2018-10-05 12:26:06 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
end subroutine HDF5_read_pInt_4
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 5 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_5(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape5: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape5: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape5: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_5
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 6 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_6(dataset,loc_id,datasetName)
|
|
|
|
|
2018-10-04 20:30:24 +05:30
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape6: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape6: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape6: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_6
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for reading dataset of the type pInt with 7 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_read_pInt_7(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
integer(pInt),dimension(:), allocatable :: myShape
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-09 14:27:06 +05:30
|
|
|
integer :: hdferr
|
2018-10-10 21:24:55 +05:30
|
|
|
integer(HID_T) :: dset_id
|
|
|
|
myShape = shape(dataset)
|
2018-11-09 20:41:19 +05:30
|
|
|
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5dopen_f(loc_id,datasetName,dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape7: h5dopen_f')
|
|
|
|
call h5dread_f(dset_id,H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T),hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape7: h5dread_f')
|
|
|
|
call h5dclose_f(dset_id,hdferr)
|
|
|
|
if (hdferr /= 0) call IO_error(0_pInt,ext_msg='HDF5_read_pInt__shape7: h5dclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_read_pInt_7
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 1 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal1(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
2018-10-09 14:27:06 +05:30
|
|
|
integer(HID_T) :: dset_id, space_id
|
2018-10-10 21:24:55 +05:30
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-09 14:27:06 +05:30
|
|
|
! create dataspace
|
2018-10-10 21:24:55 +05:30
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal1: h5dcreate_f')
|
2018-10-05 12:26:06 +05:30
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-10-10 21:24:55 +05:30
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal1: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal1: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal1
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 2 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal2(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal2: h5dcreate_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
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
2018-10-10 21:24:55 +05:30
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal2: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal2: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal2
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 3 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal3(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal3: h5dcreate_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal3: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal3: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal3
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 4 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal4(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal4: h5dcreate_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal4: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal4: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal4
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 5 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal5(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal5: h5dcreate_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal5: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal5: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal5
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 6 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal6(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal6: h5dcreate_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal6: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal6: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal6
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pReal with 7 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pReal7(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
real(pReal), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pReal7: h5dcreate_f')
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal7: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pReal7: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pReal7
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 1 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt1(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt1: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt1: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt1: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt1
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 2 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt2(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt2: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt2: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt2: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt2
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 3 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt3(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt3: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt3: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt3: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt3
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 4 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt4(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt4: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt4: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt4: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt4
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 5 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt5(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt5: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt5: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt5: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt5
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 6 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt6(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt6: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt6: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt6: h5sclose_f')
|
|
|
|
|
|
|
|
end subroutine HDF5_write_pInt6
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief subroutine for writing dataset of the type pInt with 7 dimensions
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine HDF5_write_pInt7(dataset,loc_id,datasetName)
|
|
|
|
|
|
|
|
implicit none
|
2018-10-10 21:39:10 +05:30
|
|
|
integer(pInt), intent(out), 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
|
|
|
|
|
|
|
|
integer(pInt), dimension(:), allocatable :: myShape !<shape of the dataset
|
|
|
|
integer :: hdferr
|
|
|
|
integer(HID_T) :: dset_id, space_id
|
|
|
|
|
|
|
|
myShape = shape(dataset)
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataspace
|
|
|
|
call h5screate_simple_f(size(myShape), int(myShape,HSIZE_T), space_id, hdferr, &
|
|
|
|
int(myShape,HSIZE_T))
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5screate_simple_f')
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
! create dataset
|
|
|
|
call h5dcreate_f(loc_id, trim(datasetName), H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_write_pInt7: h5dcreate_f')
|
|
|
|
|
|
|
|
CALL h5dwrite_f(dset_id, H5T_NATIVE_INTEGER,dataset,int(myShape,HSIZE_T), hdferr)
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!close types, dataspaces
|
|
|
|
call h5dclose_f(dset_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt7: h5dclose_f')
|
|
|
|
call h5sclose_f(space_id, hdferr)
|
|
|
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_HDF5_write_pInt7: h5sclose_f')
|
|
|
|
|
|
|
|
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
|