cleaned + suggested structure to write data
This commit is contained in:
parent
cb28d10d79
commit
fd2d4d856b
|
@ -332,6 +332,7 @@ subroutine CPFEM_results(inc)
|
||||||
call results_openJobFile
|
call results_openJobFile
|
||||||
write(incChar,*) inc
|
write(incChar,*) inc
|
||||||
call HDF5_closeGroup(results_addGroup(trim('inc'//trim(adjustl(incChar)))))
|
call HDF5_closeGroup(results_addGroup(trim('inc'//trim(adjustl(incChar)))))
|
||||||
|
call results_setLink(trim('inc'//trim(adjustl(incChar))),'current')
|
||||||
call constitutive_results()
|
call constitutive_results()
|
||||||
call results_closeJobFile
|
call results_closeJobFile
|
||||||
|
|
||||||
|
|
|
@ -13,7 +13,7 @@ module HDF5_utilities
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
public
|
||||||
integer(pInt), parameter, private :: &
|
integer(pInt), parameter, private :: &
|
||||||
HDF5_ERR_TYPE = 4_pInt !< kind of the integer return in the HDF5 library
|
HDF5_ERR_TYPE = 4_pInt !< kind of the integer return in the HDF5 library
|
||||||
|
|
||||||
|
@ -71,7 +71,8 @@ module HDF5_utilities
|
||||||
HDF5_openGroup, &
|
HDF5_openGroup, &
|
||||||
HDF5_addGroup, &
|
HDF5_addGroup, &
|
||||||
HDF5_read, &
|
HDF5_read, &
|
||||||
HDF5_write
|
HDF5_write, &
|
||||||
|
HDF5_setLink
|
||||||
contains
|
contains
|
||||||
|
|
||||||
subroutine HDF5_utilities_init
|
subroutine HDF5_utilities_init
|
||||||
|
@ -304,7 +305,28 @@ subroutine HDF5_addIntegerAttribute(entity,attrLabel,attrValue)
|
||||||
|
|
||||||
end subroutine HDF5_addIntegerAttribute
|
end subroutine HDF5_addIntegerAttribute
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief set link to object in results file
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
subroutine HDF5_setLink(fileHandle,path,link)
|
||||||
|
use hdf5
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
character(len=*), intent(in) :: path, link
|
||||||
|
integer(HID_T), intent(in) :: fileHandle
|
||||||
|
integer(HDF5_ERR_TYPE) :: hdferr
|
||||||
|
logical :: linkExists
|
||||||
|
|
||||||
|
call h5lexists_f(fileHandle, link,linkExists, hdferr)
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lexists_soft_f ('//trim(link)//')')
|
||||||
|
if (linkExists) then
|
||||||
|
call h5ldelete_f(fileHandle,link, hdferr)
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5ldelete_soft_f ('//trim(link)//')')
|
||||||
|
endif
|
||||||
|
call h5lcreate_soft_f(path, fileHandle, link, hdferr)
|
||||||
|
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lcreate_soft_f ('//trim(path)//' '//trim(link)//')')
|
||||||
|
|
||||||
|
end subroutine HDF5_setLink
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief subroutine for reading dataset of type pReal with 1 dimensions
|
!> @brief subroutine for reading dataset of type pReal with 1 dimensions
|
||||||
|
|
|
@ -1193,10 +1193,25 @@ subroutine constitutive_results()
|
||||||
PLASTICITY_DISLOUCLA_ID, &
|
PLASTICITY_DISLOUCLA_ID, &
|
||||||
PLASTICITY_NONLOCAL_ID
|
PLASTICITY_NONLOCAL_ID
|
||||||
#if defined(PETSc) || defined(DAMASKHDF5)
|
#if defined(PETSc) || defined(DAMASKHDF5)
|
||||||
|
use results
|
||||||
|
use HDF5_utilities
|
||||||
|
use config, only: &
|
||||||
|
config_name_phase => phase_name ! anticipate logical name
|
||||||
|
use material, only: &
|
||||||
|
material_phase_plasticity_type => phase_plasticity
|
||||||
use plastic_phenopowerlaw, only: &
|
use plastic_phenopowerlaw, only: &
|
||||||
plastic_phenopowerlaw_results
|
plastic_phenopowerlaw_results
|
||||||
|
|
||||||
call plastic_phenopowerlaw_results
|
implicit none
|
||||||
|
integer(pInt) :: p
|
||||||
|
call HDF5_closeGroup(results_addGroup('current/phase'))
|
||||||
|
do p=1,size(config_name_phase)
|
||||||
|
call HDF5_closeGroup(results_addGroup('current/phase/'//trim(config_name_phase(p))))
|
||||||
|
if (material_phase_plasticity_type(p) == PLASTICITY_PHENOPOWERLAW_ID) then
|
||||||
|
call plastic_phenopowerlaw_results(p,'current/phase/'//trim(config_name_phase(p)))
|
||||||
|
endif
|
||||||
|
enddo
|
||||||
|
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -749,8 +749,29 @@ end function plastic_phenopowerlaw_postResults
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief writes results to HDF5 output file
|
!> @brief writes results to HDF5 output file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine plastic_phenopowerlaw_results()
|
subroutine plastic_phenopowerlaw_results(instance,group)
|
||||||
#if defined(PETSc) || defined(DAMASKHDF5)
|
#if defined(PETSc) || defined(DAMASKHDF5)
|
||||||
|
use results
|
||||||
|
|
||||||
|
implicit none
|
||||||
|
integer(pInt), intent(in) :: instance
|
||||||
|
character(len=*) :: group
|
||||||
|
integer(pInt) :: o
|
||||||
|
|
||||||
|
associate(prm => param(instance), stt => state(instance))
|
||||||
|
outputsLoop: do o = 1_pInt,size(prm%outputID)
|
||||||
|
select case(prm%outputID(o))
|
||||||
|
case (resistance_slip_ID)
|
||||||
|
call results_writeVectorDataset(group,stt%xi_slip,'xi_slip','Pa')
|
||||||
|
case (accumulatedshear_slip_ID)
|
||||||
|
call results_writeVectorDataset(group,stt%gamma_slip,'gamma_slip','1/s')
|
||||||
|
end select
|
||||||
|
enddo outputsLoop
|
||||||
|
end associate
|
||||||
|
!results_writeVectorDataset
|
||||||
|
#else
|
||||||
|
integer(pInt), intent(in) :: instance
|
||||||
|
character(len=*) :: group
|
||||||
#endif
|
#endif
|
||||||
end subroutine plastic_phenopowerlaw_results
|
end subroutine plastic_phenopowerlaw_results
|
||||||
|
|
||||||
|
|
265
src/results.f90
265
src/results.f90
|
@ -34,8 +34,7 @@ module results
|
||||||
results_addGroup, &
|
results_addGroup, &
|
||||||
results_openGroup, &
|
results_openGroup, &
|
||||||
results_writeVectorDataset, &
|
results_writeVectorDataset, &
|
||||||
HDF5_writeScalarDataset, &
|
results_setLink, &
|
||||||
HDF5_writeTensorDataset, &
|
|
||||||
HDF5_removeLink
|
HDF5_removeLink
|
||||||
contains
|
contains
|
||||||
|
|
||||||
|
@ -116,24 +115,16 @@ end function results_addGroup
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief set link to object in results file
|
!> @brief set link to object in results file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine HDF5_setLink(path,link)
|
subroutine results_setLink(path,link)
|
||||||
use hdf5
|
use hdf5_utilities, only: &
|
||||||
|
HDF5_setLink
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
character(len=*), intent(in) :: path, link
|
character(len=*), intent(in) :: path, link
|
||||||
integer :: hdferr
|
|
||||||
logical :: linkExists
|
|
||||||
|
|
||||||
call h5lexists_f(resultsFile, link,linkExists, hdferr)
|
call HDF5_setLink(resultsFile,path,link)
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lexists_soft_f ('//trim(link)//')')
|
|
||||||
if (linkExists) then
|
|
||||||
call h5ldelete_f(resultsFile,link, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5ldelete_soft_f ('//trim(link)//')')
|
|
||||||
endif
|
|
||||||
call h5lcreate_soft_f(path, resultsFile, link, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_setLink: h5lcreate_soft_f ('//trim(path)//' '//trim(link)//')')
|
|
||||||
|
|
||||||
end subroutine HDF5_setLink
|
end subroutine results_setLink
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief remove link to an object
|
!> @brief remove link to an object
|
||||||
|
@ -952,253 +943,21 @@ subroutine HDF5_mappingCells(mapping)
|
||||||
|
|
||||||
end subroutine HDF5_mappingCells
|
end subroutine HDF5_mappingCells
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief creates a new 3D Tensor dataset in the given group location !!!TODO: really necessary?
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine HDF5_addTensor3DDataset(group,Nnodes,tensorSize,label,SIunit)
|
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(HID_T), intent(in) :: group
|
|
||||||
integer(pInt), intent(in) :: Nnodes, tensorSize
|
|
||||||
character(len=*), intent(in) :: SIunit, label
|
|
||||||
|
|
||||||
integer :: hdferr
|
|
||||||
integer(HID_T) :: space_id, dset_id
|
|
||||||
integer(HSIZE_T), dimension(3) :: dataShape
|
|
||||||
|
|
||||||
dataShape = int([tensorSize,tensorSize,Nnodes], HSIZE_T)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create dataspace
|
|
||||||
call h5screate_simple_f(3, dataShape, space_id, hdferr, dataShape)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addTensor3DDataset: h5screate_simple_f')
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create Dataset
|
|
||||||
call h5dcreate_f(group, trim(label),H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addTensor3DDataset: h5dcreate_f')
|
|
||||||
call HDF5_addStringAttribute(dset_id,'unit',trim(SIunit))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!close types, dataspaces
|
|
||||||
call h5dclose_f(dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addTensor3DDataset: h5dclose_f')
|
|
||||||
call h5sclose_f(space_id, hdferr)
|
|
||||||
|
|
||||||
end subroutine HDF5_addTensor3DDataset
|
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief creates a new vector dataset in the given group location
|
!> @brief creates a new vector dataset in the given group location
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine results_writeVectorDataset(group,dataset,label,SIunit)
|
subroutine results_writeVectorDataset(group,dataset,label,SIunit)
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(HID_T), intent(in) :: group
|
character(len=*), intent(in) :: SIunit,label,group
|
||||||
character(len=*), intent(in) :: SIunit,label
|
real(pReal), intent(inout), dimension(:,:) :: dataset
|
||||||
real(pReal), intent(in), dimension(:,:) :: dataset
|
integer(HID_T) :: groupHandle
|
||||||
|
|
||||||
integer :: hdferr, vectorSize
|
|
||||||
integer(HID_T) :: dset_id, space_id, memspace, plist_id
|
|
||||||
|
|
||||||
integer(HSIZE_T), dimension(2) :: counter
|
|
||||||
integer(HSSIZE_T), dimension(2) :: fileOffset
|
|
||||||
|
|
||||||
if(any(shape(dataset) == 0)) return
|
|
||||||
|
|
||||||
vectorSize = size(dataset,1)
|
|
||||||
call h5dopen_f(group, label, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeVectorDataset: h5dopen_f')
|
|
||||||
|
|
||||||
|
groupHandle = results_openGroup(group)
|
||||||
|
call HDF5_write(dataset,groupHandle,label)
|
||||||
|
call HDF5_closeGroup(groupHandle)
|
||||||
|
|
||||||
end subroutine results_writeVectorDataset
|
end subroutine results_writeVectorDataset
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief creates a new tensor dataset in the given group location
|
|
||||||
! by default, a 3x3 tensor is assumed !!!TODO: really necessary?
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine HDF5_writeTensorDataset(group,dataset,label,SIunit,dataspace_size,mpiOffset)
|
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(HID_T), intent(in) :: group
|
|
||||||
character(len=*), intent(in) :: SIunit,label
|
|
||||||
integer(pInt), intent(in) :: dataspace_size, mpiOffset
|
|
||||||
real(pReal), intent(in), dimension(:,:,:) :: dataset
|
|
||||||
|
|
||||||
integer :: hdferr, tensorSize
|
|
||||||
integer(HID_T) :: dset_id, space_id, memspace, plist_id
|
|
||||||
|
|
||||||
integer(HSIZE_T), dimension(3) :: counter
|
|
||||||
integer(HSSIZE_T), dimension(3) :: fileOffset
|
|
||||||
|
|
||||||
if(any(shape(dataset) == 0)) return
|
|
||||||
|
|
||||||
tensorSize = size(dataset,1)
|
|
||||||
|
|
||||||
call HDF5_addTensor3DDataset(group,dataspace_size,tensorSize,label,SIunit)
|
|
||||||
call h5dopen_f(group, label, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5dopen_f')
|
|
||||||
|
|
||||||
! Define and select hyperslabs
|
|
||||||
counter(1) = tensorSize ! how big i am
|
|
||||||
counter(2) = tensorSize
|
|
||||||
counter(3) = size(dataset,3)
|
|
||||||
fileOffset(1) = 0 ! where i start to write my data
|
|
||||||
fileOffset(2) = 0
|
|
||||||
fileOffset(3) = mpiOffset
|
|
||||||
|
|
||||||
call h5screate_simple_f(3, counter, memspace, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5screate_simple_f')
|
|
||||||
call h5dget_space_f(dset_id, space_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5dget_space_f')
|
|
||||||
call h5sselect_hyperslab_f(space_id, H5S_SELECT_SET_F, fileOffset, counter, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5sselect_hyperslab_f')
|
|
||||||
|
|
||||||
! Create property list for collective dataset write
|
|
||||||
#ifdef PETSc
|
|
||||||
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5pcreate_f')
|
|
||||||
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5pset_dxpl_mpio_f')
|
|
||||||
#endif
|
|
||||||
|
|
||||||
! Write the dataset collectively
|
|
||||||
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE, dataset, int([tensorSize, dataspace_size],HSIZE_T), hdferr, &
|
|
||||||
file_space_id = space_id, mem_space_id = memspace, xfer_prp = plist_id)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeTensorDataset: h5dwrite_f')
|
|
||||||
|
|
||||||
call h5sclose_f(space_id, hdferr)
|
|
||||||
call h5sclose_f(memspace, hdferr)
|
|
||||||
call h5dclose_f(dset_id, hdferr)
|
|
||||||
call h5pclose_f(plist_id, hdferr)
|
|
||||||
|
|
||||||
end subroutine HDF5_writeTensorDataset
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief adds a new vector dataset to the given group location
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine HDF5_addVectorDataset(group,nnodes,vectorSize,label,SIunit)
|
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(HID_T), intent(in) :: group
|
|
||||||
integer(pInt), intent(in) :: nnodes,vectorSize
|
|
||||||
character(len=*), intent(in) :: SIunit,label
|
|
||||||
|
|
||||||
integer :: hdferr
|
|
||||||
integer(HID_T) :: space_id, dset_id
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create dataspace
|
|
||||||
call h5screate_simple_f(2, int([vectorSize,Nnodes],HSIZE_T), space_id, hdferr, &
|
|
||||||
int([vectorSize,Nnodes],HSIZE_T))
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addVectorDataset: h5screate_simple_f')
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create Dataset
|
|
||||||
call h5dcreate_f(group, trim(label), H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addVectorDataset: h5dcreate_f')
|
|
||||||
call HDF5_addStringAttribute(dset_id,'unit',trim(SIunit))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!close types, dataspaces
|
|
||||||
call h5dclose_f(dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addVectorDataset: h5dclose_f')
|
|
||||||
call h5sclose_f(space_id, hdferr)
|
|
||||||
|
|
||||||
end subroutine HDF5_addVectorDataset
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief writes to a new scalar dataset in the given group location
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine HDF5_writeScalarDataset(group,dataset,label,SIunit,dataspace_size,mpiOffset)
|
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(HID_T), intent(in) :: group
|
|
||||||
character(len=*), intent(in) :: SIunit,label
|
|
||||||
integer(pInt), intent(in) :: dataspace_size, mpiOffset
|
|
||||||
real(pReal), intent(in), dimension(:) :: dataset
|
|
||||||
|
|
||||||
integer :: hdferr, nNodes
|
|
||||||
integer(HID_T) :: dset_id, space_id, memspace, plist_id
|
|
||||||
|
|
||||||
integer(HSIZE_T), dimension(1) :: counter
|
|
||||||
integer(HSIZE_T), dimension(1) :: fileOffset
|
|
||||||
|
|
||||||
nNodes = size(dataset)
|
|
||||||
if (nNodes < 1) return
|
|
||||||
|
|
||||||
call HDF5_addScalarDataset(group,dataspace_size,label,SIunit)
|
|
||||||
call h5dopen_f(group, label, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5dopen_f')
|
|
||||||
|
|
||||||
! Define and select hyperslabs
|
|
||||||
counter = size(dataset) ! how big i am
|
|
||||||
fileOffset = mpiOffset ! where i start to write my data
|
|
||||||
|
|
||||||
call h5screate_simple_f(1, counter, memspace, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5screate_simple_f')
|
|
||||||
call h5dget_space_f(dset_id, space_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5dget_space_f')
|
|
||||||
call h5sselect_hyperslab_f(space_id, H5S_SELECT_SET_F, fileOffset, counter, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5sselect_hyperslab_f')
|
|
||||||
|
|
||||||
! Create property list for collective dataset write
|
|
||||||
#ifdef PETSc
|
|
||||||
call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5pcreate_f')
|
|
||||||
call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5pset_dxpl_mpio_f')
|
|
||||||
#endif
|
|
||||||
|
|
||||||
! Write the dataset collectively
|
|
||||||
call h5dwrite_f(dset_id, H5T_NATIVE_DOUBLE, dataset, int([dataspace_size],HSIZE_T), hdferr, &
|
|
||||||
file_space_id = space_id, mem_space_id = memspace, xfer_prp = plist_id)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_writeScalarDataset: h5dwrite_f')
|
|
||||||
|
|
||||||
call h5sclose_f(space_id, hdferr)
|
|
||||||
call h5sclose_f(memspace, hdferr)
|
|
||||||
call h5dclose_f(dset_id, hdferr)
|
|
||||||
call h5pclose_f(plist_id, hdferr)
|
|
||||||
|
|
||||||
end subroutine HDF5_writeScalarDataset
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!> @brief adds a new scalar dataset to the given group location
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
subroutine HDF5_addScalarDataset(group,nnodes,label,SIunit)
|
|
||||||
use hdf5
|
|
||||||
|
|
||||||
implicit none
|
|
||||||
integer(HID_T), intent(in) :: group
|
|
||||||
integer(pInt), intent(in) :: nnodes
|
|
||||||
character(len=*), intent(in) :: SIunit,label
|
|
||||||
|
|
||||||
integer :: hdferr
|
|
||||||
integer(HID_T) :: space_id, dset_id
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create dataspace
|
|
||||||
call h5screate_simple_f(1, int([Nnodes],HSIZE_T), space_id, hdferr, &
|
|
||||||
int([Nnodes],HSIZE_T))
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addScalarDataset: h5screate_simple_f')
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! create Dataset
|
|
||||||
call h5dcreate_f(group, trim(label),H5T_NATIVE_DOUBLE, space_id, dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addScalarDataset: h5dcreate_f')
|
|
||||||
call HDF5_addStringAttribute(dset_id,'unit',trim(SIunit))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
!close types, dataspaces
|
|
||||||
call h5dclose_f(dset_id, hdferr)
|
|
||||||
if (hdferr < 0) call IO_error(1_pInt,ext_msg='HDF5_addScalarDataset: h5dclose_f')
|
|
||||||
call h5sclose_f(space_id, hdferr)
|
|
||||||
|
|
||||||
end subroutine HDF5_addScalarDataset
|
|
||||||
|
|
||||||
end module results
|
end module results
|
||||||
|
|
Loading…
Reference in New Issue